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

Last change on this file since 1834 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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