source: trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/start2archive.F @ 2943

Last change on this file since 2943 was 2943, checked in by llange, 19 months ago

Mars PCM
Following r-2942: Fix a bug in newstart when rewriting inertiesoil. Inertiesoil is now also managed in startarchive.
When using startarchive or newstart, inertiesoil is set to inertiedat.
LL

File size: 17.8 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, only: nsoilmx, inertiedat
23      use surfdat_h, only: ini_surfdat_h, qsurf
24      use comsoil_h, only: ini_comsoil_h
25!      use comgeomphy, only: initcomgeomphy
26      use filtreg_mod, only: inifilr
27      USE mod_const_mpi, ONLY: COMM_LMDZ
28      use control_mod, only: planet_type
29      USE comvert_mod, ONLY: ap,bp
30      USE comconst_mod, ONLY: daysec,dtphys,rad,g,r,cpp
31      USE temps_mod, ONLY: day_ini,hour_ini
32      USE iniphysiq_mod, ONLY: iniphysiq
33      USE phyetat0_mod, ONLY: phyetat0
34      USE exner_hyb_m, ONLY: exner_hyb
35      use comslope_mod, ONLY: nslope,def_slope,def_slope_mean,
36     &                        subslope_dist
37      USE comcstfi_h, only: pi
38      implicit none
39
40      include "dimensions.h"
41      integer, parameter :: ngridmx = (2+(jjm-1)*iim - 1/jjm)
42      include "paramet.h"
43      include "comdissip.h"
44      include "comgeom.h"
45      include "netcdf.inc"
46
47c-----------------------------------------------------------------------
48c   Declarations
49c-----------------------------------------------------------------------
50
51c variables dynamiques du GCM
52c -----------------------------
53      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
54      REAL teta(ip1jmp1,llm)                    ! temperature potentielle
55      REAL,ALLOCATABLE :: q(:,:,:)   ! champs advectes
56      REAL pks(ip1jmp1)                      ! exner (f pour filtre)
57      REAL pk(ip1jmp1,llm)
58      REAL pkf(ip1jmp1,llm)
59      REAL phis(ip1jmp1)                     ! geopotentiel au sol
60      REAL masse(ip1jmp1,llm)                ! masse de l'atmosphere
61      REAL ps(ip1jmp1)                       ! pression au sol
62      REAL p3d(iip1, jjp1, llm+1)            ! pression aux interfaces
63     
64c Variable Physiques (grille physique)
65c ------------------------------------
66      REAL,ALLOCATABLE :: tsurf(:,:)        ! Surface temperature
67      REAL,ALLOCATABLE :: tsoil(:,:,:) ! Soil temperature
68      REAL,ALLOCATABLE :: inertiesoil(:,:,:) ! Soil thermal inertia (!= inertiedat which is for present day climate)
69      REAL,ALLOCATABLE :: watercap(:,:)        ! h2o ice layer
70      REAL :: tauscaling(ngridmx) ! dust conversion factor
71      REAL:: totcloudfrac(ngridmx) ! sub-grid cloud fraction
72      REAL q2(ngridmx,llm+1)
73      REAL,ALLOCATABLE :: emis(:,:)
74      REAL,ALLOCATABLE :: albedo(:,:,:)
75      REAL wstar(ngridmx)
76      INTEGER start,length
77      PARAMETER (length = 100)
78      REAL tab_cntrl_fi(length) ! tableau des parametres de startfi
79      INTEGER*4 day_ini_fi
80
81c Variable naturelle / grille scalaire
82c ------------------------------------
83      REAL T(ip1jmp1,llm),us(ip1jmp1,llm),vs(ip1jmp1,llm)
84      REAL,ALLOCATABLE :: tsurfS(:,:)
85      REAL,ALLOCATABLE :: tsoilS(:,:,:)
86      REAL,ALLOCATABLE :: inertiesoilS(:,:,:)! Variable Soil Thermal Inertia  (obtained from PEM)
87      REAL ithS(ip1jmp1,nsoilmx) ! Soil Thermal Inertia for inertie dat (present day climate)
88      REAL,ALLOCATABLE :: watercapS(:,:)
89      REAL :: tauscalingS(ip1jmp1)
90      REAL :: totcloudfracS(ip1jmp1)
91      REAL q2S(ip1jmp1,llm+1)
92      REAL,ALLOCATABLE :: qsurfS(:,:,:)
93      REAL,ALLOCATABLE :: emisS(:,:)
94      REAL,ALLOCATABLE :: albedoS(:,:)
95      REAL, ALLOCATABLE :: subslope_distS(:,:)
96
97c Variables intermediaires : vent naturel, mais pas coord scalaire
98c----------------------------------------------------------------
99      REAL vn(ip1jm,llm),un(ip1jmp1,llm)
100
101c Autres  variables
102c -----------------
103      LOGICAL startdrs
104      INTEGER Lmodif
105
106      REAL ptotal, co2icetotal
107      REAL timedyn,timefi !fraction du jour dans start, startfi
108      REAL date
109
110      CHARACTER*2 str2
111      CHARACTER*80 fichier
112      data  fichier /'startfi'/
113
114      INTEGER ij, l,i,j,isoil,iq,islope
115      character*80      fichnom
116      integer :: ierr,ntime
117      integer :: igcm_co2
118      integer :: nq,numvanle
119      character(len=30) :: txt ! to store some text
120
121c Netcdf
122c-------
123      integer varid,dimid,timelen
124      INTEGER nid,nid1
125
126c-----------------------------------------------------------------------
127c   Initialisations
128c-----------------------------------------------------------------------
129
130      CALL defrun_new(99, .TRUE. )
131
132      planet_type='mars'
133
134c=======================================================================
135c Lecture des donnees
136c=======================================================================
137! Load tracer number and names:
138      call infotrac_init
139
140! allocate arrays:
141      allocate(q(ip1jmp1,llm,nqtot))     
142
143      fichnom = 'start.nc'
144      CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
145     .       ps,phis,timedyn)
146
147c-----------------------------------------------------------------------
148c   Initialisations
149c-----------------------------------------------------------------------
150
151      CALL defrun_new(99, .FALSE. )
152      call iniconst
153      call inigeom
154      call inifilr
155
156! Initialize the physics
157         CALL iniphysiq(iim,jjm,llm,
158     &                  (jjm-1)*iim+2,comm_lmdz,
159     &                  daysec,day_ini,dtphys,
160     &                  rlatu,rlatv,rlonu,rlonv,
161     &                  aire,cu,cv,rad,g,r,cpp,
162     &                  1)
163
164      fichnom = 'startfi.nc'
165      Lmodif=0
166
167      allocate(tsurf(ngridmx,nslope))
168      allocate(tsoil(ngridmx,nsoilmx,nslope))
169      allocate(inertiesoil(ngridmx,nsoilmx,nslope))
170      allocate(watercap(ngridmx,nslope))
171      allocate(emis(ngridmx,nslope))
172      allocate(albedo(ngridmx,2,nslope))
173
174      allocate(qsurfS(ip1jmp1,nqtot,nslope))
175      allocate(tsurfS(ip1jmp1,nslope))
176      allocate(tsoilS(ip1jmp1,nsoilmx,nslope))
177      allocate(inertiesoilS(ip1jmp1,nsoilmx,nslope))
178      allocate(watercapS(ip1jmp1,nslope))
179      allocate(emisS(ip1jmp1,nslope))
180      allocate(albedoS(ip1jmp1,nslope))
181      allocate(subslope_distS(ip1jmp1,nslope))
182
183      CALL phyetat0 (fichnom,0,Lmodif,nsoilmx,ngridmx,llm,nqtot,
184     &      day_ini_fi,timefi,tsurf,tsoil,albedo,emis,q2,qsurf,
185     &      tauscaling,totcloudfrac,wstar,watercap,def_slope,
186     &      def_slope_mean,subslope_dist)
187
188       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
189       IF (ierr.NE.NF_NOERR) THEN
190         write(6,*)' Pb d''ouverture du fichier'//fichnom
191        CALL ABORT
192       ENDIF
193                                               
194      ierr = NF_INQ_VARID (nid1, "controle", varid)
195      IF (ierr .NE. NF_NOERR) THEN
196       PRINT*, "start2archive: Le champ <controle> est absent"
197       CALL abort
198      ENDIF
199#ifdef NC_DOUBLE
200       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_fi)
201#else
202      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_fi)
203#endif
204       IF (ierr .NE. NF_NOERR) THEN
205          PRINT*, "start2archive: Lecture echoue pour <controle>"
206          CALL abort
207       ENDIF
208
209      ierr = NF_CLOSE(nid1)
210
211c-----------------------------------------------------------------------
212c Controle de la synchro
213c-----------------------------------------------------------------------
214!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
215      if ((mod(day_ini_fi,669).ne.mod(day_ini,669)))
216     &  stop ' Probleme de Synchro entre start et startfi !!!'
217
218
219c *****************************************************************
220c    Option : Reinitialisation des dates dans la premieres annees :
221       do while (day_ini.ge.669)
222          day_ini=day_ini-669
223       enddo
224c *****************************************************************
225
226      CALL pression(ip1jmp1, ap, bp, ps, p3d)
227      call exner_hyb(ip1jmp1, ps, p3d, pks, pk, pkf)
228
229c=======================================================================
230c Transformation EN VARIABLE NATURELLE / GRILLE SCALAIRE si necessaire
231c=======================================================================
232c  Les variables modeles dependent de la resolution. Il faut donc
233c  eliminer les facteurs responsables de cette dependance
234c  (pour utiliser newstart)
235c=======================================================================
236
237c-----------------------------------------------------------------------
238c Vent   (depend de la resolution horizontale)
239c-----------------------------------------------------------------------
240c
241c ucov --> un  et  vcov --> vn
242c un --> us  et   vn --> vs
243c
244c-----------------------------------------------------------------------
245
246      call covnat(llm,ucov, vcov, un, vn)
247      call wind_scal(un,vn,us,vs)
248
249c-----------------------------------------------------------------------
250c Temperature  (depend de la resolution verticale => de "sigma.def")
251c-----------------------------------------------------------------------
252c
253c h --> T
254c
255c-----------------------------------------------------------------------
256
257      DO l=1,llm
258         DO ij=1,ip1jmp1
259            T(ij,l)=teta(ij,l)*pk(ij,l)/cpp !mars deduit de l'equation dans newstart
260         ENDDO
261      ENDDO
262
263c-----------------------------------------------------------------------
264c Variable physique
265c-----------------------------------------------------------------------
266c
267c tsurf --> tsurfS
268c watercap --> watercapS
269c tsoil --> tsoilS
270c inertiesoil --> inertiesoilS
271c inertiedat --> ithS
272c emis --> emisS
273c albedo --> albedoS
274c q2 --> q2S
275c qsurf --> qsurfS
276c tauscaling --> tauscalingS
277c totcloudfrac --> totcloudfracS
278c
279c-----------------------------------------------------------------------
280
281      do islope=1,nslope
282      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsurf(:,islope),
283     &    tsurfS(:,islope))
284      call gr_fi_dyn(1,ngridmx,iip1,jjp1,watercap(:,islope),
285     &    watercapS(:,islope))
286      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,tsoil(:,:,islope),
287     &    tsoilS(:,:,islope))
288      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiesoil(:,:,islope),
289     &    inertiesoil(:,:,islope))
290      ! Note: thermal inertia "inertiedat" is in comsoil.h
291      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis(:,islope),
292     &     emisS(:,islope))
293      call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedo(:,1,islope),
294     &   albedoS(:,islope))
295      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf(:,:,islope),
296     &   qsurfS(:,:,islope))
297      call gr_fi_dyn(1,ngridmx,iip1,jjp1,subslope_dist(:,islope),
298     &    subslope_distS(:,islope))
299      enddo
300      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
301      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
302      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tauscaling,tauscalingS)
303      call gr_fi_dyn(1,ngridmx,iip1,jjp1,totcloudfrac,totcloudfracS)
304
305c=======================================================================
306c Info pour controler
307c=======================================================================
308
309      DO iq=1,nqtot
310        if (trim(tname(iq)) .eq. "co2") then
311           igcm_co2=iq
312        endif
313      enddo
314
315      ptotal =  0.
316      co2icetotal = 0.
317      DO j=1,jjp1
318         DO i=1,iim
319           DO islope=1,nslope
320           ptotal=ptotal+aire(i+(iim+1)*(j-1))*ps(i+(iim+1)*(j-1))/g
321           co2icetotal = co2icetotal +
322     &        qsurfS(i+(iim+1)*(j-1),igcm_co2,islope)*
323     &        aire(i+(iim+1)*(j-1))*
324     &    subslope_distS(i+(iim+1)*(j-1),islope)/
325     &    cos(pi*def_slope_mean(islope))
326           ENDDO
327         ENDDO
328      ENDDO
329      write(*,*)'Ancienne grille : masse de l''atm :',ptotal
330      write(*,*)'Ancienne grille : masse de la glace CO2 :',co2icetotal
331
332c-----------------------------------------------------------------------
333c Passage de "ptotal" et "co2icetotal" par tab_cntrl_fi
334c-----------------------------------------------------------------------
335
336      tab_cntrl_fi(49) = ptotal
337      tab_cntrl_fi(50) = co2icetotal
338
339c=======================================================================
340c Ecriture dans le fichier  "start_archive"
341c=======================================================================
342
343c-----------------------------------------------------------------------
344c Ouverture de "start_archive"
345c-----------------------------------------------------------------------
346
347      ierr = NF_OPEN ('start_archive.nc', NF_WRITE,nid)
348 
349c-----------------------------------------------------------------------
350c  si "start_archive" n'existe pas:
351c    1_ ouverture
352c    2_ creation de l'entete dynamique ("ini_archive")
353c-----------------------------------------------------------------------
354c ini_archive:
355c On met dans l'entete le tab_cntrl dynamique (1 a 16)
356c  On y ajoute les valeurs du tab_cntrl_fi (a partir de 51)
357c  En plus les deux valeurs ptotal et co2icetotal (99 et 100)
358c-----------------------------------------------------------------------
359
360      if (ierr.ne.NF_NOERR) then
361         write(*,*)'OK, Could not open file "start_archive.nc"'
362         write(*,*)'So let s create a new "start_archive"'
363         ierr = NF_CREATE('start_archive.nc',
364     &  IOR(NF_CLOBBER,NF_64BIT_OFFSET), nid)
365         call ini_archive(nid,day_ini,phis,ithS,tab_cntrl_fi,
366     &         def_slope,subslope_distS)
367      endif
368
369c-----------------------------------------------------------------------
370c Ecriture de la coordonnee temps (date en jours)
371c-----------------------------------------------------------------------
372
373      date = day_ini + hour_ini
374      ierr= NF_INQ_VARID(nid,"Time",varid)
375      ierr= NF_INQ_DIMID(nid,"Time",dimid)
376      ierr= NF_INQ_DIMLEN(nid,dimid,timelen)
377      ntime=timelen+1
378
379      write(*,*) "******************"
380      write(*,*) "ntime",ntime
381      write(*,*) "******************"
382#ifdef NC_DOUBLE
383      ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
384#else
385      ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
386#endif
387      if (ierr.ne.NF_NOERR) then
388         write(*,*) "time matter ",NF_STRERROR(ierr)
389         stop
390      endif
391
392c-----------------------------------------------------------------------
393c Ecriture des champs  (co2ice,emis,albedo,ps,Tsurf,T,u,v,q2,q,qsurf)
394c-----------------------------------------------------------------------
395c ATTENTION: q2 a une couche de plus!!!!
396c    Pour creer un fichier netcdf lisible par grads,
397c    On passe donc une des couches de q2 a part
398c    comme une variable 2D (la couche au sol: "q2surf")
399c    Les lmm autres couches sont nommees "q2atm" (3D)
400c-----------------------------------------------------------------------
401
402      call write_archive(nid,ntime,'watercap','couche de glace h2o',
403     &  'kg/m2',2,watercapS)
404      call write_archive(nid,ntime,'tauscaling',
405     &  'dust conversion factor',' ',2,tauscalingS)
406      call write_archive(nid,ntime,'totcloudfrac',
407     &  'sub grid cloud fraction',' ',2,totcloudfracS)
408      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
409      call write_archive(nid,ntime,'albedo','surface albedo',' ',
410     &                             2,albedoS)
411      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
412      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
413      call write_archive(nid,ntime,'temp','temperature','K',3,t)
414      call write_archive(nid,ntime,'u','Vent zonal','m.s-1',3,us)
415      call write_archive(nid,ntime,'v','Vent merid','m.s-1',3,vs)
416      call write_archive(nid,ntime,'q2surf','wind variance','m2.s-2',2,
417     .              q2S)
418      call write_archive(nid,ntime,'q2atm','wind variance','m2.s-2',3,
419     .              q2S(1,2))
420
421c-----------------------------------------------------------------------
422c Ecriture du champs  q  ( q[1,nqtot] )
423c-----------------------------------------------------------------------
424      do iq=1,nqtot
425c       write(str2,'(i2.2)') iq
426c        call write_archive(nid,ntime,'q'//str2,'tracer','kg/kg',
427c     .         3,q(1,1,iq))
428        call write_archive(nid,ntime,tname(iq),'tracer','kg/kg',
429     &         3,q(1,1,iq))
430      end do
431c-----------------------------------------------------------------------
432c Ecriture du champs  qsurf  ( qsurf[1,nqtot] )
433c-----------------------------------------------------------------------
434      do iq=1,nqtot
435c       write(str2,'(i2.2)') iq
436c       call write_archive(nid,ntime,'qsurf'//str2,'Tracer on surface',
437c     $  'kg.m-2',2,qsurfS(1,iq))
438        txt=trim(tname(iq))//"_surf"
439        call write_archive(nid,ntime,txt,'Tracer on surface',
440     &  'kg.m-2',2,qsurfS(:,iq,:))
441      enddo
442
443
444c-----------------------------------------------------------------------
445c Ecriture du champs  tsoil  ( Tg[1,10] )
446c-----------------------------------------------------------------------
447c "tsoil" Temperature au sol definie dans 10 couches dans le sol
448c   Les 10 couches sont lues comme 10 champs
449c  nommees Tg[1,10]
450
451c      do isoil=1,nsoilmx
452c       write(str2,'(i2.2)') isoil
453c       call write_archive(nid,ntime,'Tg'//str2,'Ground Temperature ',
454c     .   'K',2,tsoilS(1,isoil))
455c      enddo
456
457! Write soil temperatures tsoil
458      call write_archive(nid,ntime,'tsoil','Soil temperature',
459     &     'K',-3,tsoilS(:,:,:))
460! Write soil thermal inertia
461      call write_archive(nid,ntime,'inertiesoil','Soil TI',
462     &     'J.s-1/2.m-2.K-1',-3,inertiesoilS(:,:,:))
463! Write soil thermal inertia for current climate
464      call write_archive(nid,ntime,'inertiedat - present day TI',
465     &     'Soil thermal inertia',
466     &     'J.s-1/2.m-2.K-1',-3,ithS)
467
468! Write (0D) volumetric heat capacity (stored in comsoil.h)
469!      call write_archive(nid,ntime,'volcapa',
470!     &     'Soil volumetric heat capacity',
471!     &     'J.m-3.K-1',0,volcapa)
472! Note: no need to write volcapa, it is stored in "controle" table
473
474      ierr=NF_CLOSE(nid)
475c-----------------------------------------------------------------------
476c Fin
477c-----------------------------------------------------------------------
478
479      write(*,*) "startarchive: all is well that ends well"
480     
481      end
Note: See TracBrowser for help on using the repository browser.