orog_mask_tools  1.4.0
 All Data Structures Files Functions Variables
inland.F90
Go to the documentation of this file.
1 
4 
9 PROGRAM inland_mask
10  USE cs_nb
11  IMPLICIT NONE
12 
13  INTEGER :: tile, i, j
14  TYPE(nb_gp_idx) :: nbs
15 
16  REAL, ALLOCATABLE :: inland(:,:,:)
17  REAL, ALLOCATABLE :: land_frac(:,:,:)
18  INTEGER :: i_ctr, j_ctr, tile_beg, tile_end
19  INTEGER :: cs_res, x_res, y_res
20  CHARACTER(len=32) :: arg
21  INTEGER :: stat
22  INTEGER :: max_rd
23  REAL :: cutoff
24  CHARACTER(len=1) :: reg
25 
26  LOGICAL, ALLOCATABLE :: done(:,:,:)
27 
28  CALL getarg(0, arg) ! get the program name
29  IF (iargc() /= 3 .AND. iargc() /= 4) THEN
30  print*, 'Usage: '
31  print*, trim(arg), ' [cres(48,96, ...)][nonland cutoff][max recursive depth][regional(r),global(g)]'
32  stop
33  ENDIF
34 
35  CALL getarg(1, arg)
36  READ(arg,*,iostat=stat) cs_res
37  CALL getarg(2, arg)
38  READ(arg,*,iostat=stat) cutoff
39  CALL getarg(3, arg)
40  READ(arg,*,iostat=stat) max_rd
41  CALL getarg(4, reg)
42 
43  IF (reg /= 'r') THEN
44  tile_beg = 1; tile_end = 6
45 ! read in orography data (land_frac)
46  CALL read_orog(cs_res)
47 
48 ! init inter-panel neighbor index
49  CALL idx_init(cs_res)
50 
51 ! create a inland mask
52  CALL mark_global_inland(cs_res)
53 
54 ! write back to the orography data files
55  CALL write_inland(cs_res)
56  ELSE
57 ! read in orography data (land_frac) for the SAR domain
58  CALL read_orog_reg(cs_res)
59 
60 ! init inter-panel neighbor index
61  CALL idx_init_reg(x_res, y_res)
62 
63 ! create a inland mask
64  CALL mark_inland_reg(cs_res)
65 
66 ! write back to the orography data files
67  CALL write_inland_reg(cs_res)
68  ENDIF
69 
70  CALL free_mem()
71 
72 CONTAINS
73 
79 SUBROUTINE mark_global_inland(cs_res)
80  INTEGER, INTENT(IN) :: cs_res
81 
82  ALLOCATE(done(cs_res,cs_res,6))
83  ALLOCATE(inland(cs_res,cs_res,6))
84  done = .false.
85  inland = 1.0
86  i_ctr = cs_res/2; j_ctr = cs_res/2
87 
88  CALL mark_global_inland_rec_d(i_ctr, j_ctr, 2, 0)
89 
90  DEALLOCATE(done)
91 
92 END SUBROUTINE mark_global_inland
93 
99 SUBROUTINE mark_inland_reg(cs_res)
100  INTEGER, INTENT(IN) :: cs_res
101  INTEGER :: i_seed, j_seed
102 
103  ALLOCATE(done(x_res,y_res,1))
104  ALLOCATE(inland(x_res,y_res,1))
105 
106  done = .false.
107  inland = 1.0
108 
109 ! set up three seeds, for the current domain
110  i_seed = 1; j_seed = y_res/2
111  CALL mark_regional_inland_rec_d(i_seed, j_seed, 1, 0)
112 
113  i_seed = x_res; j_seed = y_res/2
114  CALL mark_regional_inland_rec_d(i_seed, j_seed, 1, 0)
115 
116  i_seed = x_res/3; j_seed = 1
117  CALL mark_regional_inland_rec_d(i_seed, j_seed, 1, 0)
118 
119  DEALLOCATE(done)
120 
121 END SUBROUTINE mark_inland_reg
122 
131 RECURSIVE SUBROUTINE mark_global_inland_rec_d(i, j, t, rd)
132  INTEGER, INTENT(IN) :: i, j, t, rd
133 
134  TYPE(nb_gp_idx) :: nbs
135  INTEGER :: k, nrd
136 
137  IF (t == 0) RETURN
138 
139  IF (land_frac(i,j,t) <= 0.15) THEN
140  nrd = 1
141  ELSE
142  nrd = rd + 1
143  ENDIF
144 
145  IF (nrd > max_rd) RETURN
146 
147  IF (done(i,j,t)) RETURN
148  IF (land_frac(i,j,t) < cutoff) THEN
149  done(i,j,t) = .true.
150  inland(i,j,t) = 0.0
151  CALL neighbors(t, i, j, nbs)
152  ! recursively go through k neighbors
153  DO k = 1, 4
154  CALL mark_global_inland_rec_d(nbs%ijt(1,k),nbs%ijt(2,k),nbs%ijt(3,k),nrd)
155  ENDDO
156  ENDIF
157 
158 END SUBROUTINE mark_global_inland_rec_d
159 
168 RECURSIVE SUBROUTINE mark_regional_inland_rec_d(i, j, t, rd)
169  INTEGER, INTENT(IN) :: i, j, t, rd
170 
171  TYPE(nb_gp_idx) :: nbs
172  INTEGER :: k, nrd
173 
174  IF (t == 0) RETURN
175 
176  IF (land_frac(i,j,t) <= 0.15) THEN
177  nrd = 1
178  ELSE
179  nrd = rd + 1
180  ENDIF
181 
182  IF (nrd > max_rd) RETURN
183 
184  IF (done(i,j,t)) RETURN
185  IF (land_frac(i,j,t) < cutoff) THEN
186  done(i,j,t) = .true.
187  inland(i,j,t) = 0.0
188  CALL neighbors_reg(i, j, nbs)
189  ! recursively go through k neighbors
190  DO k = 1, 4
191  CALL mark_regional_inland_rec_d(nbs%ijt(1,k),nbs%ijt(2,k),nbs%ijt(3,k),nrd)
192  ENDDO
193  ENDIF
194 
195 END SUBROUTINE mark_regional_inland_rec_d
196 
202 SUBROUTINE read_orog(cs_res)
203  USE netcdf
204  INTEGER, INTENT(IN) :: cs_res
205 
206  INTEGER :: tile_sz, tile_num
207  INTEGER :: stat, ncid, varid
208  INTEGER :: land_frac_id, slmsk_id, geolon_id, geolat_id
209  CHARACTER(len=256) :: filename,string
210  CHARACTER(len=1) :: ich
211  CHARACTER(len=4) res_ch
212  CHARACTER(len=8) dimname
213 
214  INTEGER :: i, j
215  REAL, ALLOCATABLE :: var_tmp(:,:)
216 
217  ALLOCATE(var_tmp(cs_res,cs_res))
218  ALLOCATE(land_frac(cs_res,cs_res,6))
219 
220  WRITE(res_ch,'(I4)') cs_res
221  DO tile_num = tile_beg, tile_end
222  WRITE(ich, '(I1)') tile_num
223  filename = "oro.C" // trim(adjustl(res_ch)) // ".tile" // ich // ".nc"
224  print *,'Read, update, and write ',trim(filename)
225  stat = nf90_open(filename, nf90_nowrite, ncid)
226  CALL nc_opchk(stat, "nf90_open oro_data.nc")
227 
228 ! original orodata netcdf file uses (y, x) order, so we made change to match it.
229  stat = nf90_inq_varid(ncid, "land_frac", land_frac_id)
230  CALL nc_opchk(stat, "nf90_inq_varid: land_frac")
231  stat = nf90_get_var(ncid, land_frac_id, var_tmp, &
232  start = (/ 1, 1 /), count = (/ cs_res, cs_res /) )
233  CALL nc_opchk(stat, "nf90_get_var: land_frac")
234  land_frac(:,:,tile_num) = var_tmp(:,:)
235  stat = nf90_close(ncid)
236  CALL nc_opchk(stat, "nf90_close oro_data.nc")
237  ENDDO
238 
239  DEALLOCATE(var_tmp)
240 
241 END SUBROUTINE read_orog
242 
248 SUBROUTINE read_orog_reg(cs_res)
249  USE netcdf
250  INTEGER, INTENT(IN) :: cs_res
251 
252  INTEGER :: tile_num
253  INTEGER :: stat, ncid, x_dimid, y_dimid, varid
254  INTEGER :: land_frac_id, slmsk_id, geolon_id, geolat_id
255  CHARACTER(len=256) :: filename,string
256  CHARACTER(len=1) :: ich
257  CHARACTER(len=4) res_ch
258  CHARACTER(len=8) dimname
259 
260  INTEGER :: i, j
261  REAL, ALLOCATABLE :: var_tmp(:,:)
262 
263  WRITE(res_ch,'(I4)') cs_res
264  tile_num = 7
265  WRITE(ich, '(I1)') tile_num
266  filename = "oro.C" // trim(adjustl(res_ch)) // ".tile" // ich // ".nc"
267  print *,'Read, update, and write ',trim(filename)
268  stat = nf90_open(filename, nf90_nowrite, ncid)
269  CALL nc_opchk(stat, "nf90_open oro_data.nc")
270  stat = nf90_inq_dimid(ncid, "lon", x_dimid)
271  CALL nc_opchk(stat, "nf90_inq_dim: x")
272  stat = nf90_inq_dimid(ncid, "lat", y_dimid)
273  CALL nc_opchk(stat, "nf90_inq_dim: y")
274  stat = nf90_inquire_dimension(ncid,x_dimid,dimname,len=x_res)
275  CALL nc_opchk(stat,'nf90_inquire_dimension: lon')
276  stat = nf90_inquire_dimension(ncid,y_dimid,dimname,len=y_res)
277  CALL nc_opchk(stat,'nf90_inquire_dimension: lon')
278 
279 ! original orodata netcdf file uses (y, x) order, so we made change to match it.
280  ALLOCATE(var_tmp(x_res,y_res))
281  ALLOCATE(land_frac(x_res,y_res,1))
282  stat = nf90_inq_varid(ncid, "land_frac", land_frac_id)
283  CALL nc_opchk(stat, "nf90_inq_varid: land_frac")
284  stat = nf90_get_var(ncid, land_frac_id, var_tmp, &
285  start = (/ 1, 1 /), count = (/ x_res, y_res /) )
286  CALL nc_opchk(stat, "nf90_get_var: land_frac")
287  land_frac(:,:,1) = var_tmp(:,:)
288  stat = nf90_close(ncid)
289  CALL nc_opchk(stat, "nf90_close oro_data.nc")
290 
291  DEALLOCATE(var_tmp)
292 
293 END SUBROUTINE read_orog_reg
294 
300 SUBROUTINE write_inland(cs_res)
301  USE netcdf
302  INTEGER, INTENT(IN) :: cs_res
303 
304  CHARACTER(len=256) :: filename
305  CHARACTER(len=1) :: ich
306  CHARACTER(len=4) res_ch
307 
308  INTEGER :: tile_num
309  INTEGER :: stat, ncid, x_dimid, y_dimid, inland_id, dimids(2)
310  REAL, ALLOCATABLE :: var_tmp(:,:)
311 
312  ALLOCATE(var_tmp(cs_res,cs_res))
313 
314  WRITE(res_ch,'(I4)') cs_res
315  DO tile_num = tile_beg, tile_end
316  WRITE(ich, '(I1)') tile_num
317  filename = "oro.C" // trim(adjustl(res_ch)) // ".tile" // ich // ".nc"
318  print *,'write inland to ',trim(filename)
319  stat = nf90_open(filename, nf90_write, ncid)
320  CALL nc_opchk(stat, "nf90_open oro_data.nc")
321  stat = nf90_inq_dimid(ncid, "lon", x_dimid)
322  CALL nc_opchk(stat, "nf90_inq_dim: x")
323  stat = nf90_inq_dimid(ncid, "lat", y_dimid)
324  CALL nc_opchk(stat, "nf90_inq_dim: y")
325 
326 ! original orodata netcdf file uses (y, x) order, so we made change to match it.
327  dimids = (/ x_dimid, y_dimid /)
328 
329 ! define a new variables
330  stat = nf90_inq_varid(ncid,"inland",inland_id) !safeguard if "inland" exists
331  IF (stat /= nf90_noerr) THEN
332  stat = nf90_redef(ncid)
333  CALL nc_opchk(stat, "nf90_redef")
334  stat = nf90_def_var(ncid,"inland",nf90_float,dimids,inland_id)
335  CALL nc_opchk(stat, "nf90_def_var: inland")
336  stat = nf90_put_att(ncid, inland_id,'coordinates','geolon geolat')
337  CALL nc_opchk(stat, "nf90_put_att: inland:coordinates")
338  stat = nf90_put_att(ncid, inland_id,'description', &
339  'inland = 1 indicates grid cells away from coast')
340  CALL nc_opchk(stat, "nf90_put_att: inland:description")
341  stat = nf90_enddef(ncid)
342  CALL nc_opchk(stat, "nf90_enddef")
343  ENDIF
344 
345  var_tmp(:,:) = inland(:,:,tile_num)
346  stat = nf90_put_var(ncid, inland_id, var_tmp, &
347  start = (/ 1, 1 /), count = (/ cs_res, cs_res /) )
348  CALL nc_opchk(stat, "nf90_put_var: inland")
349 
350  stat = nf90_close(ncid)
351  CALL nc_opchk(stat, "nf90_close oro_data.nc")
352  ENDDO
353  DEALLOCATE(var_tmp)
354 
355 END SUBROUTINE write_inland
356 
362 SUBROUTINE write_inland_reg(cs_res)
363  USE netcdf
364  INTEGER, INTENT(IN) :: cs_res
365 
366  CHARACTER(len=256) :: filename
367  CHARACTER(len=1) :: ich
368  CHARACTER(len=4) res_ch
369 
370  INTEGER :: tile_num
371  INTEGER :: stat, ncid, x_dimid, y_dimid, inland_id, dimids(2)
372  REAL, ALLOCATABLE :: var_tmp(:,:)
373  CHARACTER(len=8) dimname
374 
375  ALLOCATE(var_tmp(x_res,y_res))
376 
377  WRITE(res_ch,'(I4)') cs_res
378  tile_num = 7
379  WRITE(ich, '(I1)') tile_num
380  filename = "oro.C" // trim(adjustl(res_ch)) // ".tile" // ich // ".nc"
381  print*,'write inland to ',trim(filename)
382  stat = nf90_open(filename, nf90_write, ncid)
383  CALL nc_opchk(stat, "nf90_open oro_data.nc")
384  stat = nf90_inq_dimid(ncid, "lon", x_dimid)
385  CALL nc_opchk(stat, "nf90_inq_dim: x")
386  stat = nf90_inq_dimid(ncid, "lat", y_dimid)
387  CALL nc_opchk(stat, "nf90_inq_dim: y")
388  stat = nf90_inquire_dimension(ncid,x_dimid,dimname,len=x_res)
389  CALL nc_opchk(stat,'nf90_inquire_dimension: lon')
390  stat = nf90_inquire_dimension(ncid,y_dimid,dimname,len=y_res)
391  CALL nc_opchk(stat,'nf90_inquire_dimension: lon')
392 
393 ! original orodata netcdf file uses (y, x) order, so we made change to match it.
394  dimids = (/ x_dimid, y_dimid /)
395 
396 ! define a new variables
397  stat = nf90_inq_varid(ncid,"inland",inland_id) !safeguard if "inland" exists
398  IF (stat /= nf90_noerr) THEN
399  stat = nf90_redef(ncid)
400  CALL nc_opchk(stat, "nf90_redef")
401  stat = nf90_def_var(ncid,"inland",nf90_float,dimids,inland_id)
402  CALL nc_opchk(stat, "nf90_def_var: inland")
403  stat = nf90_put_att(ncid, inland_id,'coordinates','geolon geolat')
404  CALL nc_opchk(stat, "nf90_put_att: inland:coordinates")
405  stat = nf90_put_att(ncid, inland_id,'description', &
406  'inland = 1 indicates grid cells away from coast')
407  CALL nc_opchk(stat, "nf90_put_att: inland:description")
408  stat = nf90_enddef(ncid)
409  CALL nc_opchk(stat, "nf90_enddef")
410  ENDIF
411 
412  var_tmp(:,:) = inland(:,:,1)
413  stat = nf90_put_var(ncid, inland_id, var_tmp, &
414  start = (/ 1, 1 /), count = (/ x_res, y_res /) )
415  CALL nc_opchk(stat, "nf90_put_var: inland")
416 
417  stat = nf90_close(ncid)
418  CALL nc_opchk(stat, "nf90_close oro_data.nc")
419 
420  DEALLOCATE(var_tmp)
421 
422 END SUBROUTINE write_inland_reg
423 
425 SUBROUTINE free_mem()
426 
427  DEALLOCATE(inland, land_frac)
428 
429 END SUBROUTINE free_mem
430 
437 SUBROUTINE nc_opchk(stat,opname)
438  USE netcdf
439  IMPLICIT NONE
440  INTEGER stat
441  CHARACTER(len=*) opname
442  CHARACTER(64) msg
443 
444  IF (stat .NE.0) THEN
445  msg = trim(opname) // ' Error, status code and message:'
446  print*,trim(msg), stat, nf90_strerror(stat)
447  stop
448  END IF
449 
450 END SUBROUTINE nc_opchk
451 
452 END PROGRAM inland_mask
453 
recursive subroutine mark_regional_inland_rec_d(i, j, t, rd)
Recursively walk through neighbors marking inland points for regional grid.
Definition: inland.F90:168
subroutine mark_inland_reg(cs_res)
Create inland mask for regional grid.
Definition: inland.F90:99
subroutine read_orog(cs_res)
Read in orography (land fraction) data.
Definition: inland.F90:202
subroutine free_mem()
Deallocate module arrays.
Definition: inland.F90:425
subroutine neighbors(tile, i, j, nb)
Get neighbors of cell &#39;c&#39; at (tile, i, j) for global grid.
Definition: nb.F90:192
Neighboring cell descriptor.
Definition: nb.F90:17
recursive subroutine mark_global_inland_rec_d(i, j, t, rd)
Recursively walk through neighbors marking inland points for global grid.
Definition: inland.F90:131
subroutine idx_init(cres_in)
Initialize inter-panel neighbor index for global grid.
Definition: nb.F90:48
subroutine write_inland(cs_res)
Write inland back to the orography data files for global grid.
Definition: inland.F90:300
Definition: nb.F90:7
subroutine neighbors_reg(i, j, nb)
Get neighbors of cell &#39;c&#39; at (tile, i, j) for regional grid.
Definition: nb.F90:393
subroutine nc_opchk(stat, opname)
Check NetCDF return code and print error message.
Definition: inland.F90:437
program inland_mask
This program creates the inland mask and writes it to the orography data files.
Definition: inland.F90:9
subroutine write_inland_reg(cs_res)
Write inland back to the orography data files for regional grid.
Definition: inland.F90:362
subroutine read_orog_reg(cs_res)
Read in orography (land fraction) data for regional grid.
Definition: inland.F90:248
subroutine mark_global_inland(cs_res)
Create inland mask for global grid.
Definition: inland.F90:79
subroutine idx_init_reg(xres_in, yres_in)
Initialize resolution module variables for regional grid.
Definition: nb.F90:91