source: trunk/LMDZ.COMMON/libf/dyn3d_common/dynredem.F90 @ 3789

Last change on this file since 3789 was 3706, checked in by emillour, 3 months ago

Common dynamics:
Add initialization of "dscrpt_tab_cntrl(:)" (strings of descriptors
incluede in restart.nc to describe contents of controle array) to
empty strings, since in some cases they are not filled.
EM

File size: 18.3 KB
Line 
1!
2! $Id: dynredem.F 1635 2012-07-12 11:37:16Z lguez $
3!
4!
5SUBROUTINE dynredem0(fichnom,iday_end,phis)
6#ifdef CPP_IOIPSL
7  USE IOIPSL
8#endif
9  USE infotrac, ONLY: nqtot, tname, ttext
10  USE netcdf, ONLY: NF90_CREATE, NF90_DEF_DIM, NF90_INQ_VARID, NF90_GLOBAL, &
11                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER
12  USE dynredem_mod, ONLY: cre_var, put_var1, put_var2, put_char1, err, modname, fil, int2fmtstr
13  use netcdf95, only: NF95_PUT_VAR
14  use control_mod, only : planet_type
15  USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,pa,preff, &
16                        nivsig,nivsigs
17  USE comconst_mod, ONLY: daysec,dtvr,rad,omeg,g,cpp,kappa,pi
18  USE logic_mod, ONLY: fxyhypb,ysinus
19  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
20                        taux,tauy
21  USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,itaufin, &
22                        start_time,hour_ini
23  USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
24
25  IMPLICIT NONE
26!=======================================================================
27! Writting the NetCDF restart file (initialisation)
28!=======================================================================
29!   Declarations:
30!   -------------
31  include "dimensions.h"
32  include "paramet.h"
33  include "comgeom2.h"
34  include "netcdf.inc"
35  include "iniprint.h"
36
37!===============================================================================
38! Arguments:
39  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
40  INTEGER,          INTENT(IN) :: iday_end         !---
41  REAL,             INTENT(IN) :: phis(iip1, jjp1) !--- GROUND GEOPOTENTIAL
42!===============================================================================
43! Local variables:
44  INTEGER :: iq,l
45  INTEGER, PARAMETER :: length=100
46  INTEGER, PARAMETER :: ndscrpt = 42
47  INTEGER :: ldscrpt
48  REAL :: tab_cntrl(length) ! run parameters
49  character(ndscrpt), dimension(:), allocatable :: dscrpt_tab_cntrl
50  INTEGER :: ierr
51  CHARACTER(LEN=80) :: abort_message
52
53!   For NetCDF:
54  CHARACTER(LEN=30) :: unites
55  INTEGER :: indexID, descrptID, dscrpt_sID
56  INTEGER :: rlonuID, rlonvID, rlatuID, rlatvID
57  INTEGER :: sID, sigID, nID, vID, timID
58  INTEGER :: yyears0, jjour0, mmois0
59  REAL    :: zan0, zjulian, hours
60
61  CHARACTER(len=12) :: start_file_type="earth" ! default start file type
62  INTEGER :: idecal
63
64!===============================================================================
65  ! fill dynredem_mod module variables
66  modname='dynredem0'; fil=fichnom
67
68#ifdef CPP_IOIPSL
69  call ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
70  call ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
71#else
72! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
73  yyears0=0
74  mmois0=1
75  jjour0=1
76#endif       
77
78  !!! AS: idecal is a hack to be able to read planeto starts...
79  !!!     .... while keeping everything OK for LMDZ EARTH
80  if ((planet_type.eq."generic").or.(planet_type.eq."mars")) then
81    write(lunout,*) trim(modname),' : Planeto-like start file'
82    start_file_type="planeto"
83    idecal = 4
84    ldscrpt = 29
85  else
86    if ( planet_type.eq."titan" ) then
87      ! Titan inherited Earth-like start files with idecal=5
88      write(lunout,*) trim(modname),' : Titan start file'
89    else
90      write(lunout,*) trim(modname),' : Earth-like start file'
91    endif
92    idecal = 5
93    ldscrpt = 32
94  endif
95
96  tab_cntrl(:)  = 0.
97  allocate(dscrpt_tab_cntrl(ldscrpt))
98  !Initialize dscrpt_tab_cntrl(:) to empty strings
99  dscrpt_tab_cntrl(:)=""
100
101  dscrpt_tab_cntrl(1:5) = (/                        &
102      "(1)  Number of nodes along longitude      ", &
103      "(2)  Number of nodes along latitude       ", &
104      "(3)  Number of atmospheric layers         ", &
105      "(4)  Reference day                        ", &
106      "(5)  Reference year                       "/)
107  tab_cntrl(1)  = REAL(iim)
108  tab_cntrl(2)  = REAL(jjm)
109  tab_cntrl(3)  = REAL(llm)
110  if (start_file_type.eq."earth") then
111    tab_cntrl(4)=REAL(day_ref)
112  else
113    !tab_cntrl(4)=REAL(day_end)
114    tab_cntrl(4)=REAL(iday_end)
115    dscrpt_tab_cntrl(4) = "(4)  Initial day                          "
116  endif
117  tab_cntrl(5)  = REAL(annee_ref)
118  tab_cntrl(idecal+1)  = rad
119  tab_cntrl(idecal+2)  = omeg
120  tab_cntrl(idecal+3)  = g
121  tab_cntrl(idecal+4)  = cpp
122  tab_cntrl(idecal+5) = kappa
123  tab_cntrl(idecal+6) = daysec
124  tab_cntrl(idecal+7) = dtvr
125  tab_cntrl(idecal+8) = etot0
126  tab_cntrl(idecal+9) = ptot0
127  tab_cntrl(idecal+10) = ztot0
128  tab_cntrl(idecal+11) = stot0
129  tab_cntrl(idecal+12) = ang0
130  tab_cntrl(idecal+13) = pa
131  tab_cntrl(idecal+14) = preff
132
133!    .....    parameters for the zoom      ......   
134  tab_cntrl(idecal+15)  = clon
135  tab_cntrl(idecal+16)  = clat
136  tab_cntrl(idecal+17)  = grossismx
137  tab_cntrl(idecal+18)  = grossismy
138  dscrpt_tab_cntrl(idecal + 1:idecal + 18) = (/                          &
139      int2fmtstr(idecal + 1)// " Radius of the planet                 ", &
140      int2fmtstr(idecal + 2)// " Rotation of the planet (rad/s)       ", &
141      int2fmtstr(idecal + 3)// " Gravity (m/s2)                       ", &
142      int2fmtstr(idecal + 4)// " Specific heat Cp (J.kg-1.K-1)        ", &
143      int2fmtstr(idecal + 5)// " = r/Cp (=kappa)                      ", &
144      int2fmtstr(idecal + 6)// " Lenght of a sol (s)                  ", &
145      int2fmtstr(idecal + 7)// " Dynamical time step (s)              ", &
146      int2fmtstr(idecal + 8)// " Total energy                         ", &
147      int2fmtstr(idecal + 9)// " Total pressure                       ", &
148      int2fmtstr(idecal + 10)//" Total enstrophy                      ", &
149      int2fmtstr(idecal + 11)//" Total enthalpy                       ", &
150      int2fmtstr(idecal + 12)//" Total angular momentum               ", &
151      int2fmtstr(idecal + 13)//" Reference pressure (Pa)              ", &
152      int2fmtstr(idecal + 14)//" Reference surface pressure (Pa)      ", &
153      int2fmtstr(idecal + 15)//" Longitude of center of zoom          ", &
154      int2fmtstr(idecal + 16)//" Latitude of center of zoom           ", &
155      int2fmtstr(idecal + 17)//" Zooming factor, along longitude      ", &
156      int2fmtstr(idecal + 18)//" Zooming factor, along latitude       "/)
157!
158  IF ( fxyhypb )   THEN
159    tab_cntrl(idecal+19) = 1.
160    tab_cntrl(idecal+20) = dzoomx
161    tab_cntrl(idecal+21) = dzoomy
162    tab_cntrl(idecal+22) = 0.
163    tab_cntrl(idecal+23) = taux
164    tab_cntrl(idecal+24) = tauy
165    dscrpt_tab_cntrl(idecal + 19:idecal + 24) = (/                       &
166      int2fmtstr(idecal + 19)//" 1.                                   ", &
167      int2fmtstr(idecal + 20)//" Extention (in longitude) of zoom     ", &
168      int2fmtstr(idecal + 21)//" Extention (in latitude) of zoom      ", &
169      int2fmtstr(idecal + 22)//" -                                    ", &
170      int2fmtstr(idecal + 23)//" Stiffness factor of zoom in longitude", &
171      int2fmtstr(idecal + 24)//" Stiffness factor of zoom in latitude "/)
172  ELSE
173    tab_cntrl(idecal+19) = 0.
174    tab_cntrl(idecal+20) = dzoomx
175    tab_cntrl(idecal+21) = dzoomy
176    tab_cntrl(idecal+22) = 0.
177    tab_cntrl(idecal+23) = 0.
178    tab_cntrl(idecal+24) = 0.
179    IF( ysinus )  tab_cntrl(idecal+22) = 1.
180    dscrpt_tab_cntrl(idecal + 19:idecal + 24) = (/                       &
181      int2fmtstr(idecal + 19)//" -                                    ", &
182      int2fmtstr(idecal + 20)//" Extention (in longitude) of zoom     ", &
183      int2fmtstr(idecal + 21)//" Extention (in latitude) of zoom      ", &
184      int2fmtstr(idecal + 22)//" 1.                                   ", &
185      int2fmtstr(idecal + 23)//" Stiffness factor of zoom in longitude", &
186      int2fmtstr(idecal + 24)//" Stiffness factor of zoom in latitude "/)
187  ENDIF
188
189  if (start_file_type.eq."earth") then
190    tab_cntrl(idecal+25) = REAL(iday_end)
191    tab_cntrl(idecal+26) = REAL(itau_dyn + itaufin)
192! start_time: start_time of simulation (not necessarily 0.)
193    tab_cntrl(idecal+27) = start_time
194    dscrpt_tab_cntrl(idecal + 25:idecal + 27) = (/  &
195      "(30) Initial day                          ", &
196      "(31) Extention (in longitude) of zoom     ", &
197      "(32) Start time of simulation             "/)
198  endif
199
200  if (planet_type=="mars") then ! For Mars only
201    !tab_cntrl(29)=hour_ini
202    tab_cntrl(29)=0
203    dscrpt_tab_cntrl(29) = "(29) 0                                    "
204  endif
205
206!--- File creation
207  CALL err(NF90_CREATE(fichnom,NF90_CLOBBER,nid))
208
209!--- Some global attributes
210  CALL err(NF90_PUT_ATT(nid,NF90_GLOBAL,"title","Fichier demarrage dynamique"))
211
212!--- Dimensions
213  if (start_file_type.eq."earth") then
214    CALL err(NF90_DEF_DIM(nid,"index", length, indexID))
215    CALL err(NF90_DEF_DIM(nid,"rlonu", iip1,   rlonuID))
216    CALL err(NF90_DEF_DIM(nid,"rlatu", jjp1,   rlatuID))
217    CALL err(NF90_DEF_DIM(nid,"rlonv", iip1,   rlonvID))
218    CALL err(NF90_DEF_DIM(nid,"rlatv", jjm,    rlatvID))
219    CALL err(NF90_DEF_DIM(nid,"sigs",  llm,        sID))
220    CALL err(NF90_DEF_DIM(nid,"sig",   llmp1,    sigID))
221    CALL err(NF90_DEF_DIM(nid,"temps", NF90_UNLIMITED, timID))
222    CALL err(NF90_DEF_DIM(nid,"descriptor", ldscrpt, descrptID))
223    CALL err(NF90_DEF_DIM(nid,"description_size", ndscrpt, dscrpt_sID))
224  else
225    CALL err(NF90_DEF_DIM(nid,"index", length, indexID))
226    CALL err(NF90_DEF_DIM(nid,"rlonu", iip1,   rlonuID))
227    CALL err(NF90_DEF_DIM(nid,"latitude", jjp1,   rlatuID))
228    CALL err(NF90_DEF_DIM(nid,"longitude", iip1,   rlonvID))
229    CALL err(NF90_DEF_DIM(nid,"rlatv", jjm,    rlatvID))
230    CALL err(NF90_DEF_DIM(nid,"altitude",  llm,        sID))
231    CALL err(NF90_DEF_DIM(nid,"interlayer",   llmp1,    sigID))
232    CALL err(NF90_DEF_DIM(nid,"Time", NF90_UNLIMITED, timID))
233    CALL err(NF90_DEF_DIM(nid,"descriptor", ldscrpt, descrptID))
234    CALL err(NF90_DEF_DIM(nid,"description_size", ndscrpt, dscrpt_sID))
235  endif
236
237!--- Define and save invariant fields
238  CALL put_var1(nid,"controle","Parametres de controle",[indexID],tab_cntrl)
239  CALL put_char1(nid,"controle_descriptor","Description of control parameters",[dscrpt_sID,descrptID],dscrpt_tab_cntrl)
240  CALL put_var1(nid,"rlonu"   ,"Longitudes des points U",[rlonuID],rlonu)
241  CALL put_var1(nid,"rlatu"   ,"Latitudes des points U" ,[rlatuID],rlatu)
242  CALL put_var1(nid,"rlonv"   ,"Longitudes des points V",[rlonvID],rlonv)
243  CALL put_var1(nid,"rlatv"   ,"Latitudes des points V" ,[rlatvID],rlatv)
244  if (start_file_type.eq."earth") then
245    CALL put_var1(nid,"nivsigs" ,"Numero naturel des couches s"    ,[sID]  ,nivsigs)
246    CALL put_var1(nid,"nivsig"  ,"Numero naturel des couches sigma",[sigID],nivsig)
247  endif ! of if (start_file_type.eq."earth")
248  CALL put_var1(nid,"ap"      ,"Coefficient A pour hybride"      ,[sigID],ap)
249  CALL put_var1(nid,"bp"      ,"Coefficient B pour hybride"      ,[sigID],bp)
250  if (start_file_type.ne."earth") then
251    CALL put_var1(nid,"aps","Coef AS: hybrid pressure at midlayers",[sID],aps)
252    CALL put_var1(nid,"bps","Coef BS: hybrid sigma at midlayers",[sID],bps)
253  endif ! of if (start_file_type.eq."earth")
254  CALL put_var1(nid,"presnivs",""                                ,[sID]  ,presnivs)
255  if (start_file_type.ne."earth") then
256        ierr = NF_REDEF (nid)
257#ifdef NC_DOUBLE
258        ierr = NF_DEF_VAR(nid,"latitude",NF_DOUBLE,1,rlatuID,vID)
259#else
260        ierr = NF_DEF_VAR(nid,"latitude",NF_FLOAT,1,rlatuID,vID)
261#endif
262        ierr =NF_PUT_ATT_TEXT(nid,vID,'units',13,"degrees_north")
263        ierr = NF_PUT_ATT_TEXT (nid,vID,"long_name", 14, &
264              "North latitude")
265        ierr = NF_ENDDEF(nid)
266        call NF95_PUT_VAR(nid,vID,rlatu*180/pi)
267!
268        ierr = NF_REDEF (nid)
269#ifdef NC_DOUBLE
270        ierr=NF_DEF_VAR(nid,"longitude",NF_DOUBLE,1,rlonvID,vID)
271#else
272        ierr=NF_DEF_VAR(nid,"longitude",NF_FLOAT,1,rlonvID,vID)
273#endif
274        ierr = NF_PUT_ATT_TEXT (nid,vID,"long_name", 14, &
275              "East longitude")
276        ierr = NF_PUT_ATT_TEXT(nid,vID,'units',12,"degrees_east")
277        ierr = NF_ENDDEF(nid)
278        call NF95_PUT_VAR(nid,vID,rlonv*180/pi)
279!
280        ierr = NF_REDEF (nid)
281#ifdef NC_DOUBLE
282        ierr = NF_DEF_VAR (nid, "altitude", NF_DOUBLE, 1, &
283             sID,vID)
284#else
285        ierr = NF_DEF_VAR (nid, "altitude", NF_FLOAT, 1, &
286             sID,vID)
287#endif
288        ierr = NF_PUT_ATT_TEXT(nid,vID,"long_name",10,"pseudo-alt")
289        ierr = NF_PUT_ATT_TEXT (nid,vID,'units',2,"km")
290        ierr = NF_PUT_ATT_TEXT (nid,vID,'positive',2,"up")
291        ierr = NF_ENDDEF(nid)
292        call NF95_PUT_VAR(nid,vID,pseudoalt)
293        CALL err(NF_REDEF(nid))
294  endif ! of if (start_file_type.ne."earth")
295
296! covariant <-> contravariant <-> natural conversion coefficients
297  CALL put_var2(nid,"cu","Coefficient de passage pour U",[rlonuID,rlatuID],cu)
298  CALL put_var2(nid,"cv","Coefficient de passage pour V",[rlonvID,rlatvID],cv)
299  CALL put_var2(nid,"aire","Aires de chaque maille"     ,[rlonvID,rlatuID],aire)
300  CALL put_var2(nid,"phisinit","Geopotentiel au sol"    ,[rlonvID,rlatuID],phis)
301
302
303! Define variables that will be stored later:
304  WRITE(unites,"('days since ',i4,'-',i2.2,'-',i2.2,' 00:00:00')") &
305               yyears0,mmois0,jjour0
306  IF (start_file_type.eq."earth") THEN
307    CALL cre_var(nid,"temps","Temps de simulation",[timID],unites)
308  ELSE
309    CALL cre_var(nid,"Time","Temps de simulation",[timID],unites)
310  ENDIF
311
312  CALL cre_var(nid,"ucov" ,"Vitesse U"  ,[rlonuID,rlatuID,sID,timID])
313  CALL cre_var(nid,"vcov" ,"Vitesse V"  ,[rlonvID,rlatvID,sID,timID])
314  CALL cre_var(nid,"teta" ,"Temperature",[rlonvID,rlatuID,sID,timID])
315
316  IF(nqtot.GE.1) THEN
317    DO iq=1,nqtot
318      CALL cre_var(nid,tname(iq),ttext(iq),[rlonvID,rlatuID,sID,timID])
319    END DO
320  ENDIF
321
322  CALL cre_var(nid,"masse","Masse d air"    ,[rlonvID,rlatuID,sID,timID])
323  CALL cre_var(nid,"ps"   ,"Pression au sol",[rlonvID,rlatuID    ,timID])
324
325  CALL err(NF90_CLOSE (nid)) ! close file
326
327  WRITE(lunout,*)TRIM(modname)//': iim,jjm,llm,iday_end',iim,jjm,llm,iday_end
328  WRITE(lunout,*)TRIM(modname)//': rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
329
330  deallocate(dscrpt_tab_cntrl)
331
332END SUBROUTINE dynredem0
333
334!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
335
336SUBROUTINE dynredem1(fichnom,time,vcov,ucov,teta,q,masse,ps)
337!
338!-------------------------------------------------------------------------------
339! Purpose: Write the NetCDF restart file (append).
340!-------------------------------------------------------------------------------
341  USE infotrac, ONLY: nqtot, tname, type_trac
342  USE control_mod, only : planet_type
343  USE netcdf,   ONLY: NF90_OPEN,  NF90_NOWRITE, NF90_GET_VAR, NF90_INQ_VARID,  &
344                      NF90_CLOSE, NF90_WRITE,   NF90_PUT_VAR, NF90_NoErr
345  use netcdf95, only: NF95_PUT_VAR
346  USE temps_mod, ONLY: itaufin,itau_dyn
347  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
348                          err, modname, fil, msg
349 
350  IMPLICIT NONE
351  include "dimensions.h"
352  include "paramet.h"
353  include "netcdf.inc"
354  include "comgeom.h"
355  include "iniprint.h"
356!===============================================================================
357! Arguments:
358  CHARACTER(LEN=*), INTENT(IN) :: fichnom              !-- FILE NAME
359  REAL, INTENT(IN)    ::  time                         !-- TIME
360  REAL, INTENT(IN)    ::  vcov(iip1,jjm, llm)          !-- V COVARIANT WIND
361  REAL, INTENT(IN)    ::  ucov(iip1,jjp1,llm)          !-- U COVARIANT WIND
362  REAL, INTENT(IN)    ::  teta(iip1,jjp1,llm)          !-- POTENTIAL TEMPERATURE
363  REAL, INTENT(INOUT) ::     q(iip1,jjp1,llm,nqtot)    !-- TRACERS
364  REAL, INTENT(IN)    :: masse(iip1,jjp1,llm)          !-- MASS PER CELL
365  REAL, INTENT(IN)    ::    ps(iip1,jjp1)              !-- GROUND PRESSURE
366!===============================================================================
367! Local variables:
368  INTEGER :: l, iq, nid, vID, ierr, nid_trac, vID_trac
369  INTEGER,SAVE :: nb=0
370  INTEGER, PARAMETER :: length=100
371  REAL               :: tab_cntrl(length) ! tableau des parametres du run
372  CHARACTER(LEN=256) :: var, dum
373  LOGICAL            :: lread_inca
374  CHARACTER(LEN=80) :: abort_message
375  CHARACTER(len=12) :: start_file_type="earth" ! default start file type
376
377  ! fill dynredem_mod module variables
378  modname='dynredem1'; fil=fichnom
379
380  if ((planet_type.eq."generic").or.(planet_type.eq."mars")) then
381      write(lunout,*) trim(modname),' : Planeto-like start file'
382      start_file_type="planeto"
383  else
384      write(lunout,*) trim(modname),' : Earth-like start file'
385  endif
386
387  CALL err(NF90_OPEN(fil,NF90_WRITE,nid),"open",fil)
388
389!--- Write/extend time coordinate
390  nb = nb + 1
391  if (start_file_type.eq."earth") then
392        ierr = NF_INQ_VARID(nid, "temps", vID)
393        IF (ierr .NE. NF_NOERR) THEN
394          write(lunout,*) NF_STRERROR(ierr)
395          abort_message='Variable temps n est pas definie'
396          CALL abort_gcm(modname,abort_message,ierr)
397        ENDIF
398 else
399        ierr = NF_INQ_VARID(nid,"Time", vID)
400        IF (ierr .NE. NF_NOERR) THEN
401          write(lunout,*) NF_STRERROR(ierr)
402          abort_message='Variable Time not found'
403          CALL abort_gcm(modname,abort_message,ierr)
404        ENDIF
405  endif ! of if (start_file_type.eq."earth")
406  call NF95_PUT_VAR(nid,vID,time,start=(/nb/))
407  WRITE(lunout,*)TRIM(modname)//": Saving for ", nb, time
408
409!--- Rewrite control table (itaufin undefined in dynredem0)
410  var="controle"
411  CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var)
412  CALL err(NF90_GET_VAR(nid,vID,tab_cntrl),"get",var)
413  if (start_file_type=="earth") then
414    tab_cntrl(31) = REAL(itau_dyn + itaufin)
415    tab_cntrl(32) = time
416  else
417    tab_cntrl(31) = 0
418  endif
419  CALL err(NF90_INQ_VARID(nid,var,vID),"inq",var)
420  CALL err(NF90_PUT_VAR(nid,vID,tab_cntrl),"put",var)
421
422!--- Save fields
423  CALL dynredem_write_u(nid,"ucov" ,ucov ,llm, nb)
424  CALL dynredem_write_v(nid,"vcov" ,vcov ,llm, nb)
425  CALL dynredem_write_u(nid,"teta" ,teta ,llm, nb)
426  CALL dynredem_write_u(nid,"masse",masse,llm, nb)
427  CALL dynredem_write_u(nid,"ps"   ,ps   ,1, nb)
428
429!--- Tracers in file "start_trac.nc" (added by Anne)
430  lread_inca=.FALSE.; fil="start_trac.nc"
431  IF(type_trac=='inca') INQUIRE(FILE=fil,EXIST=lread_inca)
432  IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open")
433
434!--- Save tracers
435  IF(nqtot.GE.1) THEN
436    DO iq=1,nqtot
437      var=tname(iq); ierr=-1
438      IF(lread_inca) THEN                  !--- Possibly read from "start_trac.nc"
439        fil="start_trac.nc"
440        ierr=NF90_INQ_VARID(nid_trac,var,vID_trac)
441        dum='inq'; IF(ierr==NF90_NoErr) dum='fnd'
442        WRITE(lunout,*)msg(dum,var)
443
444
445        IF(ierr==NF90_NoErr) CALL dynredem_read_u(nid_trac,var,q(:,:,:,iq),llm)
446      END IF ! of IF(lread_inca)
447      fil=fichnom
448      CALL dynredem_write_u(nid,var,q(:,:,:,iq),llm,nb)
449    END DO ! of DO iq=1,nqtot
450  ENDIF ! of IF(nqtot.GE.1)
451
452  CALL err(NF90_CLOSE(nid),"close")
453  fil="start_trac.nc"
454  IF(lread_inca) CALL err(NF90_CLOSE(nid_trac),"close")
455
456END SUBROUTINE dynredem1
Note: See TracBrowser for help on using the repository browser.