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

Last change on this file since 3595 was 3576, checked in by jbclement, 3 weeks ago

COMMON:
Follow-up of r3574:

  • Small corrections to make it work with Git;
  • Addition of the functionality with the programs 'Generic newstart' and 'Generic start2archive';
  • Improvements of the visualization format;
  • Diplaying version control information of every sub-folder in the "trunk" instead of only the "trunk" (who can do more can do less).

JBC

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