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

Last change on this file since 3552 was 3510, checked in by jbclement, 6 weeks ago

Dynamic:
Following of r3509, the description of the 'controle' array in the "start.nc" file is adapted to the planet type (earth, mars or titan).
JBC

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