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

Last change on this file since 3878 was 3762, checked in by afalco, 8 months ago

pluto start2archive: fix for previous commit. lat/lon dimensions off by one.
AF

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