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

Last change on this file since 3026 was 2916, checked in by emillour, 22 months ago

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