source: trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F90 @ 3742

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