source: trunk/LMDZ.GENERIC/libf/phystd/writediagfi.F @ 848

Last change on this file since 848 was 787, checked in by aslmd, 12 years ago

LMDZ.GENERIC. (Sorry for long text but this is a quite major commit)

Paving the path for parallel computations. And moving towards a more flexible code.

Automatic allocation is used within all routines in phystd. No further mention to ngridmx and nqmx.

  1. ngridmx and nqmx are still used in LMDZ.GENERIC in the dyn3d part
  2. if the LMDZ4/LMDZ5 dynamical core is used, there is no more fixed dimensions ngridmx and nqmx --> a fully flexible parallel implementation is now possible (e.g. no need to recompile when changing numbers of processors)

The important stuff :

  • Compilation checked with ifort. OK with and without debug mode. No errors. Checked for: gcm, newstart, rcm1d, kcm1d
  • RUN GCM: Running an Earth test case. Comparison with previous revision --> debug mode : perfect match. bit by bit (diff command). checked with plots --> O1 mode : close match (checked with plots) --> O2 mode : sometimes up to 0.5 K departure.... BUT in this new version O2 and O1 are quite close while in previous version O1 and O2 differed by about, well, typically 0.5 K (pictures available on request)
  • RUN NEWSTART : perfect match (bit-by-bit) in either debug or normal mode.
  • RUN RCM1D : perfect match in normal mode.
  • RUN KCM1D : not tested (I don't know what is the use of kcm1d)

List of main changes :

  • Additional arguments to some subroutines (ngrid and nq)
  • F77 include strategy is obsolete and replaced by F90 module strategy In this new strategy arrays are allocatable and allocated once at first use This has to be done for all common featuring arrays defined with ngridmx or nqmx

surfdat.h >> surfdat_h.F90
tracer.h >> tracer_h.F90
comsaison.h >> comsaison_h.F90
comgeomfi.h >> comgeomfi_h.F90
comsoil.h >> comsoil_h.F90
comdiurn.h >> comdiurn_h.F90
fisice.h >> DELETED. was not used. probably a fossil.
watercap.h >> DELETED. variable put in surfdat_h.F90

  • F77 'save' strategy is obsolete and replaced by F90 'allocatable save' strategy (see previous point and e.g. new version of physiq.F90)
  • Suppressing any mention to advtrac.h which is a common in the dynamics and needs nqmx This was easily solved by adding an argument with tracer names, coming from the dynamics This is probably not a definitive solution, ... but this allows for generic physics to work easily with either LMDZ.GENERIC or LMDZ dynamical cores
  • Removing consistency tests between nq and nqmx ; and ngrid and ngridmx. No use now!
  • Adaptation of rcm1d, kcm1d, newstart given above-mentioned changes

A note on phyetat0 and soil_setting:

  • Now written so that a slice of horizontal size 'ngrid' starting at grid point 'cursor' is read in startfi.nc 'cursor' is defined in dimphys.h and initialized by inifis (or in newstart) this is useful for parallel computations. default behavior is the usual one : sequential runs, cursor is 1, size ngrid is the whole global domain

A note on an additional change :

  • nueffrad is now an argument to callcorrk as is the case for reffrad both are saved in physiq this is for consistency and lisibility (previously nueffrad was saved in callcorrk) ... but there is a call to a function which modifies nueffrad in physiq ... previously this was not modifying nueffrad (although it was quite cumbersome to detect this) ... to be conservative I kept this behaviour and highlighted it with an array nueffrad_dummy ... I added a comment because someone might want to change this
File size: 14.6 KB
Line 
1      subroutine writediagfi(ngrid,nom,titre,unite,dim,px)
2
3!  Ecriture de variables diagnostiques au choix dans la physique
4!  dans un fichier NetCDF nomme  'diagfi'. Ces variables peuvent etre
5!  3d (ex : temperature), 2d (ex : temperature de surface), ou
6!  0d (pour un scalaire qui ne depend que du temps : ex : la longitude
7!  solaire)
8!  (ou encore 1d, dans le cas de testphys1d, pour sortir une colonne)
9!  La periode d'ecriture est donnee par
10!  "ecritphy " regle dans le fichier de controle de run :  run.def
11!
12!    writediagfi peut etre appele de n'importe quelle subroutine
13!    de la physique, plusieurs fois. L'initialisation et la creation du
14!    fichier se fait au tout premier appel.
15!
16! WARNING : les variables dynamique (u,v,t,q,ps)
17!  sauvees par writediagfi avec une
18! date donnee sont legerement differentes que dans le fichier histoire car
19! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
20! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
21! avant l'ecriture dans diagfi (cf. physiq.F)
22
23! Modifs: Aug.2010 Ehouarn: enforce outputs to be real*4
24!         Oct 2011 Francois: enable having a 'diagfi.def' file to select
25!                            at runtime, which variables to put in file
26!
27!  parametres (input) :
28!  ----------
29!      ngrid : nombres de point ou est calcule la physique
30!                (ngrid = 2+(jjm-1)*iim - 1/jjm)
31!                 (= nlon ou klon dans la physique terrestre)
32!     
33!      unit : unite logique du fichier de sortie (toujours la meme)
34!      nom  : nom de la variable a sortir (chaine de caracteres)
35!      titre: titre de la variable (chaine de caracteres)
36!      unite : unite de la variable (chaine de caracteres)
37!      px : variable a sortir (real 0, 1, 2, ou 3d)
38!      dim : dimension de px : 0, 1, 2, ou 3 dimensions
39!
40!=================================================================
41
42      USE surfdat_h
43 
44      implicit none
45
46! Commons
47#include "dimensions.h"
48#include "dimphys.h"
49#include "paramet.h"
50#include "control.h"
51#include "comvert.h"
52#include "comgeom.h"
53#include "description.h"
54#include "netcdf.inc"
55#include "temps.h"
56
57! Arguments on input:
58      integer,intent(in) :: ngrid
59      character (len=*),intent(in) :: nom,titre,unite
60      integer,intent(in) :: dim
61      real,intent(in) :: px(ngrid,llm)
62
63! Local variables:
64
65      real*4 dx3(iip1,jjp1,llm) ! to store a 3D data set
66      real*4 dx2(iip1,jjp1)     ! to store a 2D (surface) data set
67      real*4 dx1(llm)           ! to store a 1D (column) data set
68      real*4 dx0
69
70      real*4,save :: date
71
72      REAL phis(ip1jmp1)
73
74      integer irythme
75      integer ierr,ierr2
76      integer iq
77      integer i,j,l,zmax , ig0
78
79      integer,save :: zitau=0
80      character(len=20),save :: firstnom='1234567890'
81
82! Ajouts
83      integer, save :: ntime=0
84      integer :: idim,varid
85      integer :: nid
86      character(len=*),parameter :: fichnom="diagfi.nc"
87      integer, dimension(4) :: id
88      integer, dimension(4) :: edges,corner
89
90! Added to use diagfi.def to select output variable
91      logical,save :: diagfi_def
92      logical :: getout
93      integer,save :: n_nom_def
94      integer :: n
95      integer,parameter :: n_nom_def_max=99
96      character(len=20),save :: nom_def(n_nom_def_max)
97      logical,save :: firstcall=.true.
98
99!***************************************************************
100!Sortie des variables au rythme voulu
101
102      irythme = int(ecritphy) ! sortie au rythme de ecritphy
103!     irythme = iconser  ! sortie au rythme des variables de controle
104!     irythme = iphysiq  ! sortie a tous les pas physique
105!     irythme = iecri*day_step ! sortie au rythme des fichiers histoires
106!     irythme = periodav*day_step ! sortie au rythme des fichiers histmoy
107
108!***************************************************************
109
110#ifndef NOWRITEDIAGFI
111
112! At very first call, check if there is a "diagfi.def" to use and read it
113! -----------------------------------------------------------------------
114      IF (firstcall) THEN
115         firstcall=.false.
116
117!      Open diagfi.def definition file if there is one:
118         open(99,file="diagfi.def",status='old',form='formatted',
119     s   iostat=ierr2)
120
121         if(ierr2.eq.0) then
122            diagfi_def=.true.
123            write(*,*) "******************"
124            write(*,*) "Reading diagfi.def"
125            write(*,*) "******************"
126            do n=1,n_nom_def_max
127              read(99,fmt='(a)',end=88) nom_def(n)
128              write(*,*) 'Output in diagfi: ', trim(nom_def(n))
129            end do
130 88         continue
131            if (n.ge.n_nom_def_max) then
132               write(*,*)"n_nom_def_max too small in writediagfi.F:",n
133               stop
134            end if
135            n_nom_def=n-1
136            close(99)
137         else
138            diagfi_def=.false.
139         endif
140      END IF ! of IF (firstcall)
141
142! Get out of write_diagfi if there is diagfi.def AND variable not listed
143!  ---------------------------------------------------------------------
144      if (diagfi_def) then
145          getout=.true.
146          do n=1,n_nom_def
147             if(trim(nom_def(n)).eq.nom) getout=.false.
148          end do
149          if (getout) return
150      end if
151
152! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
153! ------------------------------------------------------------------------
154! (at very first call to the subroutine, in accordance with diagfi.def)
155
156      if (firstnom.eq.'1234567890') then ! .true. for the very first valid
157      !   call to this subroutine; now set 'firstnom'
158         firstnom = nom
159         ! just to be sure, check that firstnom is large enough to hold nom
160         if (len_trim(firstnom).lt.len_trim(nom)) then
161           write(*,*) "writediagfi: Error !!!"
162           write(*,*) "   firstnom string not long enough!!"
163           write(*,*) "   increase its size to at least ",len_trim(nom)
164           stop
165         endif
166
167         ! Create the NetCDF file
168         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
169         ! Define the 'Time' dimension
170         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
171         ! Define the 'Time' variable
172!#ifdef NC_DOUBLE
173!         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
174!#else
175         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
176!#endif
177         ! Add a long_name attribute
178         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
179     .          4,"Time")
180         ! Add a units attribute
181         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
182     .          "days since 0000-00-0 00:00:00")
183         ! Switch out of NetCDF Define mode
184         ierr = NF_ENDDEF(nid)
185
186         ! write "header" of file (longitudes, latitudes, geopotential, ...)
187         call gr_fi_dyn(1,ngrid,iip1,jjp1,phisfi,phis)
188         call iniwrite(nid,day_ini,phis)
189         
190         zitau = -1 ! initialize zitau
191      else
192         ! Open the NetCDF file
193         ierr = NF_OPEN(fichnom,NF_WRITE,nid)
194      endif ! if (firstnom.eq.'1234567890')
195
196      if (ngrid.eq.1) then
197        ! in testphys1d, for the 1d version of the GCM, iphysiq and irythme
198        ! are undefined; so set them to 1
199        iphysiq=1
200        !JL11 irythme=1
201        ! NB:
202      endif
203
204! Increment time index 'zitau' if it is the "fist call" (at given time level)
205! to writediagfi
206!------------------------------------------------------------------------
207      if (nom.eq.firstnom) then
208          zitau = zitau + iphysiq
209      end if
210
211!--------------------------------------------------------
212! Write the variables to output file if it's time to do so
213!--------------------------------------------------------
214
215      if ( MOD(zitau+1,irythme) .eq.0.) then
216
217! Compute/write/extend 'Time' coordinate (date given in days)
218! (done every "first call" (at given time level) to writediagfi)
219! Note: date is incremented as 1 step ahead of physics time
220!--------------------------------------------------------
221
222        if (nom.eq.firstnom) then
223        ! We have identified a "first call" (at given date)
224           ntime=ntime+1 ! increment # of stored time steps
225           ! compute corresponding date (in days and fractions thereof)
226           date= float (zitau +1)/float (day_step)
227           ! Get NetCDF ID of 'Time' variable
228           ierr= NF_INQ_VARID(nid,"Time",varid)
229           ! Write (append) the new date to the 'Time' array
230!#ifdef NC_DOUBLE
231!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
232!#else
233           ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
234!#endif
235           if (ierr.ne.NF_NOERR) then
236              write(*,*) "***** PUT_VAR matter in writediagfi_nc"
237              write(*,*) "***** with time"
238              write(*,*) 'ierr=', ierr   
239c             call abort
240           endif
241
242           write(6,*)'WRITEDIAGFI: date= ', date
243        end if ! of if (nom.eq.firstnom)
244
245!Case of a 3D variable
246!---------------------
247        if (dim.eq.3) then
248
249!         Passage variable physique -->  variable dynamique
250!         recast (copy) variable from physics grid to dynamics grid
251           DO l=1,llm
252             DO i=1,iip1
253                dx3(i,1,l)=px(1,l)
254                dx3(i,jjp1,l)=px(ngrid,l)
255             ENDDO
256             DO j=2,jjm
257                ig0= 1+(j-2)*iim
258                DO i=1,iim
259                   dx3(i,j,l)=px(ig0+i,l)
260                ENDDO
261                dx3(iip1,j,l)=dx3(1,j,l)
262             ENDDO
263           ENDDO
264
265!         Ecriture du champs
266
267!         write (*,*) 'In  writediagfi, on sauve:  ' , nom
268!         write (*,*) 'In  writediagfi. Estimated date = ' ,date
269! name of the variable
270           ierr= NF_INQ_VARID(nid,nom,varid)
271           if (ierr /= NF_NOERR) then
272! corresponding dimensions
273              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
274              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
275              ierr= NF_INQ_DIMID(nid,"altitude",id(3))
276              ierr= NF_INQ_DIMID(nid,"Time",id(4))
277
278! Create the variable if it doesn't exist yet
279
280              write (*,*) "=========================="
281              write (*,*) "DIAGFI: creating variable ",nom
282              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
283
284           endif
285
286           corner(1)=1
287           corner(2)=1
288           corner(3)=1
289           corner(4)=ntime
290
291           edges(1)=iip1
292           edges(2)=jjp1
293           edges(3)=llm
294           edges(4)=1
295!#ifdef NC_DOUBLE
296!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
297!#else
298           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
299!#endif
300
301           if (ierr.ne.NF_NOERR) then
302              write(*,*) "***** PUT_VAR problem in writediagfi"
303              write(*,*) "***** with ",nom
304              write(*,*) 'ierr=', ierr
305c             call abort
306           endif
307
308!Case of a 2D variable
309!---------------------
310
311        else if (dim.eq.2) then
312
313!         Passage variable physique -->  physique dynamique
314!         recast (copy) variable from physics grid to dynamics grid
315
316             DO i=1,iip1
317                dx2(i,1)=px(1,1)
318                dx2(i,jjp1)=px(ngrid,1)
319             ENDDO
320             DO j=2,jjm
321                ig0= 1+(j-2)*iim
322                DO i=1,iim
323                   dx2(i,j)=px(ig0+i,1)
324                ENDDO
325                dx2(iip1,j)=dx2(1,j)
326             ENDDO
327
328!         write (*,*) 'In  writediagfi, on sauve:  ' , nom
329!         write (*,*) 'In  writediagfi. Estimated date = ' ,date
330           ierr= NF_INQ_VARID(nid,nom,varid)
331           if (ierr /= NF_NOERR) then
332! corresponding dimensions
333              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
334              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
335              ierr= NF_INQ_DIMID(nid,"Time",id(3))
336
337! Create the variable if it doesn't exist yet
338
339              write (*,*) "=========================="
340              write (*,*) "DIAGFI: creating variable ",nom
341
342              call def_var(nid,nom,titre,unite,3,id,varid,ierr)
343
344           endif
345
346           corner(1)=1
347           corner(2)=1
348           corner(3)=ntime
349           edges(1)=iip1
350           edges(2)=jjp1
351           edges(3)=1
352
353
354!#ifdef NC_DOUBLE
355!           ierr = NF_PUT_VARA_DOUBLE (nid,varid,corner,edges,dx2)
356!#else         
357           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx2)
358!#endif     
359
360           if (ierr.ne.NF_NOERR) then
361              write(*,*) "***** PUT_VAR matter in writediagfi"
362              write(*,*) "***** with ",nom
363              write(*,*) 'ierr=', ierr
364c             call abort
365           endif
366
367!Case of a 1D variable (ie: a column)
368!---------------------------------------------------
369
370       else if (dim.eq.1) then
371!         Passage variable physique -->  physique dynamique
372!         recast (copy) variable from physics grid to dynamics grid
373          do l=1,llm
374            dx1(l)=px(1,l)
375          enddo
376         
377          ierr= NF_INQ_VARID(nid,nom,varid)
378           if (ierr /= NF_NOERR) then
379! corresponding dimensions
380              ierr= NF_INQ_DIMID(nid,"altitude",id(1))
381              ierr= NF_INQ_DIMID(nid,"Time",id(2))
382
383! Create the variable if it doesn't exist yet
384
385              write (*,*) "=========================="
386              write (*,*) "DIAGFI: creating variable ",nom
387
388              call def_var(nid,nom,titre,unite,2,id,varid,ierr)
389             
390           endif
391           
392           corner(1)=1
393           corner(2)=ntime
394           
395           edges(1)=llm
396           edges(2)=1
397!#ifdef NC_DOUBLE
398!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx1)
399!#else
400           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx1)
401!#endif
402
403           if (ierr.ne.NF_NOERR) then
404              write(*,*) "***** PUT_VAR problem in writediagfi"
405              write(*,*) "***** with ",nom
406              write(*,*) 'ierr=', ierr
407c             call abort
408           endif
409
410!Case of a 0D variable (ie: a time-dependent scalar)
411!---------------------------------------------------
412
413        else if (dim.eq.0) then
414           dx0 = px (1,1)
415
416           ierr= NF_INQ_VARID(nid,nom,varid)
417           if (ierr /= NF_NOERR) then
418! corresponding dimensions
419              ierr= NF_INQ_DIMID(nid,"Time",id(1))
420
421! Create the variable if it doesn't exist yet
422
423              write (*,*) "=========================="
424              write (*,*) "DIAGFI: creating variable ",nom
425
426              call def_var(nid,nom,titre,unite,1,id,varid,ierr)
427
428           endif
429
430           corner(1)=ntime
431           edges(1)=1
432
433!#ifdef NC_DOUBLE
434!           ierr = NF_PUT_VARA_DOUBLE (nid,varid,corner,edges,dx0) 
435!#else
436           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx0)
437!#endif
438           if (ierr.ne.NF_NOERR) then
439              write(*,*) "***** PUT_VAR matter in writediagfi"
440              write(*,*) "***** with ",nom
441              write(*,*) 'ierr=', ierr
442c             call abort
443           endif
444
445        endif ! of if (dim.eq.3) elseif(dim.eq.2)...
446
447      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
448
449      ierr= NF_CLOSE(nid)
450
451#endif
452
453      end
Note: See TracBrowser for help on using the repository browser.