source: trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/start2archive.F @ 3946

Last change on this file since 3946 was 3946, checked in by emillour, 4 weeks ago

Generic PCM:
Minor fix in start2archive: the dimension for albedoS (albedo recasted on the
dynamics scalar grid) shoudld be ip1jmp1.
EM

File size: 21.7 KB
Line 
1c=======================================================================
2      PROGRAM start2archive
3c=======================================================================
4c
5c
6c   Date:    01/1997
7c   ----
8c
9c
10c   Objet:   Passage des  fichiers netcdf d'etat initial "start" et
11c   -----    "startfi" a un fichier netcdf unique "start_archive"
12c
13c  "start_archive" est une banque d'etats initiaux:
14c  On peut stocker plusieurs etats initiaux dans un meme fichier "start_archive"
15c    (Veiller dans ce cas avoir un day_ini different pour chacun des start)
16c
17c
18c
19c=======================================================================
20
21      use infotrac, only: infotrac_init, nqtot, tname
22      USE comsoil_h
23      USE radinc_h, only : L_NSPECTV ! number of spectral bands in the visible
24!      use slab_ice_h, only: noceanmx
25      USE ocean_slab_mod, ONLY: nslay
26      USE ioipsl_getincom, only: getin
27      USE planete_mod, only: year_day
28      USE mod_const_mpi, ONLY: COMM_LMDZ
29      USE control_mod, only: planet_type
30      USE callkeys_mod, ONLY: ok_slab_ocean
31      use filtreg_mod, only: inifilr
32      USE comvert_mod, ONLY: ap,bp
33      USE comconst_mod, ONLY: daysec,dtphys,rad,g,r,cpp
34      USE temps_mod, ONLY: day_ini
35      USE iniphysiq_mod, ONLY: iniphysiq
36      use phys_state_var_mod, only: phys_state_var_init
37      use phyetat0_mod, only: phyetat0
38      use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd,
39     &                          east_gwstress, west_gwstress
40      use exner_hyb_m, only: exner_hyb
41      use parse_args_mod, only: parse_args
42
43      implicit none
44
45      include "dimensions.h"
46      integer, parameter :: ngridmx = (2+(jjm-1)*iim - 1/jjm)
47      include "paramet.h"
48      include "comdissip.h"
49      include "comgeom.h"
50
51      include "netcdf.inc"
52c-----------------------------------------------------------------------
53c   Declarations
54c-----------------------------------------------------------------------
55
56c variables dynamiques du GCM
57c -----------------------------
58      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
59      REAL teta(ip1jmp1,llm)                    ! temperature potentielle
60      REAL,ALLOCATABLE :: q(:,:,:)   ! champs advectes
61      REAL pks(ip1jmp1)                      ! exner (f pour filtre)
62      REAL pk(ip1jmp1,llm)
63      REAL pkf(ip1jmp1,llm)
64      REAL phis(ip1jmp1)                     ! geopotentiel au sol
65      REAL masse(ip1jmp1,llm)                ! masse de l'atmosphere
66      REAL ps(ip1jmp1)                       ! pression au sol
67      REAL p3d(iip1, jjp1, llm+1)            ! pression aux interfaces
68     
69c Variables defined on the physics grid (ngridmx columns)
70c ------------------------------------------------------
71      REAL tsurf(ngridmx)        ! Surface temperature
72      REAL,ALLOCATABLE :: tsoil(:,:) ! Soil temperature
73      REAL co2ice(ngridmx)        ! CO2 ice layer
74      REAL q2(ngridmx,llm+1)
75      REAL,ALLOCATABLE :: qsurf(:,:)
76      REAL emis(ngridmx)
77      REAL :: albedo(ngridmx,L_NSPECTV) ! spectral surface albedo
78      INTEGER start,length
79      PARAMETER (length = 100)
80      REAL tab_cntrl_fi(length) ! tableau des parametres de startfi
81      REAL tab_cntrl_dyn(length) ! tableau des parametres de start
82      INTEGER*4 day_ini_fi
83
84!     added by FF for cloud fraction setup
85      REAL hice(ngridmx)
86      REAL cloudfrac(ngridmx,llm),totalcloudfrac(ngridmx)
87
88!     added by BC for slab ocean
89      REAL rnat(ngridmx),pctsrf_sic(ngridmx),sea_ice(ngridmx)
90      REAL, ALLOCATABLE :: tslab(:,:)
91      REAL tsea_ice(ngridmx),tice(ngridmx)
92
93
94c Variables defined on the scalar grid
95c ------------------------------------
96      REAL T(ip1jmp1,llm),us(ip1jmp1,llm),vs(ip1jmp1,llm)
97      REAL tsurfS(ip1jmp1)
98      REAL,ALLOCATABLE :: tsoilS(:,:)
99      REAL,ALLOCATABLE :: ithS(:,:) ! Soil Thermal Inertia
100      REAL co2iceS(ip1jmp1)
101      REAL q2S(ip1jmp1,llm+1)
102      REAL,ALLOCATABLE :: qsurfS(:,:)
103      REAL emisS(ip1jmp1)
104      REAL :: albedoS(ip1jmp1) ! surface albedo assumed same at all wavelengths
105
106!     added by FF for cloud fraction setup
107      REAL hiceS(ip1jmp1)
108      REAL cloudfracS(ip1jmp1,llm),totalcloudfracS(ip1jmp1)
109
110!     added by BC for slab ocean
111      REAL rnatS(ip1jmp1),pctsrf_sicS(ip1jmp1),sea_iceS(ip1jmp1)
112      REAL, ALLOCATABLE :: tslabS(:,:)
113      REAL tsea_iceS(ip1jmp1),ticeS(ip1jmp1)
114
115!     For non-orographic GW
116      REAL du_nonoro_gwdS(ip1jmp1,llm),dv_nonoro_gwdS(ip1jmp1,llm)
117      REAL east_gwstressS(ip1jmp1,llm),west_gwstressS(ip1jmp1,llm)
118
119c Variables intermediaires : vent naturel, mais pas coord scalaire
120c----------------------------------------------------------------
121      REAL vn(ip1jm,llm),un(ip1jmp1,llm)
122
123c Autres  variables
124c -----------------
125      LOGICAL startdrs
126      INTEGER Lmodif
127
128      REAL ptotal, co2icetotal
129      REAL timedyn,timefi !fraction du jour dans start, startfi
130      REAL date
131
132      CHARACTER*2 str2
133      CHARACTER*80 fichier
134      data  fichier /'startfi'/
135
136      INTEGER ij, l,i,j,isoil,iq
137      character*80      fichnom
138      integer :: ierr,ntime
139      integer :: nq,numvanle
140      character(len=30) :: txt ! to store some text
141
142c Netcdf
143c-------
144      integer varid,dimid,timelen
145      INTEGER nid,nid1
146
147c-----------------------------------------------------------------------
148c   Initialisations
149c-----------------------------------------------------------------------
150      ! Parse command-line options
151      call parse_args()
152
153      call conf_gcm(99,.true.)
154
155c=======================================================================
156c Lecture des donnees
157c=======================================================================
158! Load tracer number and names:
159      call infotrac_init
160
161! allocate arrays:
162      allocate(q(ip1jmp1,llm,nqtot))
163      allocate(qsurf(ngridmx,nqtot))
164      allocate(qsurfS(ip1jmp1,nqtot))
165      allocate(tslab(ngridmx,nslay)) !Added by SB for slab ocean
166      allocate(tslabS(ip1jmp1,nslay)) !Added by SB for slab ocean
167! other array allocations:
168!      call ini_comsoil_h(ngridmx) ! done via iniphysiq
169
170      fichnom = 'start.nc'
171      CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
172     .       ps,phis,timedyn)
173
174! load 'controle' array from dynamics start file
175
176       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
177       IF (ierr.NE.NF_NOERR) THEN
178         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
179        CALL abort_physic("start2archive",
180     &       "Pb d'ouverture du ficher start.nc",1)
181       ENDIF
182                                               
183      ierr = NF_INQ_VARID (nid1, "controle", varid)
184      IF (ierr .NE. NF_NOERR) THEN
185       CALL abort_physic("start2archive",
186     &      "Le champ <controle> est absent",1)
187      ENDIF
188#ifdef NC_DOUBLE
189       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_dyn)
190#else
191      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_dyn)
192#endif
193       IF (ierr .NE. NF_NOERR) THEN
194          CALL abort_physic("start2archive",
195     &         "Lecture echoue pour <controle>",1)
196       ENDIF
197
198      ierr = NF_CLOSE(nid1)
199
200! Get value of the "subsurface_layers" dimension from physics start file
201      fichnom = 'startfi.nc'
202      ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
203       IF (ierr.NE.NF_NOERR) THEN
204         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
205        CALL abort_physic("start2archive",
206     &       "Pb d'ouverture du ficher startfi.nc",1)
207       ENDIF
208      ierr = NF_INQ_DIMID(nid1,"subsurface_layers",varid)
209      IF (ierr .NE. NF_NOERR) THEN
210       CALL abort_physic("start2archive",
211     &      "No subsurface_layers dimension",1)
212      ENDIF
213      ierr = NF_INQ_DIMLEN(nid1,varid,nsoilmx)
214      IF (ierr .NE. NF_NOERR) THEN
215       CALL abort_physic("start2archive",
216     &      "Failed reading subsurface_layers value",1)
217      ENDIF
218      ierr = NF_CLOSE(nid1)
219     
220      ! allocate arrays of nsoilmx size
221      allocate(tsoil(ngridmx,nsoilmx))
222      allocate(tsoilS(ip1jmp1,nsoilmx))
223      allocate(ithS(ip1jmp1,nsoilmx))
224
225c-----------------------------------------------------------------------
226c   Initialisations
227c-----------------------------------------------------------------------
228
229      CALL defrun_new(99, .FALSE. )
230      call iniconst
231      call inigeom
232      call inifilr
233
234! Initialize the physics
235         CALL iniphysiq(iim,jjm,llm,
236     &                  (jjm-1)*iim+2,comm_lmdz,
237     &                  daysec,day_ini,dtphys,
238     &                  rlatu,rlatv,rlonu,rlonv,
239     &                  aire,cu,cv,rad,g,r,cpp,
240     &                  1)
241
242      fichnom = 'startfi.nc'
243      Lmodif=0
244
245! Allocate saved arrays (as in firstcall of physiq)
246      call phys_state_var_init(nqtot)
247     
248! Initialize tracer names, indexes and properties
249      CALL initracer(ngridmx,nqtot)
250
251      CALL phyetat0(.true.,ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
252     .      day_ini_fi,timefi,
253     .      tsurf,tsoil,emis,albedo,q2,qsurf,
254!       change FF 05/2011
255     .       cloudfrac,totalcloudfrac,hice,
256!       change BC 05/2014, SB 08/2024
257     .       rnat,pctsrf_sic,tslab,tsea_ice,tice,sea_ice)
258
259
260
261
262! load 'controle' array from physics start file
263
264       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
265       IF (ierr.NE.NF_NOERR) THEN
266         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
267        CALL abort_physic("start2archive",
268     &       "Pb d'ouverture du ficher startfi.nc",1)
269       ENDIF
270                                               
271      ierr = NF_INQ_VARID (nid1, "controle", varid)
272      IF (ierr .NE. NF_NOERR) THEN
273       CALL abort_physic("start2archive",
274     &       "Le champ <controle> est absent",1)
275      ENDIF
276#ifdef NC_DOUBLE
277       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_fi)
278#else
279      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_fi)
280#endif
281       IF (ierr .NE. NF_NOERR) THEN
282          CALL abort_physic("start2archive",
283     &         "Lecture echoue pour <controle>",1)
284       ENDIF
285
286      ierr = NF_CLOSE(nid1)
287
288
289c-----------------------------------------------------------------------
290c Controle de la synchro
291c-----------------------------------------------------------------------
292!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
293      if ((day_ini_fi.ne.day_ini)) then
294        call abort_physic("start2archive",
295     &       "Probleme de Synchro entre start et startfi",1)
296      endif
297
298
299c *****************************************************************
300c    Option : Reinitialisation des dates dans la premieres annees :
301       do while (day_ini.ge.year_day)
302          day_ini=day_ini-year_day
303       enddo
304c *****************************************************************
305
306      CALL pression(ip1jmp1, ap, bp, ps, p3d)
307      call exner_hyb(ip1jmp1, ps, p3d, pks, pk, pkf)
308
309c=======================================================================
310c Transformation EN VARIABLE NATURELLE / GRILLE SCALAIRE si necessaire
311c=======================================================================
312c  Les variables modeles dependent de la resolution. Il faut donc
313c  eliminer les facteurs responsables de cette dependance
314c  (pour utiliser newstart)
315c=======================================================================
316
317c-----------------------------------------------------------------------
318c Vent   (depend de la resolution horizontale)
319c-----------------------------------------------------------------------
320c
321c ucov --> un  et  vcov --> vn
322c un --> us  et   vn --> vs
323c
324c-----------------------------------------------------------------------
325
326      call covnat(llm,ucov, vcov, un, vn)
327      call wind_scal(un,vn,us,vs)
328
329c-----------------------------------------------------------------------
330c Temperature  (depend de la resolution verticale => de "sigma.def")
331c-----------------------------------------------------------------------
332c
333c h --> T
334c
335c-----------------------------------------------------------------------
336
337      DO l=1,llm
338         DO ij=1,ip1jmp1
339            T(ij,l)=teta(ij,l)*pk(ij,l)/cpp !mars deduit de l'equation dans newstart
340         ENDDO
341      ENDDO
342
343c-----------------------------------------------------------------------
344c Variable physique
345c-----------------------------------------------------------------------
346c
347c tsurf --> tsurfS
348c co2ice --> co2iceS
349c tsoil --> tsoilS
350c emis --> emisS
351c q2 --> q2S
352c qsurf --> qsurfS
353c
354c-----------------------------------------------------------------------
355
356      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsurf,tsurfS)
357!      call gr_fi_dyn(1,ngridmx,iip1,jjp1,co2ice,co2iceS)
358      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,tsoil,tsoilS)
359      ! Note: thermal inertia "inertiedat" is in comsoil.h
360      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
361      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis,emisS)
362      call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedo(1,1),albedoS)
363      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
364      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf,qsurfS)
365      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,cloudfrac,cloudfracS)
366      call gr_fi_dyn(1,ngridmx,iip1,jjp1,hice,hiceS)
367      call gr_fi_dyn(1,ngridmx,iip1,jjp1,totalcloudfrac,totalcloudfracS)
368
369      call gr_fi_dyn(1,ngridmx,iip1,jjp1,rnat,rnatS)
370      call gr_fi_dyn(1,ngridmx,iip1,jjp1,pctsrf_sic,pctsrf_sicS)
371      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsea_ice,tsea_iceS)
372      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tice,ticeS)
373      call gr_fi_dyn(1,ngridmx,iip1,jjp1,sea_ice,sea_iceS)
374      call gr_fi_dyn(nslay,ngridmx,iip1,jjp1,tslab,tslabS)
375
376      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,du_nonoro_gwd,du_nonoro_gwdS)
377      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,dv_nonoro_gwd,dv_nonoro_gwdS)
378      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,east_gwstress,east_gwstressS)
379      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,west_gwstress,west_gwstressS)
380c=======================================================================
381c Info pour controler
382c=======================================================================
383
384      ptotal =  0.
385      co2icetotal = 0.
386      DO j=1,jjp1
387         DO i=1,iim
388           ptotal=ptotal+aire(i+(iim+1)*(j-1))*ps(i+(iim+1)*(j-1))/g
389!           co2icetotal = co2icetotal +
390!     &            co2iceS(i+(iim+1)*(j-1))*aire(i+(iim+1)*(j-1))
391         ENDDO
392      ENDDO
393      write(*,*)'Old grid: : atmospheric mass :',ptotal
394!      write(*,*)'Ancienne grille : masse de la glace CO2 :',co2icetotal
395
396c-----------------------------------------------------------------------
397c Passage de "ptotal" et "co2icetotal" par tab_cntrl_fi
398c-----------------------------------------------------------------------
399
400      tab_cntrl_fi(49) = ptotal
401      tab_cntrl_fi(50) = co2icetotal
402
403c=======================================================================
404c Ecriture dans le fichier  "start_archive"
405c=======================================================================
406
407c-----------------------------------------------------------------------
408c Ouverture de "start_archive"
409c-----------------------------------------------------------------------
410
411      ierr = NF_OPEN ('start_archive.nc', NF_WRITE,nid)
412 
413c-----------------------------------------------------------------------
414c  si "start_archive" n'existe pas:
415c    1_ ouverture
416c    2_ creation de l'entete dynamique ("ini_archive")
417c-----------------------------------------------------------------------
418c ini_archive:
419c On met dans l'entete le tab_cntrl dynamique (1 a 16)
420c  On y ajoute les valeurs du tab_cntrl_fi (a partir de 51)
421c  En plus les deux valeurs ptotal et co2icetotal (99 et 100)
422c-----------------------------------------------------------------------
423
424      if (ierr.ne.NF_NOERR) then
425         write(*,*)'OK, Could not open file "start_archive.nc"'
426         write(*,*)'So let s create a new "start_archive"'
427         ierr = NF_CREATE('start_archive.nc', NF_CLOBBER, nid)
428         call ini_archive(nid,day_ini,phis,ithS,tab_cntrl_fi,
429     &                                          tab_cntrl_dyn)
430      endif
431
432c-----------------------------------------------------------------------
433c Ecriture de la coordonnee temps (date en jours)
434c-----------------------------------------------------------------------
435
436      date = day_ini
437      ierr= NF_INQ_VARID(nid,"Time",varid)
438      ierr= NF_INQ_DIMID(nid,"Time",dimid)
439      ierr= NF_INQ_DIMLEN(nid,dimid,timelen)
440      ntime=timelen+1
441
442      write(*,*) "******************"
443      write(*,*) "ntime",ntime
444      write(*,*) "******************"
445#ifdef NC_DOUBLE
446      ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
447#else
448      ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
449#endif
450      if (ierr.ne.NF_NOERR) then
451         write(*,*) "time matter ",NF_STRERROR(ierr)
452         call abort_physic("start2archive",
453     &        "Wibbly wobbly timey wimey error",1)
454      endif
455
456c-----------------------------------------------------------------------
457c Ecriture des champs  (co2ice,emis,ps,Tsurf,T,u,v,q2,q,qsurf)
458c-----------------------------------------------------------------------
459c ATTENTION: q2 a une couche de plus!!!!
460c    Pour creer un fichier netcdf lisible par grads,
461c    On passe donc une des couches de q2 a part
462c    comme une variable 2D (la couche au sol: "q2surf")
463c    Les lmm autres couches sont nommees "q2atm" (3D)
464c-----------------------------------------------------------------------
465
466!      call write_archive(nid,ntime,'co2ice','couche de glace co2',
467!     &  'kg/m2',2,co2iceS)
468      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
469      call write_archive(nid,ntime,'albedo','surface albedo',' ',
470     &                   2,albedoS)
471      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
472      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
473      call write_archive(nid,ntime,'temp','temperature','K',3,t)
474      call write_archive(nid,ntime,'u','Vent zonal','m.s-1',3,us)
475      call write_archive(nid,ntime,'v','Vent merid','m.s-1',3,vs)
476      call write_archive(nid,ntime,'q2surf','wind variance','m2.s-2',2,
477     .              q2S)
478      call write_archive(nid,ntime,'q2atm','wind variance','m2.s-2',3,
479     .              q2S(1,2))
480
481c-----------------------------------------------------------------------
482c Ecriture du champs  q  ( q[1,nqtot] )
483c-----------------------------------------------------------------------
484      do iq=1,nqtot
485        call write_archive(nid,ntime,tname(iq),'tracer','kg/kg',
486     &         3,q(1,1,iq))
487      end do
488c-----------------------------------------------------------------------
489c Ecriture du champs  qsurf  ( qsurf[1,nqtot] )
490c-----------------------------------------------------------------------
491      do iq=1,nqtot
492        txt=trim(tname(iq))//"_surf"
493        call write_archive(nid,ntime,txt,'Tracer on surface',
494     &  'kg.m-2',2,qsurfS(1,iq))
495      enddo
496
497
498c-----------------------------------------------------------------------
499c Ecriture du champs  tsoil  ( Tg[1,10] )
500c-----------------------------------------------------------------------
501c "tsoil" Temperature au sol definie dans 10 couches dans le sol
502c   Les 10 couches sont lues comme 10 champs
503c  nommees Tg[1,10]
504
505c      do isoil=1,nsoilmx
506c       write(str2,'(i2.2)') isoil
507c       call write_archive(nid,ntime,'Tg'//str2,'Ground Temperature ',
508c     .   'K',2,tsoilS(1,isoil))
509c      enddo
510
511! Write soil temperatures tsoil
512      call write_archive(nid,ntime,'tsoil','Soil temperature',
513     &     'K',-3,tsoilS)
514
515! Write soil thermal inertia
516      call write_archive(nid,ntime,'inertiedat',
517     &     'Soil thermal inertia',
518     &     'J.s-1/2.m-2.K-1',-3,ithS)
519
520! Write (0D) volumetric heat capacity (stored in comsoil.h)
521!      call write_archive(nid,ntime,'volcapa',
522!     &     'Soil volumetric heat capacity',
523!     &     'J.m-3.K-1',0,volcapa)
524! Note: no need to write volcapa, it is stored in "controle" table
525
526c-----------------------------------------------------------------------
527c Ecriture du champs  cloudfrac,hice,totalcloudfrac
528c-----------------------------------------------------------------------
529      call write_archive(nid,ntime,'hice',
530     &         'Height of oceanic ice','m',2,hiceS)
531      call write_archive(nid,ntime,'totalcloudfrac',
532     &        'Total cloud Fraction','',2,totalcloudfracS)
533      call write_archive(nid,ntime,'cloudfrac'
534     &        ,'Cloud fraction','',3,cloudfracS)
535
536c-----------------------------------------------------------------------
537c Slab ocean
538c-----------------------------------------------------------------------
539      OPEN(99,file='callphys.def',status='old',form='formatted'
540     &     ,iostat=ierr)
541      CLOSE(99)
542
543      IF(ierr.EQ.0) THEN
544
545        write(*,*) "Use slab-ocean ?"
546        ok_slab_ocean=.false.         ! default value
547        call getin("ok_slab_ocean",ok_slab_ocean)
548        write(*,*) "ok_slab_ocean = ",ok_slab_ocean
549
550        if(ok_slab_ocean) then
551          call write_archive(nid,ntime,'rnat'
552     &            ,'rnat','',2,rnatS)
553          call write_archive(nid,ntime,'pctsrf_sic'
554     &            ,'pctsrf_sic','',2,pctsrf_sicS)
555          call write_archive(nid,ntime,'sea_ice'
556     &            ,'sea_ice','',2,sea_iceS)
557          call write_archive(nid,ntime,'tslab'
558     &            ,'tslab','',-2,tslabS)
559          call write_archive(nid,ntime,'tsea_ice'
560     &            ,'tsea_ice','',2,tsea_iceS)
561          call write_archive(nid,ntime,'tice'
562     &            ,'tice','',2,ticeS)
563        endif !ok_slab_ocean
564     
565      ENDIF ! of IF(ierr.EQ.0)
566
567! Non-orographic gavity waves
568      call write_archive(nid,ntime,"du_nonoro_gwd",
569     &     "Zonal wind tendency due to GW",'m.s-1',3,du_nonoro_gwdS)
570      call write_archive(nid,ntime,"dv_nonoro_gwd",
571     &     "Meridional wind tendency due to GW",'m.s-1',
572     &     3,dv_nonoro_gwdS)
573      call write_archive(nid,ntime,"east_gwstress",
574     &     "Eastward stress profile due to GW",'kg.m-1.s-2',
575     &     3,east_gwstressS)
576      call write_archive(nid,ntime,"west_gwstress",
577     &     "Westward stress profile due to GW",'kg.m-1.s-2',
578     &     3,west_gwstressS)
579
580c-----------------------------------------------------------------------
581c Fin
582c-----------------------------------------------------------------------
583      ierr=NF_CLOSE(nid)
584
585      write(*,*) "start2archive: All is well that ends well."
586
587      end
Note: See TracBrowser for help on using the repository browser.