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