regrid_sfc  1.13.0
regridStates.F90
Go to the documentation of this file.
1 
4 
8 
9  program regridstates
10 
11  use mpi_f08
12  use esmf
13 
14  use grids_io, only : setup_grid, &
15  write_from_fields, &
16  read_into_fields, &
17  n_tiles, &
19 
20  use utilities, only : error_handler
21 
22  implicit none
23 
24  integer, parameter :: max_vars = 10
25 
26  ! namelist inputs
27  character(len=15) :: variable_list(max_vars)
28  character(len=2) :: time_list(9)
29  integer :: n_vars, n_tims, extrap_levs
30  real(esmf_kind_r8) :: missing_value ! value given to unmapped cells in the output grid
31 
32  type(grid_setup_type) :: grid_setup_in, grid_setup_out
33 
34  integer :: ierr, localpet, npets
35  integer :: v, t, srcterm
36 
37  character(100) :: fname_time
38 
39  type(esmf_vm) :: vm
40  type(esmf_grid) :: grid_in, grid_out
41  type(esmf_field), allocatable :: fields_in(:,:)
42  type(esmf_field), allocatable :: fields_out(:,:)
43  type(esmf_routehandle) :: regrid_route
44  real(esmf_kind_r8), pointer :: ptr_out(:,:)
45 
46  integer :: ut
47 
48  real :: t1, t2, t3, t4
49 
50  ! see README for details of namelist variables.
51  namelist /config/ n_vars, n_tims, time_list, variable_list, missing_value, extrap_levs
52 
53 ! INITIALIZE
54 !-------------------------------------------------------------------------
55 
56  call cpu_time(t1)
57 
58  call mpi_init(ierr)
59 
60  call esmf_initialize(rc=ierr)
61  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
62  call error_handler("INITIALIZING ESMF", ierr)
63 
64  call esmf_vmgetglobal(vm, rc=ierr)
65  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
66  call error_handler("IN VMGetGlobal", ierr)
67 
68  call esmf_vmget(vm, localpet=localpet, petcount=npets, rc=ierr)
69  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
70  call error_handler("IN VMGet", ierr)
71 
72 !-------------------------------------------------------------------------
73 ! RUN
74 !-------------------------------------------------------------------------
75 
76  print*,'** pets: local, total: ',localpet, npets
77 
78  ! checks
79 
80  if (mod(npets,n_tiles) /= 0) then
81  call error_handler("must run with a task count that is a multiple of 6", 1)
82  endif
83 
84 !------------------------
85 ! read in namelist
86 
87  ! defaults
88  missing_value=-999.
89  extrap_levs=2
90  n_tims=1
91 
92  open(newunit=ut, file='regrid.nml', iostat=ierr)
93  if (ierr /= 0) call error_handler("OPENING regrid NAMELIST.", ierr)
94  read(ut, nml=config, iostat=ierr)
95  if (ierr /= 0) call error_handler("OPENING config NAMELIST.", ierr)
96  call readin_setup(ut,"input",grid_setup_in)
97  call readin_setup(ut,"output",grid_setup_out)
98  close (ut)
99 
100 
101 !------------------------
102 ! Create esmf grid objects for input and output grids, and add land masks
103 
104 ! TO DO - can we make the number of tasks more flexible for fv3
105 
106  if (localpet==0) print*,'** Setting up grids'
107  call setup_grid(localpet, npets, grid_setup_in, grid_in )
108 
109  call setup_grid(localpet, npets, grid_setup_out, grid_out )
110 
111 !------------------------
112 ! Create input and output fields
113 
114  if (localpet==0) print*,'** Creating/Reading fields'
115 
116 ! input
117  allocate(fields_in(n_tims,n_vars))
118 
119  do t = 1, n_tims
120  do v = 1, n_vars
121 
122  fields_in(t,v) = esmf_fieldcreate(grid_in, &
123  typekind=esmf_typekind_r8, &
124  staggerloc=esmf_staggerloc_center, &
125  name="input for regridding", &
126  rc=ierr)
127 
128  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
129  call error_handler("in FieldCreate "//trim(variable_list(v)), ierr)
130  end do
131  end do
132 
133 ! output
134  allocate(fields_out(n_tims,n_vars))
135 
136  do t = 1, n_tims
137  do v = 1, n_vars
138 
139  fields_out(t,v) = esmf_fieldcreate(grid_out, &
140  typekind=esmf_typekind_r8, &
141  staggerloc=esmf_staggerloc_center, &
142  name="output of regridding", &
143  rc=ierr)
144  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
145  call error_handler("in FieldCreate, field_out", ierr)
146 
147 
148  ! set the default output value (for non-mapped cells)
149  call esmf_fieldget(fields_out(t,v), &
150  farrayptr=ptr_out, &
151  rc=ierr)
152  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
153  call error_handler("IN FieldGet", ierr)
154 
155  ptr_out=missing_value
156 
157  enddo
158  enddo
159 
160 !------------------------
161 ! read data into input fields
162 
163  do t = 1, n_tims
164 
165  if (n_tims>1) then
166  fname_time = trim(grid_setup_in%fname)//"."//time_list(t)
167  else
168  fname_time = trim(grid_setup_in%fname)
169  endif
170  write(6,*) 'reading into ', trim(fname_time)
171  call read_into_fields(localpet, grid_setup_in%ires, grid_setup_in%jres, &
172  trim(fname_time), trim(grid_setup_in%dir), &
173  grid_setup_in, n_vars, variable_list(1:n_vars), fields_in(t,:))
174  enddo
175 
176  call cpu_time(t2)
177 !------------------------
178 ! regrid the input fields to the output grid
179 
180  if (localpet==0) print*,'** Performing regridding'
181 
182  srcterm=1
183  ! get regriding route for a field (only uses the grid info in the field)
184  ! to turn off masking, remove [src/dstMaskVales] argumemnts
185  call esmf_fieldregridstore(srcfield=fields_in(1,1), srcmaskvalues=(/0/), &
186  dstfield=fields_out(1,1), dstmaskvalues=(/0/), &
187  ! allow unmapped grid cells, without returning error
188  unmappedaction=esmf_unmappedaction_ignore, &
189  polemethod=esmf_polemethod_allavg, &
190  ! fill un-mapped grid cells with a neighbour
191  extrapmethod=esmf_extrapmethod_creep, &
192  ! number of "levels" of neighbours to search for a value
193  extrapnumlevels=extrap_levs, &
194  ! needed for reproducibility
195  ! (combined with ESMF_TERMORDER_SRCSEQ below)
196  srctermprocessing=srcterm, &
197  routehandle=regrid_route, &
198  ! use bilinear interp (slightly better results than PATCH)
199  regridmethod=esmf_regridmethod_bilinear, rc=ierr)
200  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
201  call error_handler("IN FieldRegridStore", ierr)
202 
203 ! do the re-gridding
204 
205  call cpu_time(t3)
206 
207  do t=1, n_tims
208  do v=1, n_vars
209  call esmf_fieldregrid(fields_in(t,v), &
210  fields_out(t,v), &
211  routehandle=regrid_route, &
212  zeroregion=esmf_region_select, & ! initialize output with missing_value
213  termorderflag=esmf_termorder_srcseq, rc=ierr)
214  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
215  call error_handler("IN FieldRegrid", ierr)
216  enddo
217  enddo
218 
219 ! TO-DO: terrain-correct temperatures (all layers?)
220 
221 ! write out fields on destination grid. All times into same file.
222 
223  if (localpet==0) print*,'** Writing out regridded fields'
224 
225  call write_from_fields(localpet, grid_setup_out%ires, grid_setup_out%jres, &
226  trim(grid_setup_out%fname), trim(grid_setup_out%dir), &
227  n_vars, n_tims, variable_list(1:n_vars), fields_out)
228 
229 
230 ! clean up
231 
232  call esmf_fieldregridrelease(routehandle=regrid_route, rc=ierr)
233  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
234  call error_handler("IN FieldRegridRelease", ierr)
235 
236  do t = 1, n_tims
237  do v = 1, n_vars
238  call esmf_fielddestroy(fields_in(t,v),rc=ierr)
239  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
240  call error_handler("DESTROYING FIELD", ierr)
241 
242  call esmf_fielddestroy(fields_out(t,v),rc=ierr)
243  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
244  call error_handler("DESTROYING FIELD", ierr)
245  enddo
246  enddo
247 
248  call esmf_griddestroy(grid_in,rc=ierr)
249  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
250  call error_handler("DESTROYING GRID", ierr)
251 
252  call esmf_griddestroy(grid_out,rc=ierr)
253  if(esmf_logfounderror(rctocheck=ierr,msg=esmf_logerr_passthru,line=__line__,file=__file__)) &
254  call error_handler("DESTROYING GRID", ierr)
255 
256 !-------------------------------------------------------------------------
257 ! FINALIZE
258 !-------------------------------------------------------------------------
259 
260  call esmf_finalize(endflag=esmf_end_keepmpi, rc=ierr)
261  call mpi_finalize(ierr)
262 
263  call cpu_time(t4)
264  if (localpet==0) print*, '** time in tile2tile', t4 - t1
265  if (localpet==0) print*, '** time in RegridStore', t3 - t2
266 
267  print*,"** DONE.", localpet
268 
269  end program regridstates
subroutine readin_setup(unt, namel, grid_setup)
Subroutine to read in namelists, and convert values into setupgrid.
program regridstates
Program to re-grid a list of FV3 variables.
Definition: regridStates.F90:9