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