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

Last change on this file since 3529 was 3423, checked in by bhatnags, 3 months ago

Generic-PCM
Including variable "tice" in startarchive and newstart
SB

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