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

Last change on this file since 1242 was 1130, checked in by emillour, 11 years ago

Mars GCM:
Series of changes to enable running in parallel (using LMDZ.COMMON dynamics);
Current LMDZ.MARS can still notheless be compiled and run in serial mode
"as previously".
Summary of main changes:

  • Main programs (newstart, start2archive, xvik) that used to be in dyn3d have been moved to phymars.
  • dyn3d/control.h is now module control_mod.F90
  • rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallel case)
  • created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the min and max of a field over the whole planet.

EM

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