source: trunk/LMDZ.GENERIC/libf/phystd/writediagsoil.F90 @ 3817

Last change on this file since 3817 was 3725, checked in by emillour, 3 months ago

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