source: LMDZ6/branches/LMDZ-tracers/libf/dyn3dmem/dynredem_loc.F90 @ 3852

Last change on this file since 3852 was 3852, checked in by dcugnet, 3 years ago

Extension of the tracers management.

The tracers files can be:

1) "traceur.def": old format, with:

  • the number of tracers on the first line
  • one line for each tracer: <tracer name> <hadv> <vadv> [<parent name>]

2) "tracer.def": new format with one section each model component.
3) "tracer_<name>.def": new format with a single section.

The formats 2 and 3 reading is driven by the "type_trac" key, which can be a

coma-separated list of components.

  • Format 2: read the sections from the "tracer.def" file.
  • format 3: read one section each "tracer_<section name>.def" file.
  • the first line of a section is "&<section name>
  • the other lines start with a tracer name followed by <key>=<val> pairs.
  • the "default" tracer name is reserved ; the other tracers of the section inherit its <key>=<val>, except for the keys that are redefined locally.

This format helps keeping the tracers files compact, thanks to the "default"
special tracer and the three levels of factorization:

  • on the tracers names: a tracer name can be a coma-separated list of tracers => all the tracers of the list have the same <key>=<val> properties
  • on the parents names: the value of the "parent" property can be a coma-separated list of tracers => only possible for geographic tagging tracers
  • on the phases: the property "phases" is [g](l][s] (gas/liquid/solid)

Read information is stored in the vector "tracers(:)", of derived type "tra".

"isotopes_params.def" is a similar file, with one section each isotopes family.
It contains a database of isotopes properties ; if there are second generation
tracers (isotopes), the corresponding sections are read.

Read information is stored in the vector "isotopes(:)", of derived type "iso".

The "getKey" function helps to get the values of the parameters stored in
"tracers" or "isotopes".

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 10.4 KB
Line 
1SUBROUTINE dynredem0_loc(fichnom,iday_end,phis)
2!
3!-------------------------------------------------------------------------------
4! Write the NetCDF restart file (initialization).
5!-------------------------------------------------------------------------------
6#ifdef CPP_IOIPSL
7  USE IOIPSL
8#endif
9  USE parallel_lmdz
10  USE mod_hallo
11  USE infotrac, ONLY: nqtot, tracers
12  USE netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL,    &
13                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER,   &
14                    NF90_64BIT_OFFSET
15  USE dynredem_mod, ONLY: cre_var, put_var, err, modname, fil
16  USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff, &
17                         nivsig,nivsigs
18  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
19  USE logic_mod, ONLY: fxyhypb, ysinus
20  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
21                       taux,tauy
22  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itaufin, start_time
23  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
24
25  IMPLICIT NONE
26  include "dimensions.h"
27  include "paramet.h"
28  include "comgeom.h"
29  include "description.h"
30  include "iniprint.h"
31!===============================================================================
32! Arguments:
33  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
34  INTEGER,          INTENT(IN) :: iday_end         !---
35  REAL,             INTENT(IN) :: phis(ijb_u:ije_u)!--- GROUND GEOPOTENTIAL
36!===============================================================================
37! Local variables:
38  INTEGER :: iq, l
39  INTEGER, PARAMETER :: length=100
40  REAL    :: tab_cntrl(length)                     !--- RUN PARAMETERS TABLE
41  REAL    :: phis_glo(ip1jmp1)
42!   For NetCDF:
43  CHARACTER(LEN=30) :: unites
44  INTEGER :: indexID
45  INTEGER :: rlonuID, rlonvID, rlatuID, rlatvID
46  INTEGER :: sID, sigID, nID, vID, timID
47  INTEGER :: yyears0, jjour0, mmois0
48  REAL    :: zan0, zjulian, hours
49!===============================================================================
50  modname='dynredem0'; fil=fichnom
51  CALL Gather_field_u(phis,phis_glo,1)
52  IF(mpi_rank/=0) RETURN
53
54#ifdef CPP_IOIPSL
55  CALL ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
56  CALL ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
57#else
58! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
59  yyears0=0
60  mmois0=1
61  jjour0=1
62#endif       
63
64  tab_cntrl(:)  = 0.
65  tab_cntrl(1)  = REAL(iim)
66  tab_cntrl(2)  = REAL(jjm)
67  tab_cntrl(3)  = REAL(llm)
68  tab_cntrl(4)  = REAL(day_ref)
69  tab_cntrl(5)  = REAL(annee_ref)
70  tab_cntrl(6)  = rad
71  tab_cntrl(7)  = omeg
72  tab_cntrl(8)  = g
73  tab_cntrl(9)  = cpp
74  tab_cntrl(10) = kappa
75  tab_cntrl(11) = daysec
76  tab_cntrl(12) = dtvr
77  tab_cntrl(13) = etot0
78  tab_cntrl(14) = ptot0
79  tab_cntrl(15) = ztot0
80  tab_cntrl(16) = stot0
81  tab_cntrl(17) = ang0
82  tab_cntrl(18) = pa
83  tab_cntrl(19) = preff
84
85!    .....    parameters for zoom    ......   
86  tab_cntrl(20) = clon
87  tab_cntrl(21) = clat
88  tab_cntrl(22) = grossismx
89  tab_cntrl(23) = grossismy
90!
91  IF ( fxyhypb )   THEN
92    tab_cntrl(24) = 1.
93    tab_cntrl(25) = dzoomx
94    tab_cntrl(26) = dzoomy
95    tab_cntrl(27) = 0.
96    tab_cntrl(28) = taux
97    tab_cntrl(29) = tauy
98  ELSE
99    tab_cntrl(24) = 0.
100    tab_cntrl(25) = dzoomx
101    tab_cntrl(26) = dzoomy
102    tab_cntrl(27) = 0.
103    tab_cntrl(28) = 0.
104    tab_cntrl(29) = 0.
105    IF( ysinus )  tab_cntrl(27) = 1.
106  END IF
107  tab_cntrl(30) = REAL(iday_end)
108  tab_cntrl(31) = REAL(itau_dyn + itaufin)
109! start_time: start_time of simulation (not necessarily 0.)
110  tab_cntrl(32) = start_time
111
112!--- File creation
113  CALL err(NF90_CREATE(fichnom,IOR(NF90_CLOBBER,NF90_64BIT_OFFSET),nid))
114
115!--- Some global attributes
116  CALL err(NF90_PUT_ATT(nid,NF90_GLOBAL,"title","Fichier demarrage dynamique"))
117
118!--- Dimensions
119  CALL err(NF90_DEF_DIM(nid,"index", length, indexID))
120  CALL err(NF90_DEF_DIM(nid,"rlonu", iip1,   rlonuID))
121  CALL err(NF90_DEF_DIM(nid,"rlatu", jjp1,   rlatuID))
122  CALL err(NF90_DEF_DIM(nid,"rlonv", iip1,   rlonvID))
123  CALL err(NF90_DEF_DIM(nid,"rlatv", jjm,    rlatvID))
124  CALL err(NF90_DEF_DIM(nid,"sigs",  llm,        sID))
125  CALL err(NF90_DEF_DIM(nid,"sig",   llmp1,    sigID))
126  CALL err(NF90_DEF_DIM(nid,"temps", NF90_UNLIMITED, timID))
127
128!--- Define and save invariant fields
129  CALL put_var(nid,"controle","Parametres de controle" ,[indexID],tab_cntrl)
130  CALL put_var(nid,"rlonu"   ,"Longitudes des points U",[rlonuID],rlonu)
131  CALL put_var(nid,"rlatu"   ,"Latitudes des points U" ,[rlatuID],rlatu)
132  CALL put_var(nid,"rlonv"   ,"Longitudes des points V",[rlonvID],rlonv)
133  CALL put_var(nid,"rlatv"   ,"Latitudes des points V" ,[rlatvID],rlatv)
134  CALL put_var(nid,"nivsigs" ,"Numero naturel des couches s"    ,[sID]  ,nivsigs)
135  CALL put_var(nid,"nivsig"  ,"Numero naturel des couches sigma",[sigID],nivsig)
136  CALL put_var(nid,"ap"      ,"Coefficient A pour hybride"      ,[sigID],ap)
137  CALL put_var(nid,"bp"      ,"Coefficient B pour hybride"      ,[sigID],bp)
138  CALL put_var(nid,"presnivs",""                                ,[sID]  ,presnivs)
139! covariant <-> contravariant <-> natural conversion coefficients
140  CALL put_var(nid,"cu","Coefficient de passage pour U",[rlonuID,rlatuID],cu)
141  CALL put_var(nid,"cv","Coefficient de passage pour V",[rlonvID,rlatvID],cv)
142  CALL put_var(nid,"aire","Aires de chaque maille"     ,[rlonvID,rlatuID],aire)
143  CALL put_var(nid,"phisinit","Geopotentiel au sol"    ,[rlonvID,rlatuID],phis_glo)
144
145!--- Define fields saved later
146  WRITE(unites,"('days since ',i4,'-',i2.2,'-',i2.2,' 00:00:00')"),&
147               yyears0,mmois0,jjour0
148  CALL cre_var(nid,"temps","Temps de simulation",[timID],unites)
149  CALL cre_var(nid,"ucov" ,"Vitesse U"  ,[rlonuID,rlatuID,sID,timID])
150  CALL cre_var(nid,"vcov" ,"Vitesse V"  ,[rlonvID,rlatvID,sID,timID])
151  CALL cre_var(nid,"teta" ,"Temperature",[rlonvID,rlatuID,sID,timID])
152  DO iq=1,nqtot
153    CALL cre_var(nid,tracers(iq)%name(iq),tracers(iq)%lnam,[rlonvID,rlatuID,sID,timID])
154  END DO
155  CALL cre_var(nid,"masse","Masse d air"    ,[rlonvID,rlatuID,sID,timID])
156  CALL cre_var(nid,"ps"   ,"Pression au sol",[rlonvID,rlatuID    ,timID])
157  CALL err(NF90_CLOSE (nid))
158
159  WRITE(lunout,*)TRIM(modname)//': iim,jjm,llm,iday_end',iim,jjm,llm,iday_end
160  WRITE(lunout,*)TRIM(modname)//': rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
161
162END SUBROUTINE dynredem0_loc
163!
164!-------------------------------------------------------------------------------
165
166
167!-------------------------------------------------------------------------------
168!
169SUBROUTINE dynredem1_loc(fichnom,time,vcov,ucov,teta,q,masse,ps)
170!
171!-------------------------------------------------------------------------------
172! Purpose: Write the NetCDF restart file (append).
173!-------------------------------------------------------------------------------
174  USE parallel_lmdz
175  USE mod_hallo
176  USE infotrac, ONLY: nqtot, tracers, type_trac
177  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
178                      NF90_CLOSE, NF90_WRITE,   NF90_PUT_VAR, NF90_NoErr
179  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
180                          err, modname, fil, msg
181  USE temps_mod, ONLY: itau_dyn, itaufin
182 
183  IMPLICIT NONE
184  include "dimensions.h"
185  include "paramet.h"
186  include "description.h"
187  include "comgeom.h"
188  include "iniprint.h"
189!===============================================================================
190! Arguments:
191  CHARACTER(LEN=*), INTENT(IN) :: fichnom              !-- FILE NAME
192  REAL, INTENT(IN)    ::  time                         !-- TIME
193  REAL, INTENT(IN)    ::  vcov(ijb_v:ije_v,llm)        !-- V COVARIANT WIND
194  REAL, INTENT(IN)    ::  ucov(ijb_u:ije_u,llm)        !-- U COVARIANT WIND
195  REAL, INTENT(IN)    ::  teta(ijb_u:ije_u,llm)        !-- POTENTIAL TEMPERATURE
196  REAL, INTENT(INOUT) ::     q(ijb_u:ije_u,llm,nqtot)  !-- TRACERS
197  REAL, INTENT(IN)    :: masse(ijb_u:ije_u,llm)        !-- MASS PER CELL
198  REAL, INTENT(IN)    ::    ps(ijb_u:ije_u)            !-- GROUND PRESSURE
199!===============================================================================
200! Local variables:
201  INTEGER :: l, iq, nid, vID, ierr, nid_trac, vID_trac
202  INTEGER, SAVE :: nb=0
203  INTEGER, PARAMETER :: length=100
204  REAL               :: tab_cntrl(length) ! tableau des parametres du run
205  CHARACTER(LEN=256) :: var, dum
206  LOGICAL            :: lread_inca
207!===============================================================================
208
209!$OMP MASTER
210  IF(mpi_rank==0) THEN !++++++++++++++++++++++++++++++++++++++++++++++++++++++++
211  modname='dynredem1_loc'; fil=fichnom
212  fil=fichnom
213  CALL err(NF90_OPEN(fil,NF90_WRITE,nid),"open",fil)
214
215!--- Write/extend time coordinate
216  nb = nb + 1
217  var="temps"
218  CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var)
219  CALL err(NF90_PUT_VAR(nid,vID,[time]),"put",var)
220  WRITE(lunout,*)TRIM(modname)//": Saving for ", nb, time
221
222!--- Rewrite control table (itaufin undefined in dynredem0)
223  var="controle"
224  CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var)
225  CALL err(NF90_GET_VAR(nid,vID,tab_cntrl),"get",var)
226  tab_cntrl(31)=DBLE(itau_dyn + itaufin)
227  CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var)
228  CALL err(NF90_PUT_VAR(nid,vID,tab_cntrl),"put",var)
229  END IF               !++++++++++++++++++++++++++++++++++++++++++++++++++++++++
230!$OMP END MASTER
231
232!--- Save fields
233  CALL dynredem_write_u(nid,"ucov" ,ucov ,llm)
234  CALL dynredem_write_v(nid,"vcov" ,vcov ,llm)
235  CALL dynredem_write_u(nid,"teta" ,teta ,llm)
236  CALL dynredem_write_u(nid,"masse",masse,llm)
237  CALL dynredem_write_u(nid,"ps"   ,ps   ,1)
238
239!--- Tracers in file "start_trac.nc" (added by Anne)
240  lread_inca=.FALSE.
241!$OMP MASTER
242  fil="start_trac.nc"
243  IF(type_trac=='inca') INQUIRE(FILE=fil,EXIST=lread_inca)
244  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
245!$OMP END MASTER
246!$OMP BARRIER
247
248!--- Save tracers
249  DO iq=1,nqtot; var=tracers(iq)%name; ierr=-1
250    IF(lread_inca) THEN                  !--- Possibly read from "start_trac.nc"
251!$OMP MASTER     
252      fil="start_trac.nc"
253      ierr=NF90_INQ_VARID(nid_trac,var,vID_trac)
254      dum='inq'; IF(ierr==NF90_NoErr) dum='fnd'
255      WRITE(lunout,*)msg(dum,var)
256!$OMP END MASTER
257!$OMP BARRIER
258      IF(ierr==NF90_NoErr) CALL dynredem_read_u(nid_trac,var,q(:,:,iq),llm)
259    END IF
260    fil=fichnom
261    CALL dynredem_write_u(nid,var,q(:,:,iq),llm)
262  END DO
263
264!$OMP MASTER
265  IF(mpi_rank==0) THEN !++++++++++++++++++++++++++++++++++++++++++++++++++++++++
266  CALL err(NF90_CLOSE(nid),"close")
267  fil="start_trac.nc"
268  IF(lread_inca) CALL err(NF90_CLOSE(nid_trac),"close")
269  END IF               !++++++++++++++++++++++++++++++++++++++++++++++++++++++++
270!$OMP END MASTER
271
272END SUBROUTINE dynredem1_loc
273
Note: See TracBrowser for help on using the repository browser.