source: trunk/LMDZ.GENERIC/libf/phystd/writediagspecIR.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 writediagspecIR(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 OLR to be saved in .nc format
44      use radinc_h, only : L_NSPECTI
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,intent(in) :: ngrid
58      character (len=*),intent(in) :: nom,titre,unite
59      integer,intent(in) :: dimpx
60      real,intent(in) :: px(ngrid,L_NSPECTI)
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 OLR output
89       real dx3(nbp_lon+1,nbp_lat,L_NSPECTI) ! to store the data set
90
91#ifdef CPP_PARA
92! Added to work in parallel mode
93      real dx3_glop(klon_glo,L_NSPECTI)
94      real dx3_glo(nbp_lon,nbp_lat,L_NSPECTI) ! 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*iradia
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
110! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
111! ------------------------------------------------------------------------
112! (Au tout premier appel de la subroutine durant le run.)
113
114      fichnom="diagspecIR.nc"
115
116      if (firstnom.eq.'1234567890') then ! .true. for the very first call
117      !  to this subroutine; now set 'firstnom'
118         firstnom = nom
119         ! just to be sure, check that firstnom is large enough to hold nom
120         if (len_trim(firstnom).lt.len_trim(nom)) then
121           write(*,*) "writediagspecIR: Error !!!"
122           write(*,*) "   firstnom string not long enough!!"
123           write(*,*) "   increase its size to at least ",len_trim(nom)
124           stop
125         endif
126
127#ifdef CPP_PARA
128          ! Gather airephy() mesh area on physics grid
129          call Gather(airephy,areafi_glo)
130#else
131         areafi_glo(:)=airephy(:)
132#endif
133         ! Create the NetCDF file
134         if (is_master) then
135         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
136         ! Define the 'Time' dimension
137         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
138         ! Define the 'Time' variable
139#ifdef NC_DOUBLE
140         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
141#else
142         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
143#endif
144         ! Add a long_name attribute
145         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
146     .          4,"Time")
147         ! Add a units attribute
148         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
149     .          "days since 0000-00-0 00:00:00")
150         ! Switch out of NetCDF Define mode
151         ierr = NF_ENDDEF(nid)
152
153         ! Build area()
154         do i=1,nbp_lon+1 ! poles
155           ! divide at the poles by nbp_lon
156           area(i,1)=areafi_glo(1)/nbp_lon
157           area(i,nbp_lat)=areafi_glo(klon_glo)/nbp_lon
158         enddo
159         do j=2,nbp_lat-1
160           ig0= 1+(j-2)*nbp_lon
161           do i=1,nbp_lon
162              area(i,j)=areafi_glo(ig0+i)
163           enddo
164           ! handle redundant point in longitude
165           area(nbp_lon+1,j)=area(1,j)
166         enddo
167
168         ! write "header" of file (longitudes, latitudes, area, ...)
169         call iniwrite_specIR(nid,day_ini,area)
170         endif ! of if (is_master)
171
172         zitau = -1 ! initialize zitau
173      else
174         if (is_master) then
175           ! Open the NetCDF file
176           ierr = NF_OPEN(fichnom,NF_WRITE,nid)
177         endif
178      endif ! if (firstnom.eq.'1234567890')
179
180! Increment time index 'zitau' if it is the "firstcall" (at given time level)
181! to writediagfi
182!------------------------------------------------------------------------
183      if (nom.eq.firstnom) then
184          zitau = zitau + iphysiq
185      end if
186
187!--------------------------------------------------------
188! Write the variables to output file if it's time to do so
189!--------------------------------------------------------
190
191      if ( MOD(zitau+1,irythme) .eq.0.) then
192
193! Compute/write/extend 'Time' coordinate (date given in days)
194! (done every "first call" (at given time level) to writediagfi)
195! Note: date is incremented as 1 step ahead of physics time
196!       (like the 'histoire' outputs)
197!--------------------------------------------------------
198
199        if (nom.eq.firstnom) then
200
201        ! We have identified a "first call" (at given date)
202           ntime=ntime+1 ! increment # of stored time steps
203           ! compute corresponding date (in days and fractions thereof)
204           date= float (zitau +1)/float (day_step)
205
206           if (is_master) then
207             ! Get NetCDF ID of 'Time' variable
208             ierr= NF_INQ_VARID(nid,"Time",varid)
209
210             ! Write (append) the new date to the 'Time' array
211#ifdef NC_DOUBLE
212             ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
213#else
214             ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
215#endif
216             if (ierr.ne.NF_NOERR) then
217              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
218              write(*,*) "***** with time"
219              write(*,*) 'ierr=', ierr   
220c             call abort
221             endif
222
223             write(6,*)'WRITEDIAGSPECIR: date= ', date
224           endif ! of if (is_master)
225        end if ! of if (nom.eq.firstnom)
226
227
228 
229!Case of a 3D variable
230!---------------------
231        if (dimpx.eq.3) then
232
233!         A. Recast (copy) variable from physics grid to dynamics grid
234#ifdef CPP_PARA
235  ! gather field on a "global" (without redundant longitude) array
236          call Gather(px,dx3_glop)
237!$OMP MASTER
238          if (is_mpi_root) then
239            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
240            ! copy dx3_glo() to dx3(:) and add redundant longitude
241            dx3(1:nbp_lon,:,:)=dx3_glo(1:nbp_lon,:,:)
242            dx3(nbp_lon+1,:,:)=dx3(1,:,:)
243          endif
244!$OMP END MASTER
245!$OMP BARRIER
246#else
247           DO l=1,L_NSPECTI
248             DO i=1,nbp_lon+1
249                dx3(i,1,l)=px(1,l)
250                dx3(i,nbp_lat,l)=px(ngrid,l)
251             ENDDO
252             DO j=2,nbp_lat-1
253                ig0= 1+(j-2)*nbp_lon
254                DO i=1,nbp_lon
255                   dx3(i,j,l)=px(ig0+i,l)
256                ENDDO
257                dx3(nbp_lon+1,j,l)=dx3(1,j,l)
258             ENDDO
259           ENDDO
260#endif
261
262!         B. Write (append) the variable to the NetCDF file
263          if (is_master) then
264
265! name of the variable
266           ierr= NF_INQ_VARID(nid,nom,varid)
267           if (ierr /= NF_NOERR) then
268! corresponding dimensions
269              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
270              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
271              ierr= NF_INQ_DIMID(nid,"IR Wavenumber",id(3))
272              ierr= NF_INQ_DIMID(nid,"Time",id(4))
273
274! Create the variable if it doesn't exist yet
275
276              write (*,*) "=========================="
277              write (*,*) "DIAGSPECIR: creating variable ",nom
278              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
279
280           endif
281
282           corner(1)=1
283           corner(2)=1
284           corner(3)=1
285           corner(4)=ntime
286
287           edges(1)=nbp_lon+1
288           edges(2)=nbp_lat
289           edges(3)=L_NSPECTI
290           edges(4)=1
291#ifdef NC_DOUBLE
292           ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
293#else
294           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
295#endif
296
297           if (ierr.ne.NF_NOERR) then
298              write(*,*) "***** PUT_VAR problem in writediagspec"
299              write(*,*) "***** with ",nom
300              write(*,*) 'ierr=', ierr
301             call abort
302           endif
303
304          endif ! of if (is_master)
305
306        endif ! of if (dimpx.eq.3)
307
308      endif ! of if ( MOD(zitau+1,irythme) .eq.0.)
309
310      ! Close the NetCDF file
311      if (is_master) then
312        ierr= NF_CLOSE(nid)
313      endif
314
315      end
Note: See TracBrowser for help on using the repository browser.