source: trunk/LMDZ.MARS/libf/phymars/writediagsoil.F90

Last change on this file was 3369, checked in by emillour, 6 months ago

Mars PCM:
Change the way the rate of outputs for diagfi.nc files is specified:
IMPORTANT: Specifying "ecritphy" no longer possible and will trigger an error.
Use "outputs_per_sol" to specify output rate instead.
This should makes things (hopefully) clearer for users and also better
enforces a cleaner and clearer separation between dynamics and physics.
EM

File size: 13.0 KB
Line 
1module writediagsoil_mod
2
3implicit none
4
5logical,save :: diagsoil ! global flag to trigger generating a diagsoil.nc
6                         ! file or not. Initialized in conf_phys()
7
8contains
9
10subroutine writediagsoil(ngrid,name,title,units,dimpx,px)
11
12! Write variable 'name' to NetCDF file 'diagsoil.nc'.
13! The variable may be 3D (lon,lat,depth) subterranean field,
14! a 2D (lon,lat) surface field, or a simple scalar (0D variable).
15!
16! Calls to 'writediagsoil' can originate from anywhere in the program;
17! An initialisation of variable 'name' is done if it is the first time
18! that this routine is called with given 'name'; otherwise data is appended
19! (yielding the sought time series of the variable)
20
21! Modifs: Aug.2010 Ehouarn: enforce outputs to be real*4
22
23use comsoil_h, only: mlayer, nsoilmx, inertiedat
24use geometry_mod, only: cell_area
25use time_phylmdz_mod, only: steps_per_sol, outputs_per_sol
26use mod_phys_lmdz_para, only: is_mpi_root, is_master, gather
27use mod_grid_phy_lmdz, only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat
28use mod_grid_phy_lmdz, only: grid_type, unstructured
29use iniwritesoil_mod, only: iniwritesoil
30
31implicit none
32
33include"netcdf.inc"
34
35! Arguments:
36integer,intent(in) :: ngrid ! number of (horizontal) points of physics grid
37! i.e. ngrid = 2+(jjm-1)*iim - 1/jjm
38character(len=*),intent(in) :: name ! 'name' of the variable
39character(len=*),intent(in) :: title ! 'long_name' attribute of the variable
40character(len=*),intent(in) :: units ! 'units' attribute of the variable
41integer,intent(in) :: dimpx ! dimension of the variable (3,2 or 0)
42real,dimension(ngrid,nsoilmx),intent(in) :: px ! variable
43
44! Local variables:
45real*4,dimension(nbp_lon+1,nbp_lat,nsoilmx) :: data3 ! to store 3D data
46real*4,dimension(nbp_lon+1,nbp_lat) :: data2 ! to store 2D data
47real*4 :: data0 ! to store 0D data
48real*4 :: data3_1d(1,nsoilmx) ! to store a profile in 1D model
49real*4 :: data2_1d ! to store surface value with 1D model
50integer :: i,j,l ! for loops
51integer :: ig0
52
53real*4,save :: date ! time counter (in elapsed days)
54
55real :: inertia((nbp_lon+1),nbp_lat,nsoilmx)
56real :: area((nbp_lon+1),nbp_lat)
57
58real :: inertiafi_glo(klon_glo,nsoilmx)
59real :: areafi_glo(klon_glo)
60
61integer,save :: isample ! sample rate at which data is to be written to output
62integer,save :: ntime=0 ! counter to internally store time steps
63character(len=20),save :: firstname="1234567890"
64integer,save :: zitau=0
65!$OMP THREADPRIVATE(date,isample,ntime,firstname,zitau)
66
67character(len=30) :: filename="diagsoil.nc"
68
69! NetCDF stuff:
70integer :: nid ! NetCDF output file ID
71integer :: varid ! NetCDF ID of a variable
72integer :: ierr ! NetCDF routines return code
73integer,dimension(4) :: id ! NetCDF IDs of the dimensions of the variable
74integer,dimension(4) :: edges,corners
75
76#ifdef CPP_PARA
77! Added to work in parallel mode
78real dx3_glop(klon_glo,nsoilmx)
79real dx3_glo(nbp_lon,nbp_lat,nsoilmx) ! to store a global 3D data set
80real dx2_glop(klon_glo)
81real dx2_glo(nbp_lon,nbp_lat)     ! to store a global 2D (surface) data set
82real px2(ngrid)
83#endif
84
85! 0. Do we ouput a diagsoil.nc file? If not just bail out now.
86if(.not.diagsoil) return
87
88! additional check: one can only output diagsoil.nc files
89! in lon-lat case (or 1D)
90if (grid_type==unstructured) then
91  write(*,*) "writediagsoil: Error !!!"
92  write(*,*) "diagsoil.nc outputs not possible on unstructured grids!!"
93  call abort_physic("writediagsoil","impossible on unstructured grid",1)
94endif
95
96! 1. Initialization step
97if (firstname.eq."1234567890") then
98  ! Store 'name' as 'firstname'
99  firstname=name
100  ! From now on, if 'name'.eq.'firstname', then it is a new time cycle
101
102  ! just to be sure, check that firstnom is large enough to hold nom
103  if (len_trim(firstname).lt.len_trim(name)) then
104    write(*,*) "writediagsoil: Error !!!"
105    write(*,*) "   firstname string not long enough!!"
106    write(*,*) "   increase its size to at least ",len_trim(name)
107    call abort_physic("writediagsoil","firstname too short",1)
108  endif
109 
110  ! Set output sample rate
111  isample=steps_per_sol/outputs_per_sol ! same as for diagfi outputs
112  ! Note ecritphy is known from control.h
113 
114  ! Create output NetCDF file
115  if (is_master) then
116   ierr=NF_CREATE(filename,NF_CLOBBER,nid)
117   if (ierr.ne.NF_NOERR) then
118    write(*,*)'writediagsoil: Error, failed creating file '//trim(filename)
119    call abort_physic("writediagsoil","failed creating"//trim(filename),1)
120   endif
121  endif
122
123#ifdef CPP_PARA
124   ! Gather inertiedat() soil thermal inertia on physics grid
125   call Gather(inertiedat,inertiafi_glo)
126   ! Gather cell_area() mesh area on physics grid
127   call Gather(cell_area,areafi_glo)
128#else
129         inertiafi_glo(:,:)=inertiedat(:,:)
130         areafi_glo(:)=cell_area(:)
131#endif
132
133  if (is_master) then
134   ! build inertia() and area()
135   if (klon_glo>1) then
136    do i=1,nbp_lon+1 ! poles
137     inertia(i,1,1:nsoilmx)=inertiafi_glo(1,1:nsoilmx)
138     inertia(i,nbp_lat,1:nsoilmx)=inertiafi_glo(klon_glo,1:nsoilmx)
139     ! for area, divide at the poles by nbp_lon
140     area(i,1)=areafi_glo(1)/nbp_lon
141     area(i,nbp_lat)=areafi_glo(klon_glo)/nbp_lon
142    enddo
143    do j=2,nbp_lat-1
144     ig0= 1+(j-2)*nbp_lon
145     do i=1,nbp_lon
146        inertia(i,j,1:nsoilmx)=inertiafi_glo(ig0+i,1:nsoilmx)
147        area(i,j)=areafi_glo(ig0+i)
148     enddo
149     ! handle redundant point in longitude
150     inertia(nbp_lon+1,j,1:nsoilmx)=inertia(1,j,1:nsoilmx)
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 iniwritesoil(nid,ngrid,inertia,area,nbp_lon+1,nbp_lat,nsoilmx,mlayer)
158   else ! 1D model
159     call iniwritesoil(nid,ngrid,inertiafi_glo(1,:),areafi_glo(1),1,1,nsoilmx,mlayer)
160   endif
161
162  endif ! of if (is_master)
163 
164  ! set zitau to -1 to be compatible with zitau incrementation step below
165  zitau=-1
166 
167else
168  ! If not an initialization call, simply open the NetCDF file
169  if (is_master) then
170   ierr=NF_OPEN(filename,NF_WRITE,nid)
171  endif
172endif ! of if (firstname.eq."1234567890")
173
174! 2. Increment local time counter, if necessary
175if (name.eq.firstname) then
176  ! if we run across 'firstname', then it is a new time step
177  zitau=zitau+1
178endif
179
180! 3. Write data, if the time index matches the sample rate
181if (mod(zitau+1,isample).eq.0) then
182
183! 3.1 If first call at this date, update 'time' variable
184  if (name.eq.firstname) then
185    ntime=ntime+1
186    date=float(zitau+1)/float(steps_per_sol)
187   
188    if (is_master) then
189     ! Get NetCDF ID for "time"
190     ierr=NF_INQ_VARID(nid,"time",varid)
191     ! Add the current value of date to the "time" array
192!#ifdef NC_DOUBLE
193!     ierr=NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
194!#else
195     ierr=NF_PUT_VARA_REAL(nid,varid,[ntime],[1],[date])
196!#endif
197     if (ierr.ne.NF_NOERR) then
198      write(*,*)"writediagsoil: Failed writing date to time variable"
199      call abort_physic("writediagsoil","failed writing time",1)
200     endif
201    endif ! of if (is_master)
202  endif ! of if (name.eq.firstname)
203
204! 3.2 Write the variable to the NetCDF file
205if (dimpx.eq.3) then ! Case of a 3D variable
206  ! A. Recast data along 'dynamics' grid
207  if (klon_glo>1) then ! General case
208#ifdef CPP_PARA
209  ! gather field on a "global" (without redundant longitude) array
210  call Gather(px,dx3_glop)
211!$OMP MASTER
212  if (is_mpi_root) then
213    call Grid1Dto2D_glo(dx3_glop,dx3_glo)
214    ! copy dx3_glo() to dx3(:) and add redundant longitude
215    data3(1:nbp_lon,:,:)=dx3_glo(1:nbp_lon,:,:)
216    data3(nbp_lon+1,:,:)=data3(1,:,:)
217  endif
218!$OMP END MASTER
219!$OMP BARRIER
220#else
221   do l=1,nsoilmx
222    ! handle the poles
223    do i=1,nbp_lon+1
224      data3(i,1,l)=px(1,l)
225      data3(i,nbp_lat,l)=px(ngrid,l)
226    enddo
227    ! rest of the grid
228    do j=2,nbp_lat-1
229      ig0=1+(j-2)*nbp_lon
230      do i=1,nbp_lon
231        data3(i,j,l)=px(ig0+i,l)
232      enddo
233      data3(nbp_lon+1,j,l)=data3(1,j,l) ! extra (modulo) longitude
234    enddo
235   enddo
236#endif
237  else ! 1D model case
238   data3_1d(1,1:nsoilmx)=px(1,1:nsoilmx)
239  endif
240 
241  ! B. Write (append) the variable to the NetCDF file
242  if (is_master) then
243  ! B.1. Get the ID of the variable
244  ierr=NF_INQ_VARID(nid,name,varid)
245  if (ierr.ne.NF_NOERR) then
246    ! If we failed geting the variable's ID, we assume it is because
247    ! the variable doesn't exist yet and must be created.
248    ! Start by obtaining corresponding dimensions IDs
249    ierr=NF_INQ_DIMID(nid,"longitude",id(1))
250    ierr=NF_INQ_DIMID(nid,"latitude",id(2))
251    ierr=NF_INQ_DIMID(nid,"depth",id(3))
252    ierr=NF_INQ_DIMID(nid,"time",id(4))
253    ! Tell the world about it
254    write(*,*) "====================="
255    write(*,*) "writediagsoil: creating variable "//trim(name)
256    call def_var(nid,name,title,units,4,id,varid,ierr)
257  endif ! of if (ierr.ne.NF_NOERR)
258 
259  ! B.2. Prepare things to be able to write/append the variable
260  corners(1)=1
261  corners(2)=1
262  corners(3)=1
263  corners(4)=ntime
264 
265  if (klon_glo==1) then
266    edges(1)=1
267  else
268    edges(1)=nbp_lon+1
269  endif
270  edges(2)=nbp_lat
271  edges(3)=nsoilmx
272  edges(4)=1
273 
274  ! B.3. Write the slab of data
275!#ifdef NC_DOUBLE
276!  ierr=NF_PUT_VARA_DOUBLE(nid,varid,corners,edges,data3)
277!#else
278  if (klon_glo>1) then
279    ierr=NF_PUT_VARA_REAL(nid,varid,corners,edges,data3)
280  else
281    ierr=NF_PUT_VARA_REAL(nid,varid,corners,edges,data3_1d)
282  endif
283!#endif
284  if (ierr.ne.NF_NOERR) then
285    write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
286               " to file "//trim(filename)//" at time",date
287  endif
288  endif ! of if (is_master)
289
290elseif (dimpx.eq.2) then ! Case of a 2D variable
291
292  ! A. Recast data along 'dynamics' grid
293  if (klon_glo>1) then ! General case
294#ifdef CPP_PARA
295  ! gather field on a "global" (without redundant longitude) array
296  px2(:)=px(:,1)
297  call Gather(px2,dx2_glop)
298!$OMP MASTER
299  if (is_mpi_root) then
300    call Grid1Dto2D_glo(dx2_glop,dx2_glo)
301    ! copy dx3_glo() to dx3(:) and add redundant longitude
302    data2(1:nbp_lon,:)=dx2_glo(1:nbp_lon,:)
303    data2(nbp_lon+1,:)=data2(1,:)
304  endif
305!$OMP END MASTER
306!$OMP BARRIER
307#else
308    ! handle the poles
309    do i=1,nbp_lon+1
310      data2(i,1)=px(1,1)
311      data2(i,nbp_lat)=px(ngrid,1)
312    enddo
313    ! rest of the grid
314    do j=2,nbp_lat-1
315      ig0=1+(j-2)*nbp_lon
316      do i=1,nbp_lon
317        data2(i,j)=px(ig0+i,1)
318      enddo
319      data2(nbp_lon+1,j)=data2(1,j) ! extra (modulo) longitude
320    enddo
321#endif
322  else ! 1D model case
323    data2_1d=px(1,1)
324  endif
325
326  ! B. Write (append) the variable to the NetCDF file
327  if (is_master) then
328  ! B.1. Get the ID of the variable
329  ierr=NF_INQ_VARID(nid,name,varid)
330  if (ierr.ne.NF_NOERR) then
331    ! If we failed geting the variable's ID, we assume it is because
332    ! the variable doesn't exist yet and must be created.
333    ! Start by obtaining corresponding dimensions IDs
334    ierr=NF_INQ_DIMID(nid,"longitude",id(1))
335    ierr=NF_INQ_DIMID(nid,"latitude",id(2))
336    ierr=NF_INQ_DIMID(nid,"time",id(3))
337    ! Tell the world about it
338    write(*,*) "====================="
339    write(*,*) "writediagsoil: creating variable "//trim(name)
340    call def_var(nid,name,title,units,3,id,varid,ierr)
341  endif ! of if (ierr.ne.NF_NOERR)
342
343  ! B.2. Prepare things to be able to write/append the variable
344  corners(1)=1
345  corners(2)=1
346  corners(3)=ntime
347 
348  if (klon_glo==1) then
349    edges(1)=1
350  else
351    edges(1)=nbp_lon+1
352  endif
353  edges(2)=nbp_lat
354  edges(3)=1
355 
356  ! B.3. Write the slab of data
357!#ifdef NC_DOUBLE
358!  ierr=NF_PUT_VARA_DOUBLE(nid,varid,corners,edges,data2)
359!#else
360  if (klon_glo>1) then ! General case
361    ierr=NF_PUT_VARA_REAL(nid,varid,corners,edges,data2)
362  else
363    ierr=NF_PUT_VARA_REAL(nid,varid,corners,edges,[data2_1d])
364  endif
365!#endif
366  if (ierr.ne.NF_NOERR) then
367    write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
368               " to file "//trim(filename)//" at time",date
369  endif
370  endif ! of if (is_master)
371
372elseif (dimpx.eq.0) then ! Case of a 0D variable
373#ifdef CPP_PARA
374  write(*,*) "writediagsoil: dimps==0 case not implemented in // mode!!"
375  call abort_physic("writediagsoil","dimps==0 not implemented",1)
376#endif
377  ! A. Copy data value
378  data0=px(1,1)
379
380  ! B. Write (append) the variable to the NetCDF file
381  ! B.1. Get the ID of the variable
382  ierr=NF_INQ_VARID(nid,name,varid)
383  if (ierr.ne.NF_NOERR) then
384    ! If we failed geting the variable's ID, we assume it is because
385    ! the variable doesn't exist yet and must be created.
386    ! Start by obtaining corresponding dimensions IDs
387    ierr=NF_INQ_DIMID(nid,"time",id(1))
388    ! Tell the world about it
389    write(*,*) "====================="
390    write(*,*) "writediagsoil: creating variable "//trim(name)
391    call def_var(nid,name,title,units,1,id,varid,ierr)
392  endif ! of if (ierr.ne.NF_NOERR)
393
394  ! B.2. Prepare things to be able to write/append the variable
395  corners(1)=ntime
396 
397  edges(1)=1
398
399  ! B.3. Write the data
400!#ifdef NC_DOUBLE
401!  ierr=NF_PUT_VARA_DOUBLE(nid,varid,corners,edges,data0)
402!#else
403  ierr=NF_PUT_VARA_REAL(nid,varid,corners,edges,[data0])
404!#endif
405  if (ierr.ne.NF_NOERR) then
406    write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
407               " to file "//trim(filename)//" at time",date
408  endif
409
410endif ! of if (dimpx.eq.3) elseif (dimpx.eq.2) ...
411endif ! of if (mod(zitau+1,isample).eq.0)
412
413! 4. Close the NetCDF file
414if (is_master) then
415  ierr=NF_CLOSE(nid)
416endif
417
418end subroutine writediagsoil
419
420end module writediagsoil_mod
Note: See TracBrowser for help on using the repository browser.