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