source: trunk/LMDZ.PLUTO/libf/dynphy_lonlat/phypluto/start2archive.F @ 3745

Last change on this file since 3745 was 3635, checked in by tbertrand, 11 months ago

Pluto: small fix to correctly read the soil thermal inertia from the starts
TB

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