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

Last change on this file since 3546 was 3546, checked in by afalco, 13 days ago

Pluto: add SSO fields to start_archive, in order for startarchive2icosa scripts to work.
AF

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