source: trunk/LMDZ.GENERIC/libf/aeronostd/writediagspecUV.F @ 3529

Last change on this file since 3529 was 3309, checked in by yjaziri, 7 months ago

GENERIC PCM:

  • Cosmetic + clarifying some variables and comments in chemistry
  • add controle variable for actinique UV flux in photochemistry and output surface UV flux in diagspecUV.nc

YJ

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