source: trunk/LMDZ.GENERIC/libf/phystd/writediagspecVI.F @ 1529

Last change on this file since 1529 was 1529, checked in by emillour, 9 years ago

Generic GCM: Towards a cleaner separation between physics and dynamics

  • Got rid of references to "dimensions.h" from physics packages: use nbp_lon (=iim), nbp_lat (=jjp1) and nbp_lev from module mod_grid_phy_lmdz (in phy_common) instead.
  • Removed module "comhdiff_mod.F90", as it is only used by module surf_heat_transp_mod.F90, moved module variables there.
  • Addedin "surf_heat_transp_mod" local versions of some arrays and routines (from dyn3d) required to compute gradient, divergence, etc. on the global dynamics grid. As before, the slab ocean only works in serial.

EM

File size: 10.4 KB
Line 
1      subroutine writediagspecVI(ngrid,nom,titre,unite,dimpx,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!  Dans la version 2000, la periode d'ecriture est celle de
9!  "ecritphy " regle dans le fichier de controle de run :  run.def
10!
11!    writediagfi peut etre appele de n'importe quelle subroutine
12!    de la physique, plusieurs fois. L'initialisation et la creation du
13!    fichier se fait au tout premier appel.
14!
15! WARNING : les variables dynamique (u,v,t,q,ps)
16!  sauvees par writediagfi avec une
17! date donnee sont legerement differentes que dans le fichier histoire car
18! on ne leur a pas encore ajoute de la dissipation et de la physique !!!
19! IL est  RECOMMANDE d'ajouter les tendance physique a ces variables
20! avant l'ecriture dans diagfi (cf. physiq.F)
21
22!
23!  parametres (input) :
24!  ----------
25!      ngrid : nombres de point ou est calcule la physique
26!                (ngrid = 2+(jjm-1)*iim - 1/jjm)
27!                 (= nlon ou klon dans la physique terrestre)
28!     
29!      unit : unite logique du fichier de sortie (toujours la meme)
30!      nom  : nom de la variable a sortir (chaine de caracteres)
31!      titre: titre de la variable (chaine de caracteres)
32!      unite : unite de la variable (chaine de caracteres)
33!      px : variable a sortir (real 0, 2, ou 3d)
34!      dimpx : dimension de px : 0, 2, ou 3 dimensions
35!
36!=================================================================
37!
38!      This is a modified version that accepts spectrally varying input
39!      RW (2010)
40!
41!=================================================================
42 
43! Addition by RW (2010) to allow OSR to be saved in .nc format
44      use radinc_h, only : L_NSPECTV
45      use comgeomphy, only: airephy
46      use mod_phys_lmdz_para, only : is_mpi_root, is_master, gather
47      use mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo,
48     &                              nbp_lon, nbp_lat
49      use time_phylmdz_mod, only: ecritphy, iphysiq, day_step, day_ini
50      use callkeys_mod, only: iradia
51
52      implicit none
53
54      include "netcdf.inc"
55
56! Arguments on input:
57      integer ngrid
58      character (len=*) :: nom,titre,unite
59      integer dimpx
60      real px(ngrid,L_NSPECTV)
61
62! Local variables:
63
64!      real dx3(iip1,jjp1,llm) ! to store a 3D data set
65!      real dx2(iip1,jjp1)     ! to store a 2D (surface) data set
66!      real dx0
67
68      integer irythme
69      integer ierr
70      integer iq
71      integer i,j,l,zmax , ig0
72
73      integer,save :: zitau=0
74      character(len=20),save :: firstnom='1234567890'
75      real,save :: date
76!$OMP THREADPRIVATE(firstnom,zitau,date)
77
78! Ajouts
79      integer, save :: ntime=0
80!$OMP THREADPRIVATE(ntime)
81      integer :: idim,varid
82      integer :: nid
83      character (len =50):: fichnom
84      integer, dimension(4) :: id
85      integer, dimension(4) :: edges,corner
86
87      real area((nbp_lon+1),nbp_lat)
88! added by RDW for OSR output
89       real dx3(nbp_lon+1,nbp_lat,L_NSPECTV) ! to store the data set
90
91#ifdef CPP_PARA
92! Added to work in parallel mode
93      real dx3_glop(klon_glo,L_NSPECTV)
94      real dx3_glo(nbp_lon,nbp_lat,L_NSPECTV) ! to store a global 3D data set
95      real areafi_glo(klon_glo) ! mesh area on global physics grid
96#else
97      real areafi_glo(ngrid) ! mesh area on global physics grid
98#endif
99
100!***************************************************************
101!Sortie des variables au rythme voulu
102
103      irythme = ecritphy*iradia ! sortie au rythme de ecritphy
104!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
105!     irythme = iphysiq  ! sortie a tous les pas physique
106
107!***************************************************************
108
109! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
110! ------------------------------------------------------------------------
111! (Au tout premier appel de la subroutine durant le run.)
112
113      fichnom="diagspecVI.nc"
114
115      if (firstnom.eq.'1234567890') then ! .true. for the very first call
116      !  to this subroutine; now set 'firstnom'
117         firstnom = nom
118         ! just to be sure, check that firstnom is large enough to hold nom
119         if (len_trim(firstnom).lt.len_trim(nom)) then
120           write(*,*) "writediagfi: Error !!!"
121           write(*,*) "   firstnom string not long enough!!"
122           write(*,*) "   increase its size to at least ",len_trim(nom)
123           stop
124         endif
125
126#ifdef CPP_PARA
127          ! Gather airephy() mesh area on physics grid
128          call Gather(airephy,areafi_glo)
129#else
130         areafi_glo(:)=airephy(:)
131#endif
132         ! Create the NetCDF file
133         if (is_master) then
134         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
135         ! Define the 'Time' dimension
136         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
137         ! Define the 'Time' variable
138#ifdef NC_DOUBLE
139         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
140#else
141         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
142#endif
143         ! Add a long_name attribute
144         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
145     .          4,"Time")
146         ! Add a units attribute
147         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
148     .          "days since 0000-00-0 00:00:00")
149         ! Switch out of NetCDF Define mode
150         ierr = NF_ENDDEF(nid)
151
152         ! Build area()
153         do i=1,nbp_lon+1 ! poles
154           ! divide at the poles by nbp_lon
155           area(i,1)=areafi_glo(1)/nbp_lon
156           area(i,nbp_lat)=areafi_glo(klon_glo)/nbp_lon
157         enddo
158         do j=2,nbp_lat-1
159           ig0= 1+(j-2)*nbp_lon
160           do i=1,nbp_lon
161              area(i,j)=areafi_glo(ig0+i)
162           enddo
163           ! handle redundant point in longitude
164           area(nbp_lon+1,j)=area(1,j)
165         enddo
166
167         ! write "header" of file (longitudes, latitudes, geopotential, ...)
168         call iniwrite_specVI(nid,day_ini,area)
169         endif ! of if (is_master)
170
171         zitau = -1 ! initialize zitau
172      else
173         if (is_master) then
174           ! Open the NetCDF file
175           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
176         endif
177      endif ! if (firstnom.eq.'1234567890')
178
179! Increment time index 'zitau' if it is the "firstcall" (at given time level)
180! to writediagfi
181!------------------------------------------------------------------------
182      if (nom.eq.firstnom) then
183          zitau = zitau + iphysiq
184      end if
185
186!--------------------------------------------------------
187! Write the variables to output file if it's time to do so
188!--------------------------------------------------------
189
190      if ( MOD(zitau+1,irythme) .eq.0.) then
191
192! Compute/write/extend 'Time' coordinate (date given in days)
193! (done every "first call" (at given time level) to writediagfi)
194! Note: date is incremented as 1 step ahead of physics time
195!       (like the 'histoire' outputs)
196!--------------------------------------------------------
197
198        if (nom.eq.firstnom) then
199
200        ! We have identified a "first call" (at given date)
201           ntime=ntime+1 ! increment # of stored time steps
202           ! compute corresponding date (in days and fractions thereof)
203           date= float (zitau +1)/float (day_step)
204
205           if (is_master) then
206             ! Get NetCDF ID of 'Time' variable
207             ierr= NF_INQ_VARID(nid,"Time",varid)
208
209             ! Write (append) the new date to the 'Time' array
210#ifdef NC_DOUBLE
211             ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
212#else
213             ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
214#endif
215             if (ierr.ne.NF_NOERR) then
216              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
217              write(*,*) "***** with time"
218              write(*,*) 'ierr=', ierr   
219c             call abort
220             endif
221
222             write(6,*)'WRITEDIAGSPECVI: date= ', date
223           endif ! of if (is_master)
224        end if ! of if (nom.eq.firstnom)
225
226
227 
228!Case of a 3D variable
229!---------------------
230        if (dimpx.eq.3) then
231
232!         A. Recast (copy) variable from physics grid to dynamics grid
233#ifdef CPP_PARA
234  ! gather field on a "global" (without redundant longitude) array
235          call Gather(px,dx3_glop)
236!$OMP MASTER
237          if (is_mpi_root) then
238            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
239            ! copy dx3_glo() to dx3(:) and add redundant longitude
240            dx3(1:nbp_lon,:,:)=dx3_glo(1:nbp_lon,:,:)
241            dx3(nbp_lon+1,:,:)=dx3(1,:,:)
242          endif
243!$OMP END MASTER
244!$OMP BARRIER
245#else
246           DO l=1,L_NSPECTV
247             DO i=1,nbp_lon+1
248                dx3(i,1,l)=px(1,l)
249                dx3(i,nbp_lat,l)=px(ngrid,l)
250             ENDDO
251             DO j=2,nbp_lat-1
252                ig0= 1+(j-2)*nbp_lon
253                DO i=1,nbp_lon
254                   dx3(i,j,l)=px(ig0+i,l)
255                ENDDO
256                dx3(nbp_lon+1,j,l)=dx3(1,j,l)
257             ENDDO
258           ENDDO
259#endif
260
261!         B. Write (append) the variable to the NetCDF file
262          if (is_master) then
263
264! name of the variable
265           ierr= NF_INQ_VARID(nid,nom,varid)
266           if (ierr /= NF_NOERR) then
267! corresponding dimensions
268              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
269              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
270              ierr= NF_INQ_DIMID(nid,"VI Wavenumber",id(3))
271              ierr= NF_INQ_DIMID(nid,"Time",id(4))
272
273! Create the variable if it doesn't exist yet
274
275              write (*,*) "=========================="
276              write (*,*) "DIAGSPEC: creating variable ",nom
277              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
278
279           endif
280
281           corner(1)=1
282           corner(2)=1
283           corner(3)=1
284           corner(4)=ntime
285
286           edges(1)=nbp_lon+1
287           edges(2)=nbp_lat
288           edges(3)=L_NSPECTV
289           edges(4)=1
290#ifdef NC_DOUBLE
291           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
292#else
293           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
294#endif
295
296           if (ierr.ne.NF_NOERR) then
297              write(*,*) "***** PUT_VAR problem in writediagspec"
298              write(*,*) "***** with ",nom
299              write(*,*) 'ierr=', ierr
300             call abort
301           endif
302
303          endif ! of if (is_master)
304
305        endif ! of if (dimpx.eq.3)
306
307      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
308
309      ! Close the NetCDF file
310      if (is_master) then
311        ierr= NF_CLOSE(nid)
312      endif
313
314      end
Note: See TracBrowser for help on using the repository browser.