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

Last change on this file since 3992 was 3928, checked in by jmauxion, 4 months ago

Generic PCM:
Adding a slow_diagfi flag to the run.def/rcm1d.def file for 1D models only. When False, the netcdf
file is opened/closed once, thus saving significant computing time. When true,
the opening frequency is at output frequency (recommended in debug mode). Also
fixing a redundant loop on tracers when writing outputs in physiq_mod.
JM

File size: 22.9 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      use surfdat_h, only: phisfi
42      use geometry_mod, only: cell_area
43      use time_phylmdz_mod, only: diagfi_output_rate, dtphys, daysec
44      use time_phylmdz_mod, only: day_ini, nday, slow_diagfi
45      USE mod_phys_lmdz_para, only : is_parallel, is_mpi_root,
46     &                               is_master, gather
47      USE mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo,
48     &                              nbp_lon, nbp_lat, nbp_lev,
49     &                              grid_type, unstructured
50      implicit none
51
52! Commons
53      include "netcdf.inc"
54
55! Arguments on input:
56      integer,intent(in) :: ngrid
57      character (len=*),intent(in) :: nom,titre,unite
58      integer,intent(in) :: dim
59      real,intent(in) :: px(ngrid,nbp_lev)
60
61! Local variables:
62
63      real*4 dx3(nbp_lon+1,nbp_lat,nbp_lev) ! to store a 3D data set
64      real*4 dx2(nbp_lon+1,nbp_lat)     ! to store a 2D (surface) data set
65      real*4 dx1(nbp_lev)           ! to store a 1D (column) data set
66      real*4 dx0
67      real*4 dx3_1d(1,nbp_lev) ! to store a profile with 1D model
68      real*4 dx2_1d ! to store a surface value with 1D model
69
70      real*4,save :: date
71!$OMP THREADPRIVATE(date)
72
73      REAL phis((nbp_lon+1),nbp_lat)
74      REAL area((nbp_lon+1),nbp_lat)
75
76      integer ierr,ierr2
77      integer i,j,l, ig0
78
79      integer,save :: zitau=0
80      integer,save :: lastzitau=0
81      character(len=27),save :: firstnom='1234567890'
82      character(len=27),save :: prevnom='1234567890'
83      character(len=27),save :: lastnom='1234567890'
84!$OMP THREADPRIVATE(zitau,lastzitau,firstnom,prevnom,lastnom)
85
86! Ajouts
87      integer, save :: ntime=0
88!$OMP THREADPRIVATE(ntime)
89      integer :: idim,varid
90      integer, save :: nid
91!$OMP THREADPRIVATE(nid)
92      character(len=*),parameter :: fichnom="diagfi.nc"
93      integer, dimension(4) :: id
94      integer, dimension(4) :: edges,corner
95
96! Added to use diagfi.def to select output variable
97      logical,save :: diagfi_def
98      logical :: getout
99      integer,save :: n_nom_def
100      integer :: n
101      integer,parameter :: n_nom_def_max=199
102      character(len=120),save :: nom_def(n_nom_def_max)
103      logical,save :: firstcall=.true.
104!$OMP THREADPRIVATE(firstcall)  !diagfi_def,n_nom_def,nom_def read in diagfi.def
105     
106#ifdef CPP_PARA
107! Added to work in parallel mode
108      real dx3_glop(klon_glo,nbp_lev)
109      real dx3_glo(nbp_lon,nbp_lat,nbp_lev) ! to store a global 3D data set
110      real dx2_glop(klon_glo)
111      real dx2_glo(nbp_lon,nbp_lat)     ! to store a global 2D (surface) data set
112      real px2(ngrid)
113!      real dx1_glo(nbp_lev)          ! to store a 1D (column) data set
114!      real dx0_glo
115      real phisfi_glo(klon_glo) ! surface geopotential on global physics grid
116      real areafi_glo(klon_glo) ! mesh area on global physics grid
117#else
118      real phisfi_glo(ngrid) ! surface geopotential on global physics grid
119      real areafi_glo(ngrid) ! mesh area on global physics grid
120#endif
121
122      if (grid_type==unstructured) then
123           return
124      endif
125
126!***************************************************************
127
128! At very first call, check if there is a "diagfi.def" to use and read it
129! -----------------------------------------------------------------------
130      IF (firstcall) THEN
131         firstcall=.false.
132
133         ! Compute the lastzitau (i.e. last timestep-1)
134         lastzitau=nday*nint(daysec/dtphys)-1
135         if (MOD(lastzitau+1,diagfi_output_rate).ne.0.) then
136           ! If so, output rate is less than once per sol
137           ! We must adjust zitau to
138           lastzitau=lastzitau-MOD(lastzitau+1,diagfi_output_rate)
139         endif
140!$OMP MASTER
141  !      Open diagfi.def definition file if there is one:
142         open(99,file="diagfi.def",status='old',form='formatted',
143     s   iostat=ierr2)
144
145         if(ierr2.eq.0) then
146            diagfi_def=.true.
147            write(*,*) "******************"
148            write(*,*) "Reading diagfi.def"
149            write(*,*) "******************"
150            do n=1,n_nom_def_max
151              read(99,fmt='(a)',end=88) nom_def(n)
152              write(*,*) 'Output in diagfi: ', trim(nom_def(n))
153            end do
154 88         continue
155            if (n.ge.n_nom_def_max) then
156               write(*,*)"n_nom_def_max too small in writediagfi.F:",n
157               call abort_physic("writediagfi",
158     &             "n_nom_def_max too small",1)
159            end if
160            n_nom_def=n-1
161            close(99)
162         else
163            diagfi_def=.false.
164         endif
165!$OMP END MASTER
166!$OMP BARRIER
167      END IF ! of IF (firstcall)
168
169! Get out of write_diagfi if there is diagfi.def AND variable not listed
170!  ---------------------------------------------------------------------
171      if (diagfi_def) then
172          getout=.true.
173          do n=1,n_nom_def
174             if(trim(nom_def(n)).eq.nom) getout=.false.
175          end do
176          if (getout) return
177      end if
178
179! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
180! ------------------------------------------------------------------------
181! (at very first call to the subroutine, in accordance with diagfi.def)
182
183      if (firstnom.eq.'1234567890') then ! .true. for the very first valid
184      !   call to this subroutine; now set 'firstnom'
185         firstnom = nom
186         ! just to be sure, check that firstnom is large enough to hold nom
187         if (len_trim(firstnom).lt.len_trim(nom)) then
188           write(*,*) "writediagfi: Error !!!"
189           write(*,*) "   firstnom string not long enough!!"
190           write(*,*) "   increase its size to at least ",len_trim(nom)
191           call abort_physic("writediagfi","firstnom too short",1)
192         endif
193         
194         zitau = -1 ! initialize zitau
195
196#ifdef CPP_PARA
197          ! Gather phisfi() geopotential on physics grid
198          call Gather(phisfi,phisfi_glo)
199          ! Gather cell_area() mesh area on physics grid
200          call Gather(cell_area,areafi_glo)
201#else
202         phisfi_glo(:)=phisfi(:)
203         areafi_glo(:)=cell_area(:)
204#endif
205
206         !! parallel: we cannot use the usual writediagfi method
207!!         call iophys_ini
208         if (is_master) then
209         ! only the master is required to do this
210
211         ! Create the NetCDF file
212         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
213         ! Define the 'Time' dimension
214         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
215         ! Define the 'Time' variable
216!#ifdef NC_DOUBLE
217!         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
218!#else
219         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
220!#endif
221         ! Add a long_name attribute
222         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
223     .          4,"Time")
224         ! Add a units attribute
225         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
226     .          "days since 0000-00-0 00:00:00")
227         ! Switch out of NetCDF Define mode
228         ierr = NF_ENDDEF(nid)
229
230         ! Build phis() and area()
231         IF (klon_glo>1) THEN
232          do i=1,nbp_lon+1 ! poles
233           phis(i,1)=phisfi_glo(1)
234           phis(i,nbp_lat)=phisfi_glo(klon_glo)
235           ! for area, divide at the poles by nbp_lon
236           area(i,1)=areafi_glo(1)/nbp_lon
237           area(i,nbp_lat)=areafi_glo(klon_glo)/nbp_lon
238          enddo
239          do j=2,nbp_lat-1
240           ig0= 1+(j-2)*nbp_lon
241           do i=1,nbp_lon
242              phis(i,j)=phisfi_glo(ig0+i)
243              area(i,j)=areafi_glo(ig0+i)
244           enddo
245           ! handle redundant point in longitude
246           phis(nbp_lon+1,j)=phis(1,j)
247           area(nbp_lon+1,j)=area(1,j)
248          enddo
249         ENDIF
250         
251         ! write "header" of file (longitudes, latitudes, geopotential, ...)
252         IF (klon_glo>1) THEN ! general 3D case
253           call iniwrite(nid,day_ini,phis,area,nbp_lon+1,nbp_lat)
254         ELSE ! 1D model
255           call iniwrite(nid,day_ini,phisfi_glo(1),areafi_glo(1),1,1)
256         ENDIF
257
258         ierr= NF_CLOSE(nid) ! Close the NETCDF file once initialized
259
260         endif ! of if (is_master)
261      endif ! if (firstnom.eq.'1234567890')
262
263      ! Find lastnom
264      if (lastnom.eq.'1234567890') then
265         if (nom.eq.firstnom) then
266            if (prevnom.ne.'1234567890') then
267               lastnom=prevnom
268            endif
269         endif
270         prevnom=nom
271      endif
272
273! Increment time index 'zitau' if it is the "fist call" (at given time level)
274! to writediagfi
275!------------------------------------------------------------------------
276      if (nom.eq.firstnom) then
277          zitau = zitau + 1
278      end if
279
280!--------------------------------------------------------
281! Write the variables to output file if it's time to do so
282!--------------------------------------------------------
283
284      if ( MOD(zitau+1,diagfi_output_rate) .eq.0.) then
285
286! Compute/write/extend 'Time' coordinate (date given in days)
287! (done every "first call" (at given time level) to writediagfi)
288! Note: date is incremented as 1 step ahead of physics time
289!--------------------------------------------------------
290
291        if (is_master) then
292          ! only the master is required to do this
293
294          ! 1D and slow_diagfi=.false. => open/close once
295          if ((klon_glo.eq.1).and.(.not.slow_diagfi)) then
296            ! if the very first time to write, open
297            if ((nom.eq.firstnom).and.
298     &         (((zitau+1)/diagfi_output_rate).eq.1)) then
299              write(*,*) "Open NETCDF file for firstnom=", firstnom
300              write(*,*) "zitau=", zitau
301              ierr=NF_OPEN(fichnom,NF_WRITE,nid) ! open once in all simu
302            endif
303          else ! 3D or slow_diagfi=.true. => open/close at output frequency
304            ierr=NF_OPEN(fichnom,NF_WRITE,nid)           
305          endif
306
307        if (nom.eq.firstnom) then
308        ! We have identified a "first call" (at given date)
309           ntime=ntime+1 ! increment # of stored time steps
310           ! compute corresponding date (in days and fractions thereof)
311           date=(zitau +1.)*(dtphys/daysec)
312           ! Get NetCDF ID of 'Time' variable
313           ierr= NF_INQ_VARID(nid,"Time",varid)
314           ! Write (append) the new date to the 'Time' array
315!#ifdef NC_DOUBLE
316!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
317!#else
318           ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
319!#endif
320           if (ierr.ne.NF_NOERR) then
321              write(*,*) "***** PUT_VAR matter in writediagfi_nc"
322              write(*,*) "***** with time"
323              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr) 
324c             call abort
325           endif
326
327           write(6,*)'WRITEDIAGFI: date= ', date
328        end if ! of if (nom.eq.firstnom)
329
330        endif ! of if (is_master)
331
332!Case of a 3D variable
333!---------------------
334        if (dim.eq.3) then
335
336#ifdef CPP_PARA
337          ! Gather field on a "global" (without redundant longitude) array
338          call Gather(px,dx3_glop)
339!$OMP MASTER
340          if (is_mpi_root) then
341            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
342            ! copy dx3_glo() to dx3(:) and add redundant longitude
343            dx3(1:nbp_lon,:,:)=dx3_glo(1:nbp_lon,:,:)
344            dx3(nbp_lon+1,:,:)=dx3(1,:,:)
345          endif
346!$OMP END MASTER
347!$OMP BARRIER
348#else
349!         Passage variable physique -->  variable dynamique
350!         recast (copy) variable from physics grid to dynamics grid
351          IF (klon_glo>1) THEN ! General case
352           DO l=1,nbp_lev
353             DO i=1,nbp_lon+1
354                dx3(i,1,l)=px(1,l)
355                dx3(i,nbp_lat,l)=px(ngrid,l)
356             ENDDO
357             DO j=2,nbp_lat-1
358                ig0= 1+(j-2)*nbp_lon
359                DO i=1,nbp_lon
360                   dx3(i,j,l)=px(ig0+i,l)
361                ENDDO
362                dx3(nbp_lon+1,j,l)=dx3(1,j,l)
363             ENDDO
364           ENDDO
365          ELSE ! 1D model case
366           dx3_1d(1,1:nbp_lev)=px(1,1:nbp_lev)
367          ENDIF
368#endif
369!         Ecriture du champs
370
371          if (is_master) then
372           ! only the master writes to output
373! name of the variable
374           ierr= NF_INQ_VARID(nid,nom,varid)
375           if (ierr /= NF_NOERR) then
376! corresponding dimensions
377              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
378              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
379              ierr= NF_INQ_DIMID(nid,"altitude",id(3))
380              ierr= NF_INQ_DIMID(nid,"Time",id(4))
381
382! Create the variable if it doesn't exist yet
383
384              write (*,*) "=========================="
385              write (*,*) "DIAGFI: creating variable ",trim(nom)
386              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
387
388           else
389             if (ntime==0) then
390              write(*,*) "DIAGFI Error: failed creating variable ",
391     &                   trim(nom)
392              write(*,*) "it seems it already exists!"
393              call abort_physic("writediagfi",
394     &             trim(nom)//" already exists",1)
395             endif
396           endif
397
398           corner(1)=1
399           corner(2)=1
400           corner(3)=1
401           corner(4)=ntime
402
403           IF (klon_glo==1) THEN
404             edges(1)=1
405           ELSE
406             edges(1)=nbp_lon+1
407           ENDIF
408           edges(2)=nbp_lat
409           edges(3)=nbp_lev
410           edges(4)=1
411!#ifdef NC_DOUBLE
412!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
413!#else
414!           write(*,*)"test:  nid=",nid," varid=",varid
415!           write(*,*)"       corner()=",corner
416!           write(*,*)"       edges()=",edges
417!           write(*,*)"       dx3()=",dx3
418           IF (klon_glo>1) THEN ! General case
419             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
420           ELSE
421             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3_1d)
422           ENDIF
423!#endif
424
425           if (ierr.ne.NF_NOERR) then
426              write(*,*) "***** PUT_VAR problem in writediagfi"
427              write(*,*) "***** with dx3: ",trim(nom)
428              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
429              call abort_physic("writediagfi",
430     &             "failed writing "//trim(nom),1)
431           endif
432
433          endif !of if (is_master)
434
435!Case of a 2D variable
436!---------------------
437
438        else if (dim.eq.2) then
439
440#ifdef CPP_PARA
441          ! Gather field on a "global" (without redundant longitude) array
442          px2(:)=px(:,1)
443          call Gather(px2,dx2_glop)
444!$OMP MASTER
445          if (is_mpi_root) then
446            call Grid1Dto2D_glo(dx2_glop,dx2_glo)
447            ! copy dx2_glo() to dx2(:) and add redundant longitude
448            dx2(1:nbp_lon,:)=dx2_glo(1:nbp_lon,:)
449            dx2(nbp_lon+1,:)=dx2(1,:)
450          endif
451!$OMP END MASTER
452!$OMP BARRIER
453#else
454
455!         Passage variable physique -->  physique dynamique
456!         recast (copy) variable from physics grid to dynamics grid
457          IF (klon_glo>1) THEN ! General case
458             DO i=1,nbp_lon+1
459                dx2(i,1)=px(1,1)
460                dx2(i,nbp_lat)=px(ngrid,1)
461             ENDDO
462             DO j=2,nbp_lat-1
463                ig0= 1+(j-2)*nbp_lon
464                DO i=1,nbp_lon
465                   dx2(i,j)=px(ig0+i,1)
466                ENDDO
467                dx2(nbp_lon+1,j)=dx2(1,j)
468             ENDDO
469          ELSE ! 1D model case
470            dx2_1d=px(1,1)
471          ENDIF
472#endif
473
474          if (is_master) then
475           ! only the master writes to output
476!         write (*,*) 'In  writediagfi, on sauve:  ' , nom
477!         write (*,*) 'In  writediagfi. Estimated date = ' ,date
478           ierr= NF_INQ_VARID(nid,nom,varid)
479           if (ierr /= NF_NOERR) then
480! corresponding dimensions
481              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
482              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
483              ierr= NF_INQ_DIMID(nid,"Time",id(3))
484
485! Create the variable if it doesn't exist yet
486
487              write (*,*) "=========================="
488              write (*,*) "DIAGFI: creating variable ",trim(nom)
489
490              call def_var(nid,nom,titre,unite,3,id,varid,ierr)
491
492           else
493             if (ntime==0) then
494              write(*,*) "DIAGFI Error: failed creating variable ",
495     &                   trim(nom)
496              write(*,*) "it seems it already exists!"
497              call abort_physic("writediagfi",
498     &             trim(nom)//" already exists",1)
499             endif
500           endif
501
502           corner(1)=1
503           corner(2)=1
504           corner(3)=ntime
505           IF (klon_glo==1) THEN
506             edges(1)=1
507           ELSE
508             edges(1)=nbp_lon+1
509           ENDIF
510           edges(2)=nbp_lat
511           edges(3)=1
512
513
514!#ifdef NC_DOUBLE
515!           ierr = NF_PUT_VARA_DOUBLE (nid,varid,corner,edges,dx2)
516!#else         
517           IF (klon_glo>1) THEN ! General case
518             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx2)
519           ELSE
520             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx2_1d)
521           ENDIF
522!#endif     
523
524           if (ierr.ne.NF_NOERR) then
525              write(*,*) "***** PUT_VAR matter in writediagfi"
526              write(*,*) "***** with dx2: ",trim(nom)
527              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
528              call abort_physic("writediagfi",
529     &             "failed writing "//trim(nom),1)
530           endif
531
532          endif !of if (is_master)
533
534!Case of a 1D variable (ie: a column)
535!---------------------------------------------------
536
537       else if (dim.eq.1) then
538         if (is_parallel) then
539           write(*,*) "writediagfi error: dim=1 not implemented ",
540     &                 "in parallel mode. Problem for ",trim(nom)
541              call abort_physic("writediagfi",
542     &             "failed writing "//trim(nom),1)
543         endif
544!         Passage variable physique -->  physique dynamique
545!         recast (copy) variable from physics grid to dynamics grid
546          do l=1,nbp_lev
547            dx1(l)=px(1,l)
548          enddo
549         
550          ierr= NF_INQ_VARID(nid,nom,varid)
551           if (ierr /= NF_NOERR) then
552! corresponding dimensions
553              ierr= NF_INQ_DIMID(nid,"altitude",id(1))
554              ierr= NF_INQ_DIMID(nid,"Time",id(2))
555
556! Create the variable if it doesn't exist yet
557
558              write (*,*) "=========================="
559              write (*,*) "DIAGFI: creating variable ",trim(nom)
560
561              call def_var(nid,nom,titre,unite,2,id,varid,ierr)
562             
563           else
564             if (ntime==0) then
565              write(*,*) "DIAGFI Error: failed creating variable ",
566     &                   trim(nom)
567              write(*,*) "it seems it already exists!"
568              call abort_physic("writediagfi",
569     &             trim(nom)//" already exists",1)
570             endif
571           endif
572           
573           corner(1)=1
574           corner(2)=ntime
575           
576           edges(1)=nbp_lev
577           edges(2)=1
578!#ifdef NC_DOUBLE
579!           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx1)
580!#else
581           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx1)
582!#endif
583
584           if (ierr.ne.NF_NOERR) then
585              write(*,*) "***** PUT_VAR problem in writediagfi"
586              write(*,*) "***** with dx1: ",trim(nom)
587              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
588              call abort_physic("writediagfi",
589     &             "failed writing "//trim(nom),1)
590           endif
591
592!Case of a 0D variable (ie: a time-dependent scalar)
593!---------------------------------------------------
594
595        else if (dim.eq.0) then
596
597           dx0 = px (1,1)
598
599          if (is_master) then
600           ! only the master writes to output
601           ierr= NF_INQ_VARID(nid,nom,varid)
602           if (ierr /= NF_NOERR) then
603! corresponding dimensions
604              ierr= NF_INQ_DIMID(nid,"Time",id(1))
605
606! Create the variable if it doesn't exist yet
607
608              write (*,*) "=========================="
609              write (*,*) "DIAGFI: creating variable ",trim(nom)
610
611              call def_var(nid,nom,titre,unite,1,id,varid,ierr)
612
613           else
614             if (ntime==0) then
615              write(*,*) "DIAGFI Error: failed creating variable ",
616     &                   trim(nom)
617              write(*,*) "it seems it already exists!"
618              call abort_physic("writediagfi",
619     &             trim(nom)//" already exists",1)
620             endif
621           endif
622
623           corner(1)=ntime
624           edges(1)=1
625
626!#ifdef NC_DOUBLE
627!           ierr = NF_PUT_VARA_DOUBLE (nid,varid,corner,edges,dx0) 
628!#else
629           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx0)
630!#endif
631           if (ierr.ne.NF_NOERR) then
632              write(*,*) "***** PUT_VAR matter in writediagfi"
633              write(*,*) "***** with dx0: ",trim(nom)
634              write(*,*) 'ierr=', ierr,": ",NF_STRERROR(ierr)
635              call abort_physic("writediagfi",
636     &             "failed writing "//trim(nom),1)
637           endif
638
639          endif !of if (is_master)
640
641        endif ! of if (dim.eq.3) elseif(dim.eq.2)...
642
643        ! Only the master do it
644        if (is_master) then
645          ! 1D and slow_diagfi=.false. => open/close once
646          if ((klon_glo.eq.1).and.(.not.slow_diagfi)) then
647            ! if the very last time to write, close
648            if ((nom.eq.lastnom).and.(zitau.eq.lastzitau)) then
649              write(*,*) "Close NETCDF file for lastnom=",lastnom
650              write(*,*) "zitau=",zitau
651              ierr = NF_CLOSE(nid) ! close once in all simu
652            endif
653          else ! 3D or slow_diagfi=.true. => open/close at output frequency
654            ierr = NF_CLOSE(nid)
655          endif
656        endif
657
658      endif ! of if ( MOD(zitau+1,diagfi_output_rate) .eq.0.)
659
660      end
Note: See TracBrowser for help on using the repository browser.