source: trunk/LMDZ.PLUTO/libf/phypluto/writediagspecIR.F @ 4027

Last change on this file since 4027 was 4027, checked in by debatzbr, 6 days ago

Pluto PCM: Adding a slow_diagfi flag for 1D model from Generic PCM (revision 3928).
BBT

File size: 11.5 KB
RevLine 
[3184]1      subroutine writediagspecIR(ngrid,nom,titre,unite,dimpx,px)
2
[3749]3!  Ecriture de variables diagnostiques au choix dans la physique
[3184]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)
[3749]8!  Dans la version 2000, la periode d'ecriture est celle de
9!  "diagfi_output_rate " regle dans le fichier de controle de run :  run.def
[3184]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
[3749]17! date donnee sont legerement differentes que dans le fichier histoire car
[3184]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!
[3749]22!
[3184]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)
[3749]28!
[3184]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!=================================================================
[3749]42
[3184]43! Addition by RW (2010) to allow OLR to be saved in .nc format
44      use radinc_h, only : L_NSPECTI
45      use geometry_mod, only: cell_area
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, grid_type,
49     &                              unstructured
[3749]50      use time_phylmdz_mod, only: diagfi_output_rate,dtphys,daysec
51      use time_phylmdz_mod, only: day_ini
[3184]52      use callkeys_mod, only: iradia
53
54      implicit none
55
56      include "netcdf.inc"
57
58! Arguments on input:
59      integer,intent(in) :: ngrid
60      character (len=*),intent(in) :: nom,titre,unite
61      integer,intent(in) :: dimpx
62      real,intent(in) :: px(ngrid,L_NSPECTI)
63
64! Local variables:
65
66!      real dx3(iip1,jjp1,llm) ! to store a 3D data set
67!      real dx2(iip1,jjp1)     ! to store a 2D (surface) data set
68!      real dx0
69
[3749]70      integer isample
[3184]71      integer ierr
72      integer iq
73      integer i,j,l,zmax , ig0
74
75      integer,save :: zitau=0
76      character(len=20),save :: firstnom='1234567890'
77      real,save :: date
78!$OMP THREADPRIVATE(firstnom,zitau,date)
79
80! Ajouts
81      integer, save :: ntime=0
82!$OMP THREADPRIVATE(ntime)
83      integer :: idim,varid
84      integer :: nid
85      character (len =50):: fichnom
86      integer, dimension(4) :: id
87      integer, dimension(4) :: edges,corner
88
89      real area((nbp_lon+1),nbp_lat)
90! added by RDW for OLR output
91      real dx3(nbp_lon+1,nbp_lat,L_NSPECTI) ! to store the data set
92      real dx3_1d(1,L_NSPECTI) ! to store the data with 1D model
93
94#ifdef CPP_PARA
95! Added to work in parallel mode
96      real dx3_glop(klon_glo,L_NSPECTI)
97      real dx3_glo(nbp_lon,nbp_lat,L_NSPECTI) ! to store a global 3D data set
98      real areafi_glo(klon_glo) ! mesh area on global physics grid
99#else
100      real areafi_glo(ngrid) ! mesh area on global physics grid
101#endif
[3749]102      if (grid_type == unstructured) then
103        return
[3184]104      endif
105
106!***************************************************************
107!Sortie des variables au rythme voulu
108
[3749]109      isample = diagfi_output_rate*iradia ! sortie au rythme de diagfi_output_rate*iradia
[3184]110!EM+JL if the spetra need to be output more frequently, need to define a ecritSpec...
[3749]111!     isample = iphysiq  ! sortie a tous les pas physique
[3184]112
113
114!***************************************************************
115
116! Initialisation of 'firstnom' and create/open the "diagfi.nc" NetCDF file
117! ------------------------------------------------------------------------
118! (Au tout premier appel de la subroutine durant le run.)
119
120      fichnom="diagspecIR.nc"
121
122      if (firstnom.eq.'1234567890') then ! .true. for the very first call
123      !  to this subroutine; now set 'firstnom'
124         firstnom = nom
125         ! just to be sure, check that firstnom is large enough to hold nom
126         if (len_trim(firstnom).lt.len_trim(nom)) then
127           write(*,*) "writediagspecIR: Error !!!"
128           write(*,*) "   firstnom string not long enough!!"
129           write(*,*) "   increase its size to at least ",len_trim(nom)
130           stop
131         endif
132
133#ifdef CPP_PARA
134          ! Gather cell_area() mesh area on physics grid
135          call Gather(cell_area,areafi_glo)
136#else
137         areafi_glo(:)=cell_area(:)
138#endif
139         ! Create the NetCDF file
140         if (is_master) then
141         ierr = NF_CREATE(fichnom, NF_CLOBBER, nid)
142         ! Define the 'Time' dimension
143         ierr = nf_def_dim(nid,"Time",NF_UNLIMITED,idim)
144         ! Define the 'Time' variable
145#ifdef NC_DOUBLE
146         ierr = NF_DEF_VAR (nid, "Time", NF_DOUBLE, 1, idim,varid)
147#else
148         ierr = NF_DEF_VAR (nid, "Time", NF_FLOAT, 1, idim,varid)
149#endif
150         ! Add a long_name attribute
151         ierr = NF_PUT_ATT_TEXT (nid, varid, "long_name",
152     .          4,"Time")
153         ! Add a units attribute
154         ierr = NF_PUT_ATT_TEXT(nid, varid,'units',29,
155     .          "days since 0000-00-0 00:00:00")
156         ! Switch out of NetCDF Define mode
157         ierr = NF_ENDDEF(nid)
158
159         ! Build area()
160         IF (klon_glo>1) THEN
161          do i=1,nbp_lon+1 ! poles
162           ! divide at the poles by nbp_lon
163           area(i,1)=areafi_glo(1)/nbp_lon
164           area(i,nbp_lat)=areafi_glo(klon_glo)/nbp_lon
165          enddo
166          do j=2,nbp_lat-1
167           ig0= 1+(j-2)*nbp_lon
168           do i=1,nbp_lon
169              area(i,j)=areafi_glo(ig0+i)
170           enddo
171           ! handle redundant point in longitude
172           area(nbp_lon+1,j)=area(1,j)
173          enddo
174         ENDIF
175
176         ! write "header" of file (longitudes, latitudes, area, ...)
177         IF (klon_glo>1) THEN ! general 3D case
178           call iniwrite_specIR(nid,day_ini,area,nbp_lon+1,nbp_lat)
179         ELSE
180           call iniwrite_specIR(nid,day_ini,areafi_glo(1),1,1)
181         ENDIF
[4027]182         ! Close the NetCDF file
183               ierr= NF_CLOSE(nid)
[3184]184         endif ! of if (is_master)
185
186         zitau = -1 ! initialize zitau
187      endif ! if (firstnom.eq.'1234567890')
188
189! Increment time index 'zitau' if it is the "firstcall" (at given time level)
190! to writediagfi
191!------------------------------------------------------------------------
192      if (nom.eq.firstnom) then
[3749]193          zitau = zitau + 1
[3184]194      end if
195
196!--------------------------------------------------------
197! Write the variables to output file if it's time to do so
198!--------------------------------------------------------
199
[3749]200      if ( MOD(zitau+1,isample) .eq.0.) then
[3184]201
[4027]202        if (is_master) then
203                ! Open the NetCDF file
204                ierr = NF_OPEN(fichnom,NF_WRITE,nid)
205              endif
206
[3184]207! Compute/write/extend 'Time' coordinate (date given in days)
208! (done every "first call" (at given time level) to writediagfi)
209! Note: date is incremented as 1 step ahead of physics time
210!       (like the 'histoire' outputs)
211!--------------------------------------------------------
212
213        if (nom.eq.firstnom) then
214
215        ! We have identified a "first call" (at given date)
216           ntime=ntime+1 ! increment # of stored time steps
217           ! compute corresponding date (in days and fractions thereof)
[3749]218           date= float (zitau +1)*(dtphys/daysec)
[3184]219
220           if (is_master) then
221             ! Get NetCDF ID of 'Time' variable
222             ierr= NF_INQ_VARID(nid,"Time",varid)
223
224             ! Write (append) the new date to the 'Time' array
225#ifdef NC_DOUBLE
226             ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
227#else
228             ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
229#endif
230             if (ierr.ne.NF_NOERR) then
231              write(*,*) "***** PUT_VAR matter in writediagspec_nc"
232              write(*,*) "***** with time"
[3749]233              write(*,*) 'ierr=', ierr
[3184]234c             call abort
235             endif
236
237             write(6,*)'WRITEDIAGSPECIR: date= ', date
238           endif ! of if (is_master)
239        end if ! of if (nom.eq.firstnom)
240
241
[3749]242
[3184]243!Case of a 3D variable
244!---------------------
245        if (dimpx.eq.3) then
246
247!         A. Recast (copy) variable from physics grid to dynamics grid
248#ifdef CPP_PARA
249  ! gather field on a "global" (without redundant longitude) array
250          call Gather(px,dx3_glop)
251!$OMP MASTER
252          if (is_mpi_root) then
253            call Grid1Dto2D_glo(dx3_glop,dx3_glo)
254            ! copy dx3_glo() to dx3(:) and add redundant longitude
255            dx3(1:nbp_lon,:,:)=dx3_glo(1:nbp_lon,:,:)
256            dx3(nbp_lon+1,:,:)=dx3(1,:,:)
257          endif
258!$OMP END MASTER
259!$OMP BARRIER
260#else
261          IF (klon_glo>1) THEN ! General case
262           DO l=1,L_NSPECTI
263             DO i=1,nbp_lon+1
264                dx3(i,1,l)=px(1,l)
265                dx3(i,nbp_lat,l)=px(ngrid,l)
266             ENDDO
267             DO j=2,nbp_lat-1
268                ig0= 1+(j-2)*nbp_lon
269                DO i=1,nbp_lon
270                   dx3(i,j,l)=px(ig0+i,l)
271                ENDDO
272                dx3(nbp_lon+1,j,l)=dx3(1,j,l)
273             ENDDO
274           ENDDO
275          ELSE ! 1D model case
276            dx3_1d(1,1:L_NSPECTI)=px(1,1:L_NSPECTI)
277          ENDIF
278#endif
279
280!         B. Write (append) the variable to the NetCDF file
281          if (is_master) then
282
283! name of the variable
284           ierr= NF_INQ_VARID(nid,nom,varid)
285           if (ierr /= NF_NOERR) then
286! corresponding dimensions
287              ierr= NF_INQ_DIMID(nid,"longitude",id(1))
288              ierr= NF_INQ_DIMID(nid,"latitude",id(2))
289              ierr= NF_INQ_DIMID(nid,"IR_Wavenumber",id(3))
290              ierr= NF_INQ_DIMID(nid,"Time",id(4))
291
292! Create the variable if it doesn't exist yet
293
294              write (*,*) "=========================="
295              write (*,*) "DIAGSPECIR: creating variable ",nom
296              call def_var(nid,nom,titre,unite,4,id,varid,ierr)
297
298           endif
299
300           corner(1)=1
301           corner(2)=1
302           corner(3)=1
303           corner(4)=ntime
304
305           IF (klon_glo==1) THEN
306             edges(1)=1
307           ELSE
308             edges(1)=nbp_lon+1
309           ENDIF
310           edges(2)=nbp_lat
311           edges(3)=L_NSPECTI
312           edges(4)=1
313#ifdef NC_DOUBLE
314           IF (klon_glo>1) THEN ! General case
315             ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3)
316           ELSE
317             ierr= NF_PUT_VARA_DOUBLE(nid,varid,corner,edges,dx3_1d)
318           ENDIF
319#else
320           IF (klon_glo>1) THEN ! General case
321             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3)
322           ELSE
323             ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,dx3_1d)
324           ENDIF
325#endif
326
327           if (ierr.ne.NF_NOERR) then
328              write(*,*) "***** PUT_VAR problem in writediagspec"
329              write(*,*) "***** with ",nom
330              write(*,*) 'ierr=', ierr
331             call abort
[3749]332           endif
[3184]333
334          endif ! of if (is_master)
335
336        endif ! of if (dimpx.eq.3)
337
[4027]338        ! Close the NetCDF file
339              if (is_master) then
340                ierr= NF_CLOSE(nid)
341              endif
342
[3749]343      endif ! of if ( MOD(zitau+1,isample) .eq.0.)
[3184]344
345      end
Note: See TracBrowser for help on using the repository browser.