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