source: trunk/LMDZ.PLUTO/libf/phypluto/writediagsoil.F90 @ 3736

Last change on this file since 3736 was 3698, checked in by emillour, 9 months ago

Pluto PCM:
Some fixes to enable runnnig with dynamico:

  • add "strictboundcorrk" flag in callcorrk_pluto to enable running even if outside of kmatrix temperatures (when strictboundcorrk=.true.)
  • add premature exiting of writediagsoil if not with lon-lat grid
  • while at it, turned surfprop.F90 into a module
  • in physiq, enforce the possibility to output subsurface-related field in most cases, not only when "fast=.true."
  • adapt reference xml files: subsurface quantities need to be defined on a dedicated grid, otherwise XIOS will generate misleading garbage values. Updated files are put in "deftank/dynamico" for now.

EM

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