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