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

Last change on this file since 3893 was 3893, checked in by gmilcareck, 4 months ago

Remove all "call abort" and "stop" statement in LMDZ.GENERIC and replacing them by call abort_physic().

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