MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
DisNCStructured.f90
Go to the documentation of this file.
1 !> @brief This module contains the DisNCStructuredModule
2 !!
3 !! This module defines a STRUCTURED (non-ugrid) netcdf
4 !! export type for DIS models. It is dependent on netcdf
5 !! libraries.
6 !!
7 !<
9 
10  use kindmodule, only: dp, i4b, lgp
19  use dismodule, only: distype
20  use netcdfcommonmodule, only: nf_verify
21  use netcdf
22 
23  implicit none
24  private
25  public :: disncstructuredtype
26 
28  integer(I4B) :: x !< number of columns
29  integer(I4B) :: y !< number of rows
30  integer(I4B) :: z !< number of layers
31  integer(I4B) :: ncpl !< number of cells in layer
32  integer(I4B) :: time !< number of steps
33  integer(I4B) :: bnd !< number in boundary
34  contains
35  end type structuredncdimidtype
36 
38  integer(I4B) :: x !< x coordinate variable
39  integer(I4B) :: y !< y coordinate variable
40  integer(I4B) :: z !< z coordinate variable
41  integer(I4B) :: time !< time coordinate variable
42  integer(I4B) :: dependent !< dependent variable
43  integer(I4B) :: x_bnds !< x boundaries 2D array
44  integer(I4B) :: y_bnds !< y boundaries 2D array
45  integer(I4B) :: z_bnds !< z boundaries 2D array
46  integer(I4B) :: latitude !< latitude 2D array
47  integer(I4B) :: longitude !< longitude 2D array
48  contains
49  end type structuredncvaridtype
50 
52  type(structuredncdimidtype) :: dim_ids !< structured dimension ids type
53  type(structuredncvaridtype) :: var_ids !< structured variable ids type
54  type(distype), pointer :: dis => null() !< pointer to model dis package
55  integer(I4B) :: nlay !< number of layers
56  real(dp), dimension(:), pointer, contiguous :: latitude => null() !< lat input array pointer
57  real(dp), dimension(:), pointer, contiguous :: longitude => null() !< lon input array pointer
58  integer(I4B), pointer :: chunk_z !< chunking parameter for z dimension
59  integer(I4B), pointer :: chunk_y !< chunking parameter for y dimension
60  integer(I4B), pointer :: chunk_x !< chunking parameter for x dimension
61  integer(I4B), dimension(:), allocatable :: layers !< layers array
62  logical(LGP) :: latlon !< are lat and lon arrays to be written to netcdf file
63  contains
64  procedure :: init => dis_export_init
65  procedure :: destroy => dis_export_destroy
66  procedure :: df
67  procedure :: step
68  procedure :: export_input_array
69  procedure :: export_input_arrays
70  procedure :: package_step_ilayer
71  procedure :: package_step
72  procedure :: export_layer_3d
73  procedure :: add_pkg_data
74  procedure :: add_global_att
75  procedure :: define_dim
76  procedure :: define_dependent
77  procedure :: define_gridmap
78  procedure :: define_projection
79  procedure :: add_proj_data
80  procedure :: add_grid_data
81  end type disncstructuredtype
82 
83  interface nc_export_array
84  module procedure nc_export_int1d, nc_export_int2d, &
87  end interface nc_export_array
88 
89 contains
90 
91  !> @brief netcdf export dis init
92  !<
93  subroutine dis_export_init(this, modelname, modeltype, modelfname, nc_fname, &
94  disenum, nctype, iout)
97  class(disncstructuredtype), intent(inout) :: this
98  character(len=*), intent(in) :: modelname
99  character(len=*), intent(in) :: modeltype
100  character(len=*), intent(in) :: modelfname
101  character(len=*), intent(in) :: nc_fname
102  integer(I4B), intent(in) :: disenum
103  integer(I4B), intent(in) :: nctype
104  integer(I4B), intent(in) :: iout
105  integer(I4B) :: k, latsz, lonsz
106  logical(LGP) :: found
107 
108  ! set nlay
109  this%nlay = this%dis%nlay
110 
111  ! allocate
112  allocate (this%chunk_z)
113  allocate (this%chunk_y)
114  allocate (this%chunk_x)
115  allocate (this%layers(this%nlay))
116 
117  ! initialize
118  this%chunk_z = -1
119  this%chunk_y = -1
120  this%chunk_x = -1
121  do k = 1, this%nlay
122  this%layers(k) = k
123  end do
124 
125  this%latlon = .false.
126 
127  ! initialize base class
128  call this%NCModelExportType%init(modelname, modeltype, modelfname, nc_fname, &
129  disenum, nctype, iout)
130  ! update values from input context
131  if (this%ncf_mempath /= '') then
132  call mem_set_value(this%chunk_z, 'CHUNK_Z', this%ncf_mempath, found)
133  call mem_set_value(this%chunk_y, 'CHUNK_Y', this%ncf_mempath, found)
134  call mem_set_value(this%chunk_x, 'CHUNK_X', this%ncf_mempath, found)
135 
136  if (this%chunk_time > 0 .and. this%chunk_z > 0 .and. &
137  this%chunk_y > 0 .and. this%chunk_x > 0) then
138  this%chunking_active = .true.
139  else if (this%chunk_time > 0 .or. this%chunk_z > 0 .or. &
140  this%chunk_y > 0 .or. this%chunk_x > 0) then
141  this%chunk_time = -1
142  this%chunk_z = -1
143  this%chunk_y = -1
144  this%chunk_x = -1
145  write (warnmsg, '(a)') 'Ignoring user provided NetCDF chunking &
146  &parameters. Define chunk_time, chunk_x, chunk_y and chunk_z input &
147  &parameters to see an effect.'
148  call store_warning(warnmsg)
149  end if
150 
151  call get_isize('LATITUDE', this%ncf_mempath, latsz)
152  call get_isize('LONGITUDE', this%ncf_mempath, lonsz)
153 
154  if (latsz > 0 .and. lonsz > 0) then
155  this%latlon = .true.
156  call mem_setptr(this%latitude, 'LATITUDE', this%ncf_mempath)
157  call mem_setptr(this%longitude, 'LONGITUDE', this%ncf_mempath)
158  end if
159  end if
160 
161  ! create the netcdf file
162  call nf_verify(nf90_create(this%nc_fname, &
163  ior(nf90_clobber, nf90_netcdf4), this%ncid), &
164  this%nc_fname)
165  end subroutine dis_export_init
166 
167  !> @brief netcdf export dis destroy
168  !<
169  subroutine dis_export_destroy(this)
170  class(disncstructuredtype), intent(inout) :: this
171  call nf_verify(nf90_close(this%ncid), this%nc_fname)
172  deallocate (this%chunk_z)
173  deallocate (this%chunk_y)
174  deallocate (this%chunk_x)
175  deallocate (this%layers)
176  nullify (this%chunk_z)
177  nullify (this%chunk_y)
178  nullify (this%chunk_x)
179  ! destroy base class
180  call this%NCModelExportType%destroy()
181  end subroutine dis_export_destroy
182 
183  !> @brief netcdf export define
184  !<
185  subroutine df(this)
186  use constantsmodule, only: mvalidate
187  use simvariablesmodule, only: isim_mode
188  class(disncstructuredtype), intent(inout) :: this
189  ! put root group file scope attributes
190  call this%add_global_att()
191  ! define root group dimensions and coordinate variables
192  call this%define_dim()
193  ! define grid projection variables
194  call this%define_projection()
195  if (isim_mode /= mvalidate) then
196  ! define the dependent variable
197  call this%define_dependent()
198  end if
199  ! exit define mode
200  call nf_verify(nf90_enddef(this%ncid), this%nc_fname)
201  ! add data locations
202  call this%add_grid_data()
203  ! add projection data
204  call this%add_proj_data()
205  ! define and set package input griddata
206  call this%add_pkg_data()
207  ! define and set gridmap variable
208  call this%define_gridmap()
209  ! synchronize file
210  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
211  end subroutine df
212 
213  !> @brief netcdf export step
214  !<
215  subroutine step(this)
216  use constantsmodule, only: dhnoflo
217  use tdismodule, only: totim
218  class(disncstructuredtype), intent(inout) :: this
219  real(DP), dimension(:), pointer, contiguous :: dbl1d
220  integer(I4B) :: n
221 
222  this%stepcnt = this%stepcnt + 1
223 
224  if (size(this%dis%nodeuser) < &
225  size(this%dis%nodereduced)) then
226  allocate (dbl1d(size(this%dis%nodereduced)))
227  dbl1d = dhnoflo
228  do n = 1, size(this%dis%nodereduced)
229  if (this%dis%nodereduced(n) > 0) then
230  dbl1d(n) = this%x(this%dis%nodereduced(n))
231  end if
232  end do
233  ! write step data to dependent variable
234  call nf_verify(nf90_put_var(this%ncid, &
235  this%var_ids%dependent, dbl1d, &
236  start=(/1, 1, 1, this%stepcnt/), &
237  count=(/this%dis%ncol, &
238  this%dis%nrow, &
239  this%dis%nlay, 1/)), &
240  this%nc_fname)
241  deallocate (dbl1d)
242  else
243  ! write step data to dependent variable
244  call nf_verify(nf90_put_var(this%ncid, &
245  this%var_ids%dependent, this%x, &
246  start=(/1, 1, 1, this%stepcnt/), &
247  count=(/this%dis%ncol, &
248  this%dis%nrow, &
249  this%dis%nlay, 1/)), &
250  this%nc_fname)
251  end if
252 
253  ! write to time coordinate variable
254  call nf_verify(nf90_put_var(this%ncid, this%var_ids%time, &
255  totim, start=(/this%stepcnt/)), &
256  this%nc_fname)
257 
258  ! synchronize file
259  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
260  end subroutine step
261 
262  !> @brief netcdf export an input array
263  !<
264  subroutine export_input_array(this, pkgtype, pkgname, mempath, idt)
265  class(disncstructuredtype), intent(inout) :: this
266  character(len=*), intent(in) :: pkgtype
267  character(len=*), intent(in) :: pkgname
268  character(len=*), intent(in) :: mempath
269  type(inputparamdefinitiontype), pointer, intent(in) :: idt
270  integer(I4B), dimension(:), pointer, contiguous :: int1d
271  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
272  integer(I4B), dimension(:, :, :), pointer, contiguous :: int3d
273  real(DP), dimension(:), pointer, contiguous :: dbl1d
274  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
275  real(DP), dimension(:, :, :), pointer, contiguous :: dbl3d
276  character(len=LINELENGTH) :: nc_varname, input_attr
277  integer(I4B) :: iper, iaux
278 
279  ! initialize
280  iper = 0
281  iaux = 0
282 
283  ! set variable name and input attribute string
284  nc_varname = export_varname(pkgname, idt)
285  input_attr = this%input_attribute(pkgname, idt)
286 
287  select case (idt%datatype)
288  case ('INTEGER1D')
289  call mem_setptr(int1d, idt%mf6varname, mempath)
290  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
291  int1d, nc_varname, pkgname, idt%tagname, &
292  idt%shape, idt%longname, input_attr, &
293  this%gridmap_name, this%latlon, this%deflate, &
294  this%shuffle, this%chunk_z, this%chunk_y, &
295  this%chunk_x, iper, this%nc_fname)
296  case ('INTEGER2D')
297  call mem_setptr(int2d, idt%mf6varname, mempath)
298  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
299  int2d, nc_varname, pkgname, idt%tagname, &
300  idt%shape, idt%longname, input_attr, &
301  this%gridmap_name, this%latlon, this%deflate, &
302  this%shuffle, this%chunk_z, this%chunk_y, &
303  this%chunk_x, this%nc_fname)
304  case ('INTEGER3D')
305  call mem_setptr(int3d, idt%mf6varname, mempath)
306  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
307  int3d, nc_varname, pkgname, idt%tagname, &
308  idt%shape, idt%longname, input_attr, &
309  this%gridmap_name, this%latlon, this%deflate, &
310  this%shuffle, this%chunk_z, this%chunk_y, &
311  this%chunk_x, this%nc_fname)
312  case ('DOUBLE1D')
313  call mem_setptr(dbl1d, idt%mf6varname, mempath)
314  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
315  dbl1d, nc_varname, pkgname, idt%tagname, &
316  idt%shape, idt%longname, input_attr, &
317  this%gridmap_name, this%latlon, this%deflate, &
318  this%shuffle, this%chunk_z, this%chunk_y, &
319  this%chunk_x, iper, this%nc_fname)
320  case ('DOUBLE2D')
321  call mem_setptr(dbl2d, idt%mf6varname, mempath)
322  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
323  dbl2d, nc_varname, pkgname, idt%tagname, &
324  idt%shape, idt%longname, input_attr, &
325  this%gridmap_name, this%latlon, this%deflate, &
326  this%shuffle, this%chunk_z, this%chunk_y, &
327  this%chunk_x, this%nc_fname)
328  case ('DOUBLE3D')
329  call mem_setptr(dbl3d, idt%mf6varname, mempath)
330  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
331  dbl3d, nc_varname, pkgname, idt%tagname, &
332  idt%shape, idt%longname, input_attr, &
333  this%gridmap_name, this%latlon, this%deflate, &
334  this%shuffle, this%chunk_z, this%chunk_y, &
335  this%chunk_x, iper, iaux, this%nc_fname)
336  case default
337  ! no-op, no other datatypes exported
338  end select
339  end subroutine export_input_array
340 
341  !> @brief write package gridded input data
342  !<
343  subroutine export_input_arrays(this, pkgtype, pkgname, mempath, param_dfns)
344  use memorymanagermodule, only: get_isize
345  class(disncstructuredtype), intent(inout) :: this
346  character(len=*), intent(in) :: pkgtype
347  character(len=*), intent(in) :: pkgname
348  character(len=*), intent(in) :: mempath
349  type(inputparamdefinitiontype), dimension(:), pointer, &
350  intent(in) :: param_dfns
351  type(inputparamdefinitiontype), pointer :: idt
352  integer(I4B) :: iparam, isize
353  do iparam = 1, size(param_dfns)
354  ! assign param definition pointer
355  idt => param_dfns(iparam)
356  ! for now only griddata is exported
357  if (idt%blockname == 'GRIDDATA') then
358  ! check if variable is already allocated
359  call get_isize(idt%mf6varname, mempath, isize)
360  if (isize > 0) then
361  call this%export_input_array(pkgtype, pkgname, mempath, idt)
362  end if
363  end if
364  end do
365  end subroutine export_input_arrays
366 
367  !> @brief netcdf export package dynamic input with ilayer index variable
368  !<
369  subroutine package_step_ilayer(this, export_pkg, ilayer_varname, ilayer)
370  use constantsmodule, only: dnodata, dzero
371  use tdismodule, only: kper
374  class(disncstructuredtype), intent(inout) :: this
375  class(exportpackagetype), pointer, intent(in) :: export_pkg
376  character(len=*), intent(in) :: ilayer_varname
377  integer(I4B), intent(in) :: ilayer
378  type(inputparamdefinitiontype), pointer :: idt
379  integer(I4B), dimension(:), pointer, contiguous :: int1d
380  real(DP), dimension(:), pointer, contiguous :: dbl1d
381  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
382  integer(I4B), dimension(:), pointer, contiguous :: ialayer
383  real(DP), dimension(:), contiguous, pointer :: dbl1d_ptr
384  character(len=LINELENGTH) :: nc_varname, input_attr
385  integer(I4B) :: n, iparam, nvals
386  logical(LGP) :: ilayer_read
387 
388  ! initialize
389  nullify (ialayer)
390  ilayer_read = .false.
391 
392  ! set pointer to ilayer variable
393  call mem_setptr(ialayer, export_pkg%param_names(ilayer), &
394  export_pkg%mf6_input%mempath)
395 
396  ! check if layer index variable was read
397  if (export_pkg%param_reads(ilayer)%invar == 1) then
398  ilayer_read = .true.
399  end if
400 
401  ! export defined period input
402  do iparam = 1, export_pkg%nparam
403  ! check if variable was read this period
404  if (export_pkg%param_reads(iparam)%invar < 1) cycle
405 
406  ! set input definition
407  idt => &
408  get_param_definition_type(export_pkg%mf6_input%param_dfns, &
409  export_pkg%mf6_input%component_type, &
410  export_pkg%mf6_input%subcomponent_type, &
411  'PERIOD', export_pkg%param_names(iparam), &
412  this%nc_fname)
413  ! set variable name and input attrs
414  nc_varname = export_varname(export_pkg%mf6_input%subcomponent_name, idt, &
415  iper=kper)
416  input_attr = this%input_attribute(export_pkg%mf6_input%subcomponent_name, &
417  idt)
418  ! export arrays
419  select case (idt%datatype)
420  case ('INTEGER1D')
421  call mem_setptr(int1d, idt%mf6varname, export_pkg%mf6_input%mempath)
422  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
423  int1d, nc_varname, &
424  export_pkg%mf6_input%subcomponent_name, &
425  idt%tagname, idt%shape, idt%longname, input_attr, &
426  this%gridmap_name, this%latlon, this%deflate, &
427  this%shuffle, this%chunk_z, this%chunk_y, &
428  this%chunk_x, export_pkg%iper, this%nc_fname)
429  case ('DOUBLE1D')
430  call mem_setptr(dbl1d, idt%mf6varname, export_pkg%mf6_input%mempath)
431  call this%export_layer_3d(export_pkg, idt, ilayer_read, ialayer, &
432  dbl1d, nc_varname, input_attr)
433  case ('DOUBLE2D')
434  call mem_setptr(dbl2d, idt%mf6varname, export_pkg%mf6_input%mempath)
435  nvals = this%dis%ncol * this%dis%nrow
436  do n = 1, size(dbl2d, dim=1) ! naux
437  dbl1d_ptr(1:nvals) => dbl2d(n, :)
438  if (all(dbl1d_ptr == dzero)) then
439  else
440  call this%export_layer_3d(export_pkg, idt, ilayer_read, ialayer, &
441  dbl1d_ptr, nc_varname, input_attr, n)
442  end if
443  end do
444  case default
445  errmsg = 'EXPORT ilayer unsupported datatype='//trim(idt%datatype)
446  call store_error(errmsg, .true.)
447  end select
448  end do
449 
450  ! synchronize file
451  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
452  end subroutine package_step_ilayer
453 
454  !> @brief netcdf export package dynamic input
455  !<
456  subroutine package_step(this, export_pkg)
457  use tdismodule, only: kper
460  class(disncstructuredtype), intent(inout) :: this
461  class(exportpackagetype), pointer, intent(in) :: export_pkg
462  integer(I4B), dimension(:), pointer, contiguous :: int1d
463  real(DP), dimension(:), pointer, contiguous :: dbl1d
464  type(inputparamdefinitiontype), pointer :: idt
465  character(len=LINELENGTH) :: nc_varname, input_attr
466  integer(I4B) :: iparam
467 
468  do iparam = 1, export_pkg%nparam
469  ! set input definition
470  idt => get_param_definition_type(export_pkg%mf6_input%param_dfns, &
471  export_pkg%mf6_input%component_type, &
472  export_pkg%mf6_input%subcomponent_type, &
473  'PERIOD', export_pkg%param_names(iparam), &
474  this%nc_fname)
475 
476  ! set variable name and input attribute string
477  nc_varname = export_varname(export_pkg%mf6_input%subcomponent_name, idt, &
478  iper=kper)
479  input_attr = this%input_attribute(export_pkg%mf6_input%subcomponent_name, &
480  idt)
481 
482  ! export arrays
483  select case (idt%datatype)
484  case ('INTEGER1D')
485  call mem_setptr(int1d, export_pkg%param_names(iparam), &
486  export_pkg%mf6_input%mempath)
487  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
488  int1d, nc_varname, &
489  export_pkg%mf6_input%subcomponent_name, &
490  idt%tagname, idt%shape, idt%longname, input_attr, &
491  this%gridmap_name, this%latlon, this%deflate, &
492  this%shuffle, this%chunk_z, this%chunk_y, &
493  this%chunk_x, kper, this%nc_fname)
494  case ('DOUBLE1D')
495  call mem_setptr(dbl1d, export_pkg%param_names(iparam), &
496  export_pkg%mf6_input%mempath)
497  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, &
498  dbl1d, nc_varname, &
499  export_pkg%mf6_input%subcomponent_name, &
500  idt%tagname, idt%shape, idt%longname, input_attr, &
501  this%gridmap_name, this%latlon, this%deflate, &
502  this%shuffle, this%chunk_z, this%chunk_y, &
503  this%chunk_x, kper, this%nc_fname)
504  case default
505  errmsg = 'EXPORT unsupported datatype='//trim(idt%datatype)
506  call store_error(errmsg, .true.)
507  end select
508  end do
509 
510  ! synchronize file
511  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
512  end subroutine package_step
513 
514  !> @brief export layer variable as full grid
515  !<
516  subroutine export_layer_3d(this, export_pkg, idt, ilayer_read, ialayer, &
517  dbl1d, nc_varname, input_attr, iaux)
518  use constantsmodule, only: dnodata, dzero
519  use tdismodule, only: kper
521  class(disncstructuredtype), intent(inout) :: this
522  class(exportpackagetype), pointer, intent(in) :: export_pkg
523  type(inputparamdefinitiontype), pointer, intent(in) :: idt
524  logical(LGP), intent(in) :: ilayer_read
525  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: ialayer
526  real(DP), dimension(:), pointer, contiguous, intent(in) :: dbl1d
527  character(len=*), intent(inout) :: nc_varname
528  character(len=*), intent(in) :: input_attr
529  integer(I4B), optional, intent(in) :: iaux
530  real(DP), dimension(:, :, :), pointer, contiguous :: dbl3d
531  integer(I4B) :: n, i, j, k, nvals, idxaux
532  real(DP), dimension(:, :), contiguous, pointer :: dbl2d_ptr
533 
534  ! initialize
535  idxaux = 0
536  if (present(iaux)) then
537  nc_varname = export_varname(export_pkg%mf6_input%subcomponent_name, &
538  idt, iper=kper, iaux=iaux)
539  idxaux = iaux
540  end if
541 
542  allocate (dbl3d(export_pkg%mshape(3), export_pkg%mshape(2), &
543  export_pkg%mshape(1)))
544 
545  if (ilayer_read) then
546  do k = 1, size(dbl3d, dim=3)
547  n = 0
548  do i = 1, size(dbl3d, dim=2)
549  do j = 1, size(dbl3d, dim=1)
550  n = n + 1
551  if (ialayer(n) == k) then
552  dbl3d(j, i, k) = dbl1d(n)
553  else
554  dbl3d(j, i, k) = dnodata
555  end if
556  end do
557  end do
558  end do
559  else
560  dbl3d = dnodata
561  nvals = export_pkg%mshape(3) * export_pkg%mshape(2)
562  dbl2d_ptr(1:export_pkg%mshape(3), 1:export_pkg%mshape(2)) => dbl1d(1:nvals)
563  dbl3d(:, :, 1) = dbl2d_ptr(:, :)
564  end if
565 
566  call nc_export_array(this%ncid, this%dim_ids, this%var_ids, this%dis, dbl3d, &
567  nc_varname, export_pkg%mf6_input%subcomponent_name, &
568  idt%tagname, idt%shape, idt%longname, input_attr, &
569  this%gridmap_name, this%latlon, this%deflate, &
570  this%shuffle, this%chunk_z, this%chunk_y, this%chunk_x, &
571  export_pkg%iper, idxaux, this%nc_fname)
572 
573  deallocate (dbl3d)
574  end subroutine export_layer_3d
575 
576  !> @brief determine packages to write gridded input
577  !<
578  subroutine add_pkg_data(this)
584  class(disncstructuredtype), intent(inout) :: this
585  character(LENCOMPONENTNAME) :: ptype, pname, pkgtype
586  type(characterstringtype), dimension(:), contiguous, &
587  pointer :: pkgtypes => null()
588  type(characterstringtype), dimension(:), contiguous, &
589  pointer :: pkgnames => null()
590  type(characterstringtype), dimension(:), contiguous, &
591  pointer :: mempaths => null()
592  type(inputparamdefinitiontype), dimension(:), pointer :: param_dfns
593  character(len=LENMEMPATH) :: input_mempath, mempath
594  integer(I4B) :: n
595  integer(I4B), pointer :: export_arrays
596  logical(LGP) :: found
597 
598  input_mempath = create_mem_path(component=this%modelname, context=idm_context)
599 
600  ! set pointers to model path package info
601  call mem_setptr(pkgtypes, 'PKGTYPES', input_mempath)
602  call mem_setptr(pkgnames, 'PKGNAMES', input_mempath)
603  call mem_setptr(mempaths, 'MEMPATHS', input_mempath)
604 
605  do n = 1, size(mempaths)
606  ! allocate export_arrays
607  allocate (export_arrays)
608  export_arrays = 0
609 
610  ! set package attributes
611  mempath = mempaths(n)
612  pname = pkgnames(n)
613  ptype = pkgtypes(n)
614 
615  ! export input arrays
616  if (mempath /= '') then
617  ! update export
618  call mem_set_value(export_arrays, 'EXPORT_NC', mempath, found)
619 
620  if (export_arrays > 0) then
621  pkgtype = idm_subcomponent_type(this%modeltype, ptype)
622  param_dfns => param_definitions(this%modeltype, pkgtype)
623  call this%export_input_arrays(ptype, pname, mempath, param_dfns)
624  end if
625  end if
626 
627  ! cleanup
628  deallocate (export_arrays)
629  end do
630  end subroutine add_pkg_data
631 
632  !> @brief create file (group) attributes
633  !<
634  subroutine add_global_att(this)
635  class(disncstructuredtype), intent(inout) :: this
636  ! file scoped title
637  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'title', &
638  this%annotation%title), this%nc_fname)
639  ! source (MODFLOW 6)
640  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'source', &
641  this%annotation%source), this%nc_fname)
642  ! export type (MODFLOW 6)
643  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'modflow6_grid', &
644  this%annotation%grid), this%nc_fname)
645  ! MODFLOW 6 model type
646  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'modflow6_model', &
647  this%annotation%model), this%nc_fname)
648  ! generation datetime
649  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'history', &
650  this%annotation%history), this%nc_fname)
651  ! supported conventions
652  call nf_verify(nf90_put_att(this%ncid, nf90_global, 'Conventions', &
653  this%annotation%conventions), &
654  this%nc_fname)
655  end subroutine add_global_att
656 
657  !> @brief netcdf export define dimensions
658  !<
659  subroutine define_dim(this)
660  use constantsmodule, only: mvalidate
661  use simvariablesmodule, only: isim_mode
662  class(disncstructuredtype), intent(inout) :: this
663 
664  ! bound dim
665  call nf_verify(nf90_def_dim(this%ncid, 'bnd', 2, this%dim_ids%bnd), &
666  this%nc_fname)
667 
668  ! Time
669  if (isim_mode /= mvalidate) then
670  call nf_verify(nf90_def_dim(this%ncid, 'time', this%totnstp, &
671  this%dim_ids%time), this%nc_fname)
672  call nf_verify(nf90_def_var(this%ncid, 'time', nf90_double, &
673  this%dim_ids%time, this%var_ids%time), &
674  this%nc_fname)
675  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'calendar', &
676  'standard'), this%nc_fname)
677  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'units', &
678  this%datetime), this%nc_fname)
679  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'axis', 'T'), &
680  this%nc_fname)
681  !call nf_verify(nf90_put_att(ncid, var_ids%time, 'bounds', 'time_bnds'), this%nc_fname)
682  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'standard_name', &
683  'time'), this%nc_fname)
684  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'long_name', &
685  'time'), this%nc_fname)
686  end if
687 
688  ! Z dimension
689  call nf_verify(nf90_def_dim(this%ncid, 'z', this%dis%nlay, this%dim_ids%z), &
690  this%nc_fname)
691  call nf_verify(nf90_def_var(this%ncid, 'z', nf90_double, this%dim_ids%z, &
692  this%var_ids%z), this%nc_fname)
693  call nf_verify(nf90_put_att(this%ncid, this%var_ids%z, 'units', 'layer'), &
694  this%nc_fname)
695  call nf_verify(nf90_put_att(this%ncid, this%var_ids%z, 'long_name', &
696  'layer number'), this%nc_fname)
697  !call nf_verify(nf90_put_att(this%ncid, this%var_ids%z, 'bounds', 'z_bnds'), &
698  ! this%nc_fname)
699  !call nf_verify(nf90_def_var(this%ncid, 'z_bnds', NF90_DOUBLE, &
700  ! (/this%dim_ids%bnd, this%dim_ids%z/), &
701  ! this%var_ids%z_bnds), this%nc_fname)
702  !call nf_verify(nf90_put_var(this%ncid, this%var_ids%z_bnds, &
703  ! this%elev_bnds), this%nc_fname)
704 
705  ! Y dimension
706  call nf_verify(nf90_def_dim(this%ncid, 'y', this%dis%nrow, this%dim_ids%y), &
707  this%nc_fname)
708  call nf_verify(nf90_def_var(this%ncid, 'y', nf90_double, this%dim_ids%y, &
709  this%var_ids%y), this%nc_fname)
710  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'units', 'm'), &
711  this%nc_fname)
712  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'axis', 'Y'), &
713  this%nc_fname)
714  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'standard_name', &
715  'projection_y_coordinate'), this%nc_fname)
716  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'long_name', &
717  'Northing'), this%nc_fname)
718  if (this%wkt /= '') then
719  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'grid_mapping', &
720  this%gridmap_name), this%nc_fname)
721  end if
722  call nf_verify(nf90_put_att(this%ncid, this%var_ids%y, 'bounds', 'y_bnds'), &
723  this%nc_fname)
724  call nf_verify(nf90_def_var(this%ncid, 'y_bnds', nf90_double, &
725  (/this%dim_ids%bnd, this%dim_ids%y/), &
726  this%var_ids%y_bnds), this%nc_fname)
727 
728  ! X dimension
729  call nf_verify(nf90_def_dim(this%ncid, 'x', this%dis%ncol, this%dim_ids%x), &
730  this%nc_fname)
731  call nf_verify(nf90_def_var(this%ncid, 'x', nf90_double, this%dim_ids%x, &
732  this%var_ids%x), this%nc_fname)
733  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'units', 'm'), &
734  this%nc_fname)
735  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'axis', 'X'), &
736  this%nc_fname)
737  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'standard_name', &
738  'projection_x_coordinate'), this%nc_fname)
739  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'long_name', &
740  'Easting'), this%nc_fname)
741  if (this%wkt /= '') then
742  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'grid_mapping', &
743  this%gridmap_name), this%nc_fname)
744  end if
745  call nf_verify(nf90_put_att(this%ncid, this%var_ids%x, 'bounds', 'x_bnds'), &
746  this%nc_fname)
747  call nf_verify(nf90_def_var(this%ncid, 'x_bnds', nf90_double, &
748  (/this%dim_ids%bnd, this%dim_ids%x/), &
749  this%var_ids%x_bnds), this%nc_fname)
750 
751  ! NCPL dimension
752  call nf_verify(nf90_def_dim(this%ncid, 'ncpl', &
753  this%dis%ncol * this%dis%nrow, &
754  this%dim_ids%ncpl), this%nc_fname)
755  end subroutine define_dim
756 
757  !> @brief create the model layer dependent variables
758  !<
759  subroutine define_dependent(this)
760  use constantsmodule, only: dhnoflo
761  class(disncstructuredtype), intent(inout) :: this
762 
763  call nf_verify(nf90_def_var(this%ncid, this%xname, nf90_double, &
764  (/this%dim_ids%x, this%dim_ids%y, &
765  this%dim_ids%z, this%dim_ids%time/), &
766  this%var_ids%dependent), &
767  this%nc_fname)
768 
769  ! apply chunking parameters
770  if (this%chunking_active) then
771  call nf_verify(nf90_def_var_chunking(this%ncid, &
772  this%var_ids%dependent, &
773  nf90_chunked, &
774  (/this%chunk_x, this%chunk_y, &
775  this%chunk_z, this%chunk_time/)), &
776  this%nc_fname)
777  end if
778 
779  ! deflate and shuffle
780  call ncvar_deflate(this%ncid, this%var_ids%dependent, this%deflate, &
781  this%shuffle, this%nc_fname)
782 
783  ! put attr
784  call nf_verify(nf90_put_att(this%ncid, this%var_ids%dependent, &
785  'units', 'm'), this%nc_fname)
786  call nf_verify(nf90_put_att(this%ncid, this%var_ids%dependent, &
787  'standard_name', this%annotation%stdname), &
788  this%nc_fname)
789  call nf_verify(nf90_put_att(this%ncid, this%var_ids%dependent, 'long_name', &
790  this%annotation%longname), this%nc_fname)
791  call nf_verify(nf90_put_att(this%ncid, this%var_ids%dependent, '_FillValue', &
792  (/dhnoflo/)), this%nc_fname)
793 
794  ! add grid mapping
795  call ncvar_gridmap(this%ncid, this%var_ids%dependent, this%gridmap_name, &
796  this%latlon, this%nc_fname)
797  end subroutine define_dependent
798 
799  !> @brief create the file grid mapping container variable
800  !<
801  subroutine define_gridmap(this)
802  class(disncstructuredtype), intent(inout) :: this
803  integer(I4B) :: var_id
804  if (this%wkt /= '') then
805  call nf_verify(nf90_redef(this%ncid), this%nc_fname)
806  call nf_verify(nf90_def_var(this%ncid, this%gridmap_name, nf90_int, &
807  var_id), this%nc_fname)
808  ! TODO: consider variants epsg_code, spatial_ref, esri_pe_string, wkt, etc
809  call nf_verify(nf90_put_att(this%ncid, var_id, 'crs_wkt', this%wkt), &
810  this%nc_fname)
811  call nf_verify(nf90_enddef(this%ncid), this%nc_fname)
812  call nf_verify(nf90_put_var(this%ncid, var_id, 1), &
813  this%nc_fname)
814  end if
815  end subroutine define_gridmap
816 
817  !> @brief define grid projection variables
818  !<
819  subroutine define_projection(this)
820  class(disncstructuredtype), intent(inout) :: this
821  if (this%latlon .and. this%wkt /= '') then
822  ! lat
823  call nf_verify(nf90_def_var(this%ncid, 'lat', nf90_double, &
824  (/this%dim_ids%x, this%dim_ids%y/), &
825  this%var_ids%latitude), this%nc_fname)
826  call nf_verify(nf90_put_att(this%ncid, this%var_ids%latitude, &
827  'units', 'degrees_north'), this%nc_fname)
828  call nf_verify(nf90_put_att(this%ncid, this%var_ids%latitude, &
829  'standard_name', 'latitude'), this%nc_fname)
830  call nf_verify(nf90_put_att(this%ncid, this%var_ids%latitude, &
831  'long_name', 'latitude'), this%nc_fname)
832 
833  ! lon
834  call nf_verify(nf90_def_var(this%ncid, 'lon', nf90_double, &
835  (/this%dim_ids%x, this%dim_ids%y/), &
836  this%var_ids%longitude), this%nc_fname)
837  call nf_verify(nf90_put_att(this%ncid, this%var_ids%longitude, &
838  'units', 'degrees_east'), this%nc_fname)
839  call nf_verify(nf90_put_att(this%ncid, this%var_ids%longitude, &
840  'standard_name', 'longitude'), this%nc_fname)
841  call nf_verify(nf90_put_att(this%ncid, this%var_ids%longitude, &
842  'long_name', 'longitude'), this%nc_fname)
843  end if
844  end subroutine define_projection
845 
846  !> @brief add grid projection data
847  !<
848  subroutine add_proj_data(this)
849  class(disncstructuredtype), intent(inout) :: this
850  if (this%latlon .and. this%wkt /= '') then
851  ! lat
852  call nf_verify(nf90_put_var(this%ncid, this%var_ids%latitude, &
853  this%latitude, start=(/1, 1/), &
854  count=(/this%dis%ncol, this%dis%nrow/)), &
855  this%nc_fname)
856 
857  ! lon
858  call nf_verify(nf90_put_var(this%ncid, this%var_ids%longitude, &
859  this%longitude, start=(/1, 1/), &
860  count=(/this%dis%ncol, this%dis%nrow/)), &
861  this%nc_fname)
862  end if
863  end subroutine add_proj_data
864 
865  !> @brief add grid coordinates
866  !<
867  subroutine add_grid_data(this)
868  class(disncstructuredtype), intent(inout) :: this
869  integer(I4B) :: ibnd, n !, k, i, j
870  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
871  real(DP), dimension(:), allocatable :: x, y
872 
873  allocate (x(size(this%dis%cellx)))
874  allocate (y(size(this%dis%celly)))
875 
876  do n = 1, size(this%dis%cellx)
877  x(n) = this%dis%cellx(n) + this%dis%xorigin
878  end do
879 
880  do n = 1, size(this%dis%celly)
881  y(n) = this%dis%celly(n) + this%dis%yorigin
882  end do
883 
884  call nf_verify(nf90_put_var(this%ncid, this%var_ids%x, x), &
885  this%nc_fname)
886  call nf_verify(nf90_put_var(this%ncid, this%var_ids%y, y), &
887  this%nc_fname)
888  ! TODO see cf-conventions 4.3.3. Parametric Vertical Coordinate
889  call nf_verify(nf90_put_var(this%ncid, this%var_ids%z, this%layers), &
890  this%nc_fname)
891 
892  deallocate (x)
893  deallocate (y)
894 
895  ! bounds x
896  allocate (dbl2d(2, size(this%dis%cellx)))
897  ibnd = 1
898  do n = 1, size(this%dis%cellx)
899  if (ibnd == 1) then
900  dbl2d(1, ibnd) = this%dis%xorigin
901  dbl2d(2, ibnd) = this%dis%xorigin + this%dis%delr(ibnd)
902  else
903  dbl2d(1, ibnd) = dbl2d(1, ibnd - 1) + this%dis%delr(ibnd)
904  dbl2d(2, ibnd) = dbl2d(2, ibnd - 1) + this%dis%delr(ibnd)
905  end if
906  ibnd = ibnd + 1
907  end do
908  call nf_verify(nf90_put_var(this%ncid, this%var_ids%x_bnds, dbl2d), &
909  this%nc_fname)
910  deallocate (dbl2d)
911 
912  ! bounds y
913  allocate (dbl2d(2, size(this%dis%celly)))
914  ibnd = 1
915  do n = size(this%dis%celly), 1, -1
916  if (ibnd == 1) then
917  dbl2d(1, ibnd) = this%dis%yorigin + sum(this%dis%delc) - this%dis%delc(n)
918  dbl2d(2, ibnd) = this%dis%yorigin + sum(this%dis%delc)
919  else
920  dbl2d(1, ibnd) = dbl2d(1, ibnd - 1) - this%dis%delc(n)
921  dbl2d(2, ibnd) = dbl2d(2, ibnd - 1) - this%dis%delc(n)
922  end if
923  ibnd = ibnd + 1
924  end do
925  call nf_verify(nf90_put_var(this%ncid, this%var_ids%y_bnds, dbl2d), &
926  this%nc_fname)
927  deallocate (dbl2d)
928  end subroutine add_grid_data
929 
930  !> @brief define 2d variable chunking
931  !<
932  subroutine ncvar_chunk2d(ncid, varid, chunk_x, chunk_y, nc_fname)
933  integer(I4B), intent(in) :: ncid
934  integer(I4B), intent(in) :: varid
935  integer(I4B), intent(in) :: chunk_x
936  integer(I4B), intent(in) :: chunk_y
937  character(len=*), intent(in) :: nc_fname
938  if (chunk_y > 0 .and. chunk_x > 0) then
939  call nf_verify(nf90_def_var_chunking(ncid, varid, nf90_chunked, &
940  (/chunk_x, chunk_y/)), nc_fname)
941  end if
942  end subroutine ncvar_chunk2d
943 
944  !> @brief define 3d variable chunking
945  !<
946  subroutine ncvar_chunk3d(ncid, varid, chunk_x, chunk_y, chunk_z, nc_fname)
947  integer(I4B), intent(in) :: ncid
948  integer(I4B), intent(in) :: varid
949  integer(I4B), intent(in) :: chunk_x
950  integer(I4B), intent(in) :: chunk_y
951  integer(I4B), intent(in) :: chunk_z
952  character(len=*), intent(in) :: nc_fname
953  if (chunk_z > 0 .and. chunk_y > 0 .and. chunk_x > 0) then
954  call nf_verify(nf90_def_var_chunking(ncid, varid, nf90_chunked, &
955  (/chunk_x, chunk_y, chunk_z/)), &
956  nc_fname)
957  end if
958  end subroutine ncvar_chunk3d
959 
960  !> @brief define variable compression
961  !<
962  subroutine ncvar_deflate(ncid, varid, deflate, shuffle, nc_fname)
963  integer(I4B), intent(in) :: ncid
964  integer(I4B), intent(in) :: varid
965  integer(I4B), intent(in) :: deflate
966  integer(I4B), intent(in) :: shuffle
967  character(len=*), intent(in) :: nc_fname
968  ! deflate and shuffle
969  if (deflate >= 0) then
970  call nf_verify(nf90_def_var_deflate(ncid, varid, shuffle=shuffle, &
971  deflate=1, deflate_level=deflate), &
972  nc_fname)
973  end if
974  end subroutine ncvar_deflate
975 
976  !> @brief put variable gridmap attributes
977  !<
978  subroutine ncvar_gridmap(ncid, varid, gridmap_name, latlon, nc_fname)
979  integer(I4B), intent(in) :: ncid
980  integer(I4B), intent(in) :: varid
981  character(len=*), intent(in) :: gridmap_name
982  logical(LGP), intent(in) :: latlon
983  character(len=*), intent(in) :: nc_fname
984  if (gridmap_name /= '') then
985  if (latlon) then
986  call nf_verify(nf90_put_att(ncid, varid, 'coordinates', 'lon lat'), &
987  nc_fname)
988  else
989  call nf_verify(nf90_put_att(ncid, varid, 'coordinates', 'x y'), &
990  nc_fname)
991  end if
992  call nf_verify(nf90_put_att(ncid, varid, 'grid_mapping', gridmap_name), &
993  nc_fname)
994  end if
995  end subroutine ncvar_gridmap
996 
997  !> @brief put variable internal modflow6 attributes
998  !<
999  subroutine ncvar_mf6attr(ncid, varid, iper, iaux, nc_tag, nc_fname)
1000  integer(I4B), intent(in) :: ncid
1001  integer(I4B), intent(in) :: varid
1002  integer(I4B), intent(in) :: iper
1003  integer(I4B), intent(in) :: iaux
1004  character(len=*), intent(in) :: nc_tag
1005  character(len=*), intent(in) :: nc_fname
1006  if (nc_tag /= '') then
1007  call nf_verify(nf90_put_att(ncid, varid, 'modflow6_input', &
1008  nc_tag), nc_fname)
1009  if (iper > 0) then
1010  call nf_verify(nf90_put_att(ncid, varid, 'modflow6_iper', &
1011  iper), nc_fname)
1012  end if
1013  if (iaux > 0) then
1014  call nf_verify(nf90_put_att(ncid, varid, 'modflow6_iaux', &
1015  iaux), nc_fname)
1016  end if
1017  end if
1018  end subroutine ncvar_mf6attr
1019 
1020  !> @brief netcdf export 1D integer
1021  !<
1022  subroutine nc_export_int1d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1023  pkgname, tagname, shapestr, longname, nc_tag, &
1024  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1025  chunk_y, chunk_x, iper, nc_fname)
1026  integer(I4B), intent(in) :: ncid
1027  type(structuredncdimidtype), intent(inout) :: dim_ids
1028  type(structuredncvaridtype), intent(inout) :: var_ids
1029  type(distype), pointer, intent(in) :: dis
1030  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: p_mem
1031  character(len=*), intent(in) :: nc_varname
1032  character(len=*), intent(in) :: pkgname
1033  character(len=*), intent(in) :: tagname
1034  character(len=*), intent(in) :: shapestr
1035  character(len=*), intent(in) :: longname
1036  character(len=*), intent(in) :: nc_tag
1037  character(len=*), intent(in) :: gridmap_name
1038  logical(LGP), intent(in) :: latlon
1039  integer(I4B), intent(in) :: deflate
1040  integer(I4B), intent(in) :: shuffle
1041  integer(I4B), intent(in) :: chunk_z
1042  integer(I4B), intent(in) :: chunk_y
1043  integer(I4B), intent(in) :: chunk_x
1044  integer(I4B), intent(in) :: iper
1045  character(len=*), intent(in) :: nc_fname
1046  integer(I4B) :: var_id, axis_sz
1047  character(len=LINELENGTH) :: longname_l
1048 
1049  if (shapestr == 'NROW' .or. &
1050  shapestr == 'NCOL' .or. &
1051  shapestr == 'NCPL') then
1052 
1053  select case (shapestr)
1054  case ('NROW')
1055  axis_sz = dim_ids%y
1056  case ('NCOL')
1057  axis_sz = dim_ids%x
1058  case ('NCPL')
1059  axis_sz = dim_ids%ncpl
1060  end select
1061 
1062  longname_l = export_longname(longname, pkgname, tagname, layer=0, iper=iper)
1063 
1064  ! reenter define mode and create variable
1065  call nf_verify(nf90_redef(ncid), nc_fname)
1066  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_int, &
1067  (/axis_sz/), var_id), &
1068  nc_fname)
1069 
1070  ! NROW/NCOL shapes use default chunking
1071  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1072 
1073  ! put attr
1074  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1075  (/nf90_fill_int/)), nc_fname)
1076  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1077  longname_l), nc_fname)
1078 
1079  ! add mf6 attr
1080  call ncvar_mf6attr(ncid, var_id, iper, 0, nc_tag, nc_fname)
1081 
1082  ! exit define mode and write data
1083  call nf_verify(nf90_enddef(ncid), nc_fname)
1084  call nf_verify(nf90_put_var(ncid, var_id, p_mem), &
1085  nc_fname)
1086 
1087  else
1088  ! reenter define mode and create variable
1089  call nf_verify(nf90_redef(ncid), nc_fname)
1090  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_int, &
1091  (/dim_ids%x, dim_ids%y, dim_ids%z/), var_id), &
1092  nc_fname)
1093 
1094  ! apply chunking parameters
1095  call ncvar_chunk3d(ncid, var_id, chunk_x, chunk_y, chunk_z, nc_fname)
1096  ! deflate and shuffle
1097  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1098 
1099  ! put attr
1100  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1101  (/nf90_fill_int/)), nc_fname)
1102  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1103  longname), nc_fname)
1104 
1105  ! add grid mapping and mf6 attr
1106  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1107  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1108 
1109  ! exit define mode and write data
1110  call nf_verify(nf90_enddef(ncid), nc_fname)
1111  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1, 1/), &
1112  count=(/dis%ncol, dis%nrow, dis%nlay/)), &
1113  nc_fname)
1114  end if
1115  end subroutine nc_export_int1d
1116 
1117  !> @brief netcdf export 2D integer
1118  !<
1119  subroutine nc_export_int2d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1120  pkgname, tagname, shapestr, longname, nc_tag, &
1121  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1122  chunk_y, chunk_x, nc_fname)
1123  integer(I4B), intent(in) :: ncid
1124  type(structuredncdimidtype), intent(inout) :: dim_ids
1125  type(structuredncvaridtype), intent(inout) :: var_ids
1126  type(distype), pointer, intent(in) :: dis
1127  integer(I4B), dimension(:, :), pointer, contiguous, intent(in) :: p_mem
1128  character(len=*), intent(in) :: nc_varname
1129  character(len=*), intent(in) :: pkgname
1130  character(len=*), intent(in) :: tagname
1131  character(len=*), intent(in) :: shapestr
1132  character(len=*), intent(in) :: longname
1133  character(len=*), intent(in) :: nc_tag
1134  character(len=*), intent(in) :: gridmap_name
1135  logical(LGP), intent(in) :: latlon
1136  integer(I4B), intent(in) :: deflate
1137  integer(I4B), intent(in) :: shuffle
1138  integer(I4B), intent(in) :: chunk_z
1139  integer(I4B), intent(in) :: chunk_y
1140  integer(I4B), intent(in) :: chunk_x
1141  character(len=*), intent(in) :: nc_fname
1142  integer(I4B) :: var_id
1143 
1144  ! reenter define mode and create variable
1145  call nf_verify(nf90_redef(ncid), nc_fname)
1146  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_int, &
1147  (/dim_ids%x, dim_ids%y/), var_id), &
1148  nc_fname)
1149 
1150  ! apply chunking parameters
1151  call ncvar_chunk2d(ncid, var_id, chunk_x, chunk_y, nc_fname)
1152  ! deflate and shuffle
1153  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1154 
1155  ! put attr
1156  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1157  (/nf90_fill_int/)), nc_fname)
1158  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1159  longname), nc_fname)
1160 
1161  ! add grid mapping and mf6 attr
1162  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1163  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1164 
1165  ! exit define mode and write data
1166  call nf_verify(nf90_enddef(ncid), nc_fname)
1167  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1/), &
1168  count=(/dis%ncol, dis%nrow/)), &
1169  nc_fname)
1170  end subroutine nc_export_int2d
1171 
1172  !> @brief netcdf export 3D integer
1173  !<
1174  subroutine nc_export_int3d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1175  pkgname, tagname, shapestr, longname, nc_tag, &
1176  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1177  chunk_y, chunk_x, nc_fname)
1178  integer(I4B), intent(in) :: ncid
1179  type(structuredncdimidtype), intent(inout) :: dim_ids
1180  type(structuredncvaridtype), intent(inout) :: var_ids
1181  type(distype), pointer, intent(in) :: dis
1182  integer(I4B), dimension(:, :, :), pointer, contiguous, intent(in) :: p_mem
1183  character(len=*), intent(in) :: nc_varname
1184  character(len=*), intent(in) :: pkgname
1185  character(len=*), intent(in) :: tagname
1186  character(len=*), intent(in) :: shapestr
1187  character(len=*), intent(in) :: longname
1188  character(len=*), intent(in) :: nc_tag
1189  character(len=*), intent(in) :: gridmap_name
1190  logical(LGP), intent(in) :: latlon
1191  integer(I4B), intent(in) :: deflate
1192  integer(I4B), intent(in) :: shuffle
1193  integer(I4B), intent(in) :: chunk_z
1194  integer(I4B), intent(in) :: chunk_y
1195  integer(I4B), intent(in) :: chunk_x
1196  character(len=*), intent(in) :: nc_fname
1197  integer(I4B) :: var_id
1198 
1199  ! reenter define mode and create variable
1200  call nf_verify(nf90_redef(ncid), nc_fname)
1201  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_int, &
1202  (/dim_ids%x, dim_ids%y, dim_ids%z/), var_id), &
1203  nc_fname)
1204 
1205  ! apply chunking parameters
1206  call ncvar_chunk3d(ncid, var_id, chunk_x, chunk_y, chunk_z, nc_fname)
1207  ! deflate and shuffle
1208  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1209 
1210  ! put attr
1211  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1212  (/nf90_fill_int/)), nc_fname)
1213  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1214  longname), nc_fname)
1215 
1216  ! add grid mapping and mf6 attr
1217  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1218  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1219 
1220  ! exit define mode and write data
1221  call nf_verify(nf90_enddef(ncid), nc_fname)
1222  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1, 1/), &
1223  count=(/dis%ncol, dis%nrow, dis%nlay/)), &
1224  nc_fname)
1225  end subroutine nc_export_int3d
1226 
1227  !> @brief netcdf export 1D double
1228  !<
1229  subroutine nc_export_dbl1d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1230  pkgname, tagname, shapestr, longname, nc_tag, &
1231  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1232  chunk_y, chunk_x, iper, nc_fname)
1233  use constantsmodule, only: dnodata
1234  integer(I4B), intent(in) :: ncid
1235  type(structuredncdimidtype), intent(inout) :: dim_ids
1236  type(structuredncvaridtype), intent(inout) :: var_ids
1237  type(distype), pointer, intent(in) :: dis
1238  real(DP), dimension(:), pointer, contiguous, intent(in) :: p_mem
1239  character(len=*), intent(in) :: nc_varname
1240  character(len=*), intent(in) :: pkgname
1241  character(len=*), intent(in) :: tagname
1242  character(len=*), intent(in) :: shapestr
1243  character(len=*), intent(in) :: longname
1244  character(len=*), intent(in) :: nc_tag
1245  character(len=*), intent(in) :: gridmap_name
1246  logical(LGP), intent(in) :: latlon
1247  integer(I4B), intent(in) :: deflate
1248  integer(I4B), intent(in) :: shuffle
1249  integer(I4B), intent(in) :: chunk_z
1250  integer(I4B), intent(in) :: chunk_y
1251  integer(I4B), intent(in) :: chunk_x
1252  integer(I4B), intent(in) :: iper
1253  character(len=*), intent(in) :: nc_fname
1254  integer(I4B) :: var_id, axis_sz
1255  real(DP) :: fill_value
1256  character(len=LINELENGTH) :: longname_l
1257 
1258  if (shapestr == 'NROW' .or. &
1259  shapestr == 'NCOL' .or. &
1260  shapestr == 'NCPL') then
1261 
1262  select case (shapestr)
1263  case ('NROW')
1264  axis_sz = dim_ids%y
1265  case ('NCOL')
1266  axis_sz = dim_ids%x
1267  case ('NCPL')
1268  axis_sz = dim_ids%ncpl
1269  end select
1270 
1271  ! reenter define mode and create variable
1272  call nf_verify(nf90_redef(ncid), nc_fname)
1273  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_double, &
1274  (/axis_sz/), var_id), &
1275  nc_fname)
1276 
1277  ! NROW/NCOL shapes use default chunking
1278  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1279 
1280  ! put attr
1281  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1282  (/nf90_fill_double/)), nc_fname)
1283  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1284  longname), nc_fname)
1285 
1286  ! add mf6 attr
1287  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1288 
1289  ! exit define mode and write data
1290  call nf_verify(nf90_enddef(ncid), nc_fname)
1291  call nf_verify(nf90_put_var(ncid, var_id, p_mem), &
1292  nc_fname)
1293 
1294  else
1295  if (iper > 0) then
1296  fill_value = dnodata
1297  else
1298  fill_value = nf90_fill_double
1299  end if
1300 
1301  longname_l = export_longname(longname, pkgname, tagname, layer=0, iper=iper)
1302 
1303  ! reenter define mode and create variable
1304  call nf_verify(nf90_redef(ncid), nc_fname)
1305  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_double, &
1306  (/dim_ids%x, dim_ids%y, dim_ids%z/), var_id), &
1307  nc_fname)
1308 
1309  ! apply chunking parameters
1310  call ncvar_chunk3d(ncid, var_id, chunk_x, chunk_y, chunk_z, nc_fname)
1311  ! deflate and shuffle
1312  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1313 
1314  ! put attr
1315  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1316  (/fill_value/)), nc_fname)
1317  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1318  longname_l), nc_fname)
1319 
1320  ! add grid mapping and mf6 attr
1321  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1322  call ncvar_mf6attr(ncid, var_id, iper, 0, nc_tag, nc_fname)
1323 
1324  ! exit define mode and write data
1325  call nf_verify(nf90_enddef(ncid), nc_fname)
1326  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1, 1/), &
1327  count=(/dis%ncol, dis%nrow, dis%nlay/)), &
1328  nc_fname)
1329  end if
1330  end subroutine nc_export_dbl1d
1331 
1332  !> @brief netcdf export 2D double
1333  !<
1334  subroutine nc_export_dbl2d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1335  pkgname, tagname, shapestr, longname, nc_tag, &
1336  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1337  chunk_y, chunk_x, nc_fname)
1338  integer(I4B), intent(in) :: ncid
1339  type(structuredncdimidtype), intent(inout) :: dim_ids
1340  type(structuredncvaridtype), intent(inout) :: var_ids
1341  type(distype), pointer, intent(in) :: dis
1342  real(DP), dimension(:, :), pointer, contiguous, intent(in) :: p_mem
1343  character(len=*), intent(in) :: nc_varname
1344  character(len=*), intent(in) :: pkgname
1345  character(len=*), intent(in) :: tagname
1346  character(len=*), intent(in) :: shapestr
1347  character(len=*), intent(in) :: longname
1348  character(len=*), intent(in) :: nc_tag
1349  character(len=*), intent(in) :: gridmap_name
1350  logical(LGP), intent(in) :: latlon
1351  integer(I4B), intent(in) :: deflate
1352  integer(I4B), intent(in) :: shuffle
1353  integer(I4B), intent(in) :: chunk_z
1354  integer(I4B), intent(in) :: chunk_y
1355  integer(I4B), intent(in) :: chunk_x
1356  character(len=*), intent(in) :: nc_fname
1357  integer(I4B) :: var_id
1358 
1359  ! reenter define mode and create variable
1360  call nf_verify(nf90_redef(ncid), nc_fname)
1361  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_double, &
1362  (/dim_ids%x, dim_ids%y/), var_id), &
1363  nc_fname)
1364 
1365  ! apply chunking parameters
1366  call ncvar_chunk2d(ncid, var_id, chunk_x, chunk_y, nc_fname)
1367  ! deflate and shuffle
1368  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1369 
1370  ! put attr
1371  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1372  (/nf90_fill_double/)), nc_fname)
1373  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1374  longname), nc_fname)
1375 
1376  ! add grid mapping and mf6 attr
1377  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1378  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1379 
1380  ! exit define mode and write data
1381  call nf_verify(nf90_enddef(ncid), nc_fname)
1382  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1/), &
1383  count=(/dis%ncol, dis%nrow/)), &
1384  nc_fname)
1385  end subroutine nc_export_dbl2d
1386 
1387  !> @brief netcdf export 3D double
1388  !<
1389  subroutine nc_export_dbl3d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, &
1390  pkgname, tagname, shapestr, longname, nc_tag, &
1391  gridmap_name, latlon, deflate, shuffle, chunk_z, &
1392  chunk_y, chunk_x, iper, iaux, nc_fname)
1393  use constantsmodule, only: dnodata
1394  integer(I4B), intent(in) :: ncid
1395  type(structuredncdimidtype), intent(inout) :: dim_ids
1396  type(structuredncvaridtype), intent(inout) :: var_ids
1397  type(distype), pointer, intent(in) :: dis
1398  real(DP), dimension(:, :, :), pointer, contiguous, intent(in) :: p_mem
1399  character(len=*), intent(in) :: nc_varname
1400  character(len=*), intent(in) :: pkgname
1401  character(len=*), intent(in) :: tagname
1402  character(len=*), intent(in) :: shapestr
1403  character(len=*), intent(in) :: longname
1404  character(len=*), intent(in) :: nc_tag
1405  character(len=*), intent(in) :: gridmap_name
1406  logical(LGP), intent(in) :: latlon
1407  integer(I4B), intent(in) :: deflate
1408  integer(I4B), intent(in) :: shuffle
1409  integer(I4B), intent(in) :: chunk_z
1410  integer(I4B), intent(in) :: chunk_y
1411  integer(I4B), intent(in) :: chunk_x
1412  integer(I4B), intent(in) :: iper
1413  integer(I4B), intent(in) :: iaux
1414  character(len=*), intent(in) :: nc_fname
1415  integer(I4B) :: var_id
1416  real(DP) :: fill_value
1417  character(len=LINELENGTH) :: longname_l
1418 
1419  if (iper > 0) then
1420  fill_value = dnodata
1421  else
1422  fill_value = nf90_fill_double
1423  end if
1424 
1425  longname_l = export_longname(longname, pkgname, tagname, layer=0, iper=iper)
1426 
1427  ! reenter define mode and create variable
1428  call nf_verify(nf90_redef(ncid), nc_fname)
1429  call nf_verify(nf90_def_var(ncid, nc_varname, nf90_double, &
1430  (/dim_ids%x, dim_ids%y, dim_ids%z/), var_id), &
1431  nc_fname)
1432 
1433  ! apply chunking parameters
1434  call ncvar_chunk3d(ncid, var_id, chunk_x, chunk_y, chunk_z, nc_fname)
1435  ! deflate and shuffle
1436  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1437 
1438  ! put attr
1439  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1440  (/fill_value/)), nc_fname)
1441  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1442  longname_l), nc_fname)
1443 
1444  ! add grid mapping and mf6 attr
1445  call ncvar_gridmap(ncid, var_id, gridmap_name, latlon, nc_fname)
1446  call ncvar_mf6attr(ncid, var_id, iper, iaux, nc_tag, nc_fname)
1447 
1448  ! exit define mode and write data
1449  call nf_verify(nf90_enddef(ncid), nc_fname)
1450  call nf_verify(nf90_put_var(ncid, var_id, p_mem, start=(/1, 1, 1/), &
1451  count=(/dis%ncol, dis%nrow, dis%nlay/)), &
1452  nc_fname)
1453  end subroutine nc_export_dbl3d
1454 
1455  !> @brief build netcdf variable name
1456  !<
1457  function export_varname(pkgname, idt, iper, iaux) result(varname)
1458  use inputoutputmodule, only: lowcase
1459  character(len=*), intent(in) :: pkgname
1460  type(inputparamdefinitiontype), pointer, intent(in) :: idt
1461  integer(I4B), optional, intent(in) :: iper
1462  integer(I4B), optional, intent(in) :: iaux
1463  character(len=LINELENGTH) :: varname
1464  character(len=LINELENGTH) :: pname, vname
1465  pname = pkgname
1466  vname = idt%mf6varname
1467  call lowcase(pname)
1468  call lowcase(vname)
1469  if (present(iper)) then
1470  if (present(iaux)) then
1471  write (varname, '(a,i0,a,i0)') trim(pname)//'_'//trim(vname)// &
1472  '_p', iper, 'a', iaux
1473  else
1474  write (varname, '(a,i0)') trim(pname)//'_'//trim(vname)//'_p', iper
1475  end if
1476  else
1477  varname = trim(pname)//'_'//trim(vname)
1478  end if
1479  end function export_varname
1480 
1481 end module disncstructuredmodule
subroutine init()
Definition: GridSorting.f90:24
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lencomponentname
maximum length of a component name
Definition: Constants.f90:18
@ mvalidate
validation mode - do not run time steps
Definition: Constants.f90:205
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
real(dp), parameter dhnoflo
real no flow constant
Definition: Constants.f90:93
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
This module contains the DefinitionSelectModule.
type(inputparamdefinitiontype) function, pointer, public get_param_definition_type(input_definition_types, component_type, subcomponent_type, blockname, tagname, filename)
Return parameter definition.
Definition: Dis.f90:1
This module contains the DisNCStructuredModule.
subroutine add_pkg_data(this)
determine packages to write gridded input
subroutine ncvar_mf6attr(ncid, varid, iper, iaux, nc_tag, nc_fname)
put variable internal modflow6 attributes
subroutine dis_export_destroy(this)
netcdf export dis destroy
character(len=linelength) function export_varname(pkgname, idt, iper, iaux)
build netcdf variable name
subroutine ncvar_gridmap(ncid, varid, gridmap_name, latlon, nc_fname)
put variable gridmap attributes
subroutine add_global_att(this)
create file (group) attributes
subroutine nc_export_int2d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, nc_fname)
netcdf export 2D integer
subroutine dis_export_init(this, modelname, modeltype, modelfname, nc_fname, disenum, nctype, iout)
netcdf export dis init
subroutine export_input_arrays(this, pkgtype, pkgname, mempath, param_dfns)
write package gridded input data
subroutine add_grid_data(this)
add grid coordinates
subroutine nc_export_dbl3d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, iper, iaux, nc_fname)
netcdf export 3D double
subroutine define_projection(this)
define grid projection variables
subroutine df(this)
netcdf export define
subroutine ncvar_chunk2d(ncid, varid, chunk_x, chunk_y, nc_fname)
define 2d variable chunking
subroutine add_proj_data(this)
add grid projection data
subroutine export_layer_3d(this, export_pkg, idt, ilayer_read, ialayer, dbl1d, nc_varname, input_attr, iaux)
export layer variable as full grid
subroutine nc_export_int3d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, nc_fname)
netcdf export 3D integer
subroutine step(this)
netcdf export step
subroutine ncvar_deflate(ncid, varid, deflate, shuffle, nc_fname)
define variable compression
subroutine nc_export_dbl1d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, iper, nc_fname)
netcdf export 1D double
subroutine nc_export_int1d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, iper, nc_fname)
netcdf export 1D integer
subroutine define_dependent(this)
create the model layer dependent variables
subroutine nc_export_dbl2d(ncid, dim_ids, var_ids, dis, p_mem, nc_varname, pkgname, tagname, shapestr, longname, nc_tag, gridmap_name, latlon, deflate, shuffle, chunk_z, chunk_y, chunk_x, nc_fname)
netcdf export 2D double
subroutine export_input_array(this, pkgtype, pkgname, mempath, idt)
netcdf export an input array
subroutine ncvar_chunk3d(ncid, varid, chunk_x, chunk_y, chunk_z, nc_fname)
define 3d variable chunking
subroutine define_dim(this)
netcdf export define dimensions
subroutine package_step(this, export_pkg)
netcdf export package dynamic input
subroutine package_step_ilayer(this, export_pkg, ilayer_varname, ilayer)
netcdf export package dynamic input with ilayer index variable
subroutine define_gridmap(this)
create the file grid mapping container variable
type(inputparamdefinitiontype) function, dimension(:), pointer, public param_definitions(component, subcomponent)
This module contains the InputDefinitionModule.
subroutine, public lowcase(word)
Convert to lower case.
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the NCModelExportModule.
Definition: NCModel.f90:8
character(len=linelength) function, public export_longname(longname, pkgname, tagname, layer, iper)
build netcdf variable longname
Definition: NCModel.f90:416
This module contains the NetCDFCommonModule.
Definition: NetCDFCommon.f90:6
subroutine, public nf_verify(res, nc_fname)
error check a netcdf-fortran interface call
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
character(len=maxcharlen) warnmsg
warning message string
integer(i4b) isim_mode
simulation mode
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
character(len=lencomponentname) function, public idm_subcomponent_type(component, subcomponent)
component from package or model type
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
Structured grid discretization.
Definition: Dis.f90:23
abstract type for model netcdf export type
Definition: NCModel.f90:101