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

Last change on this file since 1564 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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