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

Last change on this file since 3893 was 3893, checked in by gmilcareck, 4 months ago

Remove all "call abort" and "stop" statement in LMDZ.GENERIC and replacing them by call abort_physic().

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