MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
DisNCMesh.f90
Go to the documentation of this file.
1 !> @brief This module contains the MeshDisModelModule
2 !!
3 !! This module defines UGRID layered mesh compliant netcdf
4 !! export type for DIS models. It is dependent on netcdf
5 !! libraries.
6 !!
7 !<
9 
10  use kindmodule, only: dp, i4b, lgp
13  use simvariablesmodule, only: errmsg
22  use dismodule, only: distype
23  use netcdfcommonmodule, only: nf_verify
24  use netcdf
25 
26  implicit none
27  private
28  public :: mesh2ddisexporttype
29 
30  ! UGRID layered mesh (ULM) DIS
32  type(distype), pointer :: dis => null() !< pointer to model dis package
33  integer(I4B) :: x_dim !< ncol dimension id
34  integer(I4B) :: y_dim !< nrow dimension id
35  contains
36  procedure :: init => dis_export_init
37  procedure :: destroy => dis_export_destroy
38  procedure :: df
39  procedure :: step
40  procedure :: export_input_array
41  procedure :: package_step
42  procedure :: define_dim
43  procedure :: add_mesh_data
44  end type mesh2ddisexporttype
45 
46 contains
47 
48  !> @brief netcdf export dis init
49  !<
50  subroutine dis_export_init(this, modelname, modeltype, modelfname, nc_fname, &
51  disenum, nctype, iout)
53  class(mesh2ddisexporttype), intent(inout) :: this
54  character(len=*), intent(in) :: modelname
55  character(len=*), intent(in) :: modeltype
56  character(len=*), intent(in) :: modelfname
57  character(len=*), intent(in) :: nc_fname
58  integer(I4B), intent(in) :: disenum
59  integer(I4B), intent(in) :: nctype
60  integer(I4B), intent(in) :: iout
61 
62  ! set nlay
63  this%nlay = this%dis%nlay
64 
65  ! allocate var_id arrays
66  allocate (this%var_ids%dependent(this%nlay))
67  allocate (this%var_ids%export(this%nlay))
68 
69  ! initialize base class
70  call this%mesh_init(modelname, modeltype, modelfname, nc_fname, disenum, &
71  nctype, this%dis%lenuni, iout)
72  end subroutine dis_export_init
73 
74  !> @brief netcdf export dis destroy
75  !<
76  subroutine dis_export_destroy(this)
77  class(mesh2ddisexporttype), intent(inout) :: this
78  deallocate (this%var_ids%dependent)
79  ! destroy base class
80  call this%mesh_destroy()
81  call this%NCModelExportType%destroy()
82  end subroutine dis_export_destroy
83 
84  !> @brief netcdf export define
85  !<
86  subroutine df(this)
87  use constantsmodule, only: mvalidate
88  use simvariablesmodule, only: isim_mode
89  class(mesh2ddisexporttype), intent(inout) :: this
90  ! put root group file scope attributes
91  call this%add_global_att()
92  ! define root group dimensions and coordinate variables
93  call this%define_dim()
94  ! define mesh variables
95  call this%create_mesh()
96  if (isim_mode == mvalidate) then
97  ! define period input arrays
98  call this%df_export()
99  else
100  ! define the dependent variable
101  call this%define_dependent()
102  end if
103  ! exit define mode
104  call nf_verify(nf90_enddef(this%ncid), this%nc_fname)
105  ! create mesh
106  call this%add_mesh_data()
107  if (isim_mode == mvalidate) then
108  ! define and set package input griddata
109  call this%add_pkg_data()
110  end if
111  ! define and set gridmap variable
112  call this%define_gridmap()
113  ! synchronize file
114  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
115  end subroutine df
116 
117  !> @brief netcdf export step
118  !<
119  subroutine step(this)
120  use constantsmodule, only: dhnoflo
121  use tdismodule, only: totim
122  class(mesh2ddisexporttype), intent(inout) :: this
123  real(DP), dimension(:), pointer, contiguous :: dbl1d
124  integer(I4B) :: n, k, nvals, istp
125  integer(I4B), dimension(2) :: dis_shape
126  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
127 
128  ! initialize
129  nullify (dbl1d)
130  nullify (dbl2d)
131 
132  ! set global step index
133  istp = this%istp()
134 
135  dis_shape(1) = this%dis%ncol * this%dis%nrow
136  dis_shape(2) = this%dis%nlay
137 
138  nvals = product(dis_shape)
139 
140  ! add data to dependent variable
141  if (size(this%dis%nodeuser) < &
142  size(this%dis%nodereduced)) then
143  ! allocate nodereduced size 1d array
144  allocate (dbl1d(size(this%dis%nodereduced)))
145 
146  ! initialize DHNOFLO for non-active cells
147  dbl1d = dhnoflo
148 
149  ! update active cells
150  do n = 1, size(this%dis%nodereduced)
151  if (this%dis%nodereduced(n) > 0) then
152  dbl1d(n) = this%x(this%dis%nodereduced(n))
153  end if
154  end do
155 
156  dbl2d(1:dis_shape(1), 1:dis_shape(2)) => dbl1d(1:nvals)
157  else
158  dbl2d(1:dis_shape(1), 1:dis_shape(2)) => this%x(1:nvals)
159  end if
160 
161  do k = 1, this%dis%nlay
162  ! extend array with step data
163  call nf_verify(nf90_put_var(this%ncid, &
164  this%var_ids%dependent(k), dbl2d(:, k), &
165  start=(/1, istp/), &
166  count=(/(this%dis%ncol * this%dis%nrow), 1/)), &
167  this%nc_fname)
168  end do
169 
170  ! write to time coordinate variable
171  call nf_verify(nf90_put_var(this%ncid, this%var_ids%time, &
172  totim, start=(/istp/)), &
173  this%nc_fname)
174  ! update file
175  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
176 
177  ! cleanup
178  if (associated(dbl1d)) deallocate (dbl1d)
179  nullify (dbl1d)
180  nullify (dbl2d)
181  end subroutine step
182 
183  !> @brief netcdf export package dynamic input
184  !<
185  subroutine package_step(this, export_pkg)
186  use tdismodule, only: totim, kper
189  class(mesh2ddisexporttype), intent(inout) :: this
190  class(exportpackagetype), pointer, intent(in) :: export_pkg
191  type(inputparamdefinitiontype), pointer :: idt
192  integer(I4B), dimension(:), pointer, contiguous :: int1d
193  real(DP), dimension(:), pointer, contiguous :: dbl1d, nodes
194  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
195  character(len=LINELENGTH) :: nc_tag
196  integer(I4B) :: iaux, iparam, nvals
197  integer(I4B) :: k, n
198  integer(I4B), pointer :: nbound
199 
200  ! initialize
201  iaux = 0
202 
203  ! export defined period input
204  do iparam = 1, export_pkg%nparam
205  ! check if variable was read this period
206  if (export_pkg%param_reads(iparam)%invar < 1) cycle
207 
208  ! set input definition
209  idt => &
210  get_param_definition_type(export_pkg%mf6_input%param_dfns, &
211  export_pkg%mf6_input%component_type, &
212  export_pkg%mf6_input%subcomponent_type, &
213  'PERIOD', export_pkg%param_names(iparam), '')
214 
215  ! set variable input tag
216  nc_tag = this%input_attribute(export_pkg%mf6_input%subcomponent_name, &
217  idt)
218 
219  ! export arrays
220  select case (idt%datatype)
221  case ('INTEGER1D')
222  call mem_setptr(int1d, idt%mf6varname, export_pkg%mf6_input%mempath)
223  this%var_ids%export(1) = export_pkg%varids_param(iparam, 1)
224  call nc_export_int1d(int1d, this%ncid, this%dim_ids, this%x_dim, &
225  this%y_dim, this%var_ids, this%dis, idt, &
226  export_pkg%mf6_input%mempath, nc_tag, &
227  export_pkg%mf6_input%subcomponent_name, &
228  this%gridmap_name, this%deflate, this%shuffle, &
229  this%chunk_face, kper, this%nc_fname)
230  case ('DOUBLE1D')
231  call mem_setptr(dbl1d, idt%mf6varname, export_pkg%mf6_input%mempath)
232  select case (idt%shape)
233  case ('NCPL')
234  this%var_ids%export(1) = export_pkg%varids_param(iparam, 1)
235  call nc_export_dbl1d(dbl1d, this%ncid, this%dim_ids, this%x_dim, &
236  this%y_dim, this%var_ids, this%dis, idt, &
237  export_pkg%mf6_input%mempath, nc_tag, &
238  export_pkg%mf6_input%subcomponent_name, &
239  this%gridmap_name, this%deflate, this%shuffle, &
240  this%chunk_face, kper, iaux, this%nc_fname)
241  case ('NODES')
242  nvals = this%dis%nodesuser
243  allocate (nodes(nvals))
244  nodes = dnodata
245  do k = 1, this%dis%nlay
246  this%var_ids%export(k) = export_pkg%varids_param(iparam, k)
247  end do
248  call mem_setptr(dbl1d, idt%mf6varname, export_pkg%mf6_input%mempath)
249  call mem_setptr(int1d, 'NODEULIST', export_pkg%mf6_input%mempath)
250  call mem_setptr(nbound, 'NBOUND', export_pkg%mf6_input%mempath)
251  do n = 1, nbound
252  nodes(int1d(n)) = dbl1d(n)
253  end do
254  call nc_export_dbl1d(nodes, this%ncid, this%dim_ids, this%x_dim, &
255  this%y_dim, this%var_ids, this%dis, idt, &
256  export_pkg%mf6_input%mempath, nc_tag, &
257  export_pkg%mf6_input%subcomponent_name, &
258  this%gridmap_name, this%deflate, this%shuffle, &
259  this%chunk_face, kper, iaux, this%nc_fname)
260  deallocate (nodes)
261  case default
262  end select
263  case ('DOUBLE2D')
264  call mem_setptr(dbl2d, idt%mf6varname, export_pkg%mf6_input%mempath)
265  select case (idt%shape)
266  case ('NAUX NCPL')
267  nvals = this%dis%nrow * this%dis%ncol
268  allocate (nodes(nvals))
269  do iaux = 1, size(dbl2d, dim=1) !naux
270  this%var_ids%export(1) = export_pkg%varids_aux(iaux, 1)
271  do n = 1, nvals
272  nodes(n) = dbl2d(iaux, n)
273  end do
274  call nc_export_dbl1d(nodes, this%ncid, this%dim_ids, this%x_dim, &
275  this%y_dim, this%var_ids, this%dis, idt, &
276  export_pkg%mf6_input%mempath, nc_tag, &
277  export_pkg%mf6_input%subcomponent_name, &
278  this%gridmap_name, this%deflate, this%shuffle, &
279  this%chunk_face, kper, iaux, this%nc_fname)
280  end do
281  deallocate (nodes)
282  case ('NAUX NODES')
283  nvals = this%dis%nodesuser
284  allocate (nodes(nvals))
285  call mem_setptr(int1d, 'NODEULIST', export_pkg%mf6_input%mempath)
286  call mem_setptr(nbound, 'NBOUND', export_pkg%mf6_input%mempath)
287  do iaux = 1, size(dbl2d, dim=1) ! naux
288  nodes = dnodata
289  do k = 1, this%dis%nlay
290  this%var_ids%export(k) = export_pkg%varids_aux(iaux, k)
291  end do
292  do n = 1, nbound
293  nodes(int1d(n)) = dbl2d(iaux, n)
294  end do
295  call nc_export_dbl1d(nodes, this%ncid, this%dim_ids, this%x_dim, &
296  this%y_dim, this%var_ids, this%dis, idt, &
297  export_pkg%mf6_input%mempath, nc_tag, &
298  export_pkg%mf6_input%subcomponent_name, &
299  this%gridmap_name, this%deflate, this%shuffle, &
300  this%chunk_face, kper, iaux, this%nc_fname)
301 
302  end do
303  deallocate (nodes)
304  case default
305  end select
306  case default
307  ! no-op, no other datatypes exported
308  end select
309  end do
310 
311  ! write to time coordinate variable
312  call nf_verify(nf90_put_var(this%ncid, this%var_ids%time, &
313  totim, start=(/kper/)), &
314  this%nc_fname)
315 
316  ! synchronize file
317  call nf_verify(nf90_sync(this%ncid), this%nc_fname)
318  end subroutine package_step
319 
320  !> @brief netcdf export an input array
321  !<
322  subroutine export_input_array(this, pkgtype, pkgname, mempath, idt)
323  class(mesh2ddisexporttype), intent(inout) :: this
324  character(len=*), intent(in) :: pkgtype
325  character(len=*), intent(in) :: pkgname
326  character(len=*), intent(in) :: mempath
327  type(inputparamdefinitiontype), pointer, intent(in) :: idt
328  integer(I4B), dimension(:), pointer, contiguous :: int1d
329  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
330  integer(I4B), dimension(:, :, :), pointer, contiguous :: int3d
331  real(DP), dimension(:), pointer, contiguous :: dbl1d
332  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
333  real(DP), dimension(:, :, :), pointer, contiguous :: dbl3d
334  character(len=LINELENGTH) :: nc_tag
335  integer(I4B) :: iper, iaux
336 
337  iper = 0
338  iaux = 0
339 
340  ! set package input tag
341  nc_tag = this%input_attribute(pkgname, idt)
342 
343  select case (idt%datatype)
344  case ('INTEGER1D')
345  call mem_setptr(int1d, idt%mf6varname, mempath)
346  call nc_export_int1d(int1d, this%ncid, this%dim_ids, this%x_dim, &
347  this%y_dim, this%var_ids, this%dis, idt, mempath, &
348  nc_tag, pkgname, this%gridmap_name, this%deflate, &
349  this%shuffle, this%chunk_face, iper, this%nc_fname)
350  case ('INTEGER2D')
351  call mem_setptr(int2d, idt%mf6varname, mempath)
352  call nc_export_int2d(int2d, this%ncid, this%dim_ids, this%var_ids, &
353  this%dis, idt, mempath, nc_tag, pkgname, &
354  this%gridmap_name, this%deflate, this%shuffle, &
355  this%chunk_face, this%nc_fname)
356  case ('INTEGER3D')
357  call mem_setptr(int3d, idt%mf6varname, mempath)
358  call nc_export_int3d(int3d, this%ncid, this%dim_ids, this%var_ids, &
359  this%dis, idt, mempath, nc_tag, pkgname, &
360  this%gridmap_name, this%deflate, this%shuffle, &
361  this%chunk_face, this%nc_fname)
362  case ('DOUBLE1D')
363  call mem_setptr(dbl1d, idt%mf6varname, mempath)
364  call nc_export_dbl1d(dbl1d, this%ncid, this%dim_ids, this%x_dim, &
365  this%y_dim, this%var_ids, this%dis, idt, mempath, &
366  nc_tag, pkgname, this%gridmap_name, this%deflate, &
367  this%shuffle, this%chunk_face, iper, iaux, &
368  this%nc_fname)
369  case ('DOUBLE2D')
370  call mem_setptr(dbl2d, idt%mf6varname, mempath)
371  call nc_export_dbl2d(dbl2d, this%ncid, this%dim_ids, this%var_ids, &
372  this%dis, idt, mempath, nc_tag, pkgname, &
373  this%gridmap_name, this%deflate, this%shuffle, &
374  this%chunk_face, this%nc_fname)
375  case ('DOUBLE3D')
376  call mem_setptr(dbl3d, idt%mf6varname, mempath)
377  call nc_export_dbl3d(dbl3d, this%ncid, this%dim_ids, this%var_ids, &
378  this%dis, idt, mempath, nc_tag, pkgname, &
379  this%gridmap_name, this%deflate, this%shuffle, &
380  this%chunk_face, this%nc_fname)
381  case default
382  ! no-op, no other datatypes exported
383  end select
384  end subroutine export_input_array
385 
386  !> @brief netcdf export define dimensions
387  !<
388  subroutine define_dim(this)
389  use constantsmodule, only: mvalidate
390  use simvariablesmodule, only: isim_mode
391  class(mesh2ddisexporttype), intent(inout) :: this
392 
393  if (isim_mode /= mvalidate .or. this%pkglist%Count() > 0) then
394  ! time
395  call nf_verify(nf90_def_dim(this%ncid, 'time', this%totnstp, &
396  this%dim_ids%time), this%nc_fname)
397  call nf_verify(nf90_def_var(this%ncid, 'time', nf90_double, &
398  this%dim_ids%time, this%var_ids%time), &
399  this%nc_fname)
400  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'calendar', &
401  'standard'), this%nc_fname)
402  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'units', &
403  this%datetime), this%nc_fname)
404  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'axis', 'T'), &
405  this%nc_fname)
406  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'standard_name', &
407  'time'), this%nc_fname)
408  call nf_verify(nf90_put_att(this%ncid, this%var_ids%time, 'long_name', &
409  'time'), this%nc_fname)
410  end if
411 
412  ! mesh
413  call nf_verify(nf90_def_dim(this%ncid, 'nmesh_node', &
414  ((this%dis%ncol + 1) * (this%dis%nrow + 1)), &
415  this%dim_ids%nmesh_node), this%nc_fname)
416  call nf_verify(nf90_def_dim(this%ncid, 'nmesh_face', &
417  (this%dis%ncol * this%dis%nrow), &
418  this%dim_ids%nmesh_face), this%nc_fname)
419  call nf_verify(nf90_def_dim(this%ncid, 'max_nmesh_face_nodes', 4, &
420  this%dim_ids%max_nmesh_face_nodes), &
421  this%nc_fname)
422 
423  ! x, y
424  call nf_verify(nf90_def_dim(this%ncid, 'x', this%dis%ncol, &
425  this%x_dim), this%nc_fname)
426  call nf_verify(nf90_def_dim(this%ncid, 'y', this%dis%nrow, &
427  this%y_dim), this%nc_fname)
428  end subroutine define_dim
429 
430  !> @brief netcdf export add mesh information
431  !<
432  subroutine add_mesh_data(this)
434  class(mesh2ddisexporttype), intent(inout) :: this
435  integer(I4B) :: cnt, maxvert, m
436  integer(I4B), dimension(:), allocatable :: verts
437  real(DP), dimension(:), allocatable :: bnds
438  integer(I4B) :: i, j
439  real(DP) :: x, y, x_transform, y_transform
440  real(DP), dimension(:), allocatable :: node_x, node_y
441  real(DP), dimension(:), allocatable :: cell_x, cell_y
442 
443  ! initialize max vertices required to define cell
444  maxvert = 4
445 
446  ! set mesh container variable value to 1
447  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh, 1), &
448  this%nc_fname)
449 
450  ! allocate temporary arrays
451  allocate (verts(maxvert))
452  allocate (bnds(maxvert))
453  allocate (node_x(((this%dis%ncol + 1) * (this%dis%nrow + 1))))
454  allocate (node_y(((this%dis%ncol + 1) * (this%dis%nrow + 1))))
455  allocate (cell_x((this%dis%ncol * this%dis%nrow)))
456  allocate (cell_y((this%dis%ncol * this%dis%nrow)))
457 
458  ! set node_x and node_y arrays
459  cnt = 0
460  node_x = nf90_fill_double
461  node_y = nf90_fill_double
462  y = sum(this%dis%delc)
463  do j = this%dis%nrow, 0, -1
464  x = 0
465  do i = this%dis%ncol, 0, -1
466  cnt = cnt + 1
467  call dis_transform_xy(x, y, &
468  this%dis%xorigin, &
469  this%dis%yorigin, &
470  this%dis%angrot, &
471  x_transform, y_transform)
472  node_x(cnt) = x_transform
473  node_y(cnt) = y_transform
474  if (i > 0) x = x + this%dis%delr(i)
475  end do
476  if (j > 0) y = y - this%dis%delc(j)
477  end do
478 
479  ! write node_x and node_y arrays to netcdf file
480  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_node_x, node_x), &
481  this%nc_fname)
482  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_node_y, node_y), &
483  this%nc_fname)
484 
485  ! set cell_x and cell_y arrays
486  cnt = 1
487  cell_x = nf90_fill_double
488  cell_y = nf90_fill_double
489  do j = 1, this%dis%nrow
490  y = this%dis%celly(j)
491  do i = 1, this%dis%ncol
492  x = this%dis%cellx(i)
493  call dis_transform_xy(x, y, &
494  this%dis%xorigin, &
495  this%dis%yorigin, &
496  this%dis%angrot, &
497  x_transform, y_transform)
498  cell_x(cnt) = x_transform
499  cell_y(cnt) = y_transform
500  cnt = cnt + 1
501  end do
502  end do
503 
504  ! write face_x and face_y arrays to netcdf file
505  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_face_x, cell_x), &
506  this%nc_fname)
507  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_face_y, cell_y), &
508  this%nc_fname)
509 
510  ! set face nodes array
511  cnt = 0
512  do i = 1, this%dis%nrow
513  do j = 1, this%dis%ncol
514  cnt = cnt + 1
515  verts = nf90_fill_int
516  verts(1) = cnt + this%dis%ncol + i
517  verts(2) = cnt + this%dis%ncol + i + 1
518  if (i > 1) then
519  verts(3) = cnt + i
520  verts(4) = cnt + i - 1
521  else
522  verts(3) = cnt + 1
523  verts(4) = cnt
524  end if
525 
526  ! write face nodes array to netcdf file
527  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_face_nodes, &
528  verts, start=(/1, cnt/), &
529  count=(/maxvert, 1/)), &
530  this%nc_fname)
531 
532  ! set face y bounds array
533  bnds = nf90_fill_double
534  do m = 1, size(bnds)
535  if (verts(m) /= nf90_fill_int) then
536  bnds(m) = node_y(verts(m))
537  end if
538  ! write face y bounds array to netcdf file
539  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_face_ybnds, &
540  bnds, start=(/1, cnt/), &
541  count=(/maxvert, 1/)), &
542  this%nc_fname)
543  end do
544 
545  ! set face x bounds array
546  bnds = nf90_fill_double
547  do m = 1, size(bnds)
548  if (verts(m) /= nf90_fill_int) then
549  bnds(m) = node_x(verts(m))
550  end if
551  ! write face x bounds array to netcdf file
552  call nf_verify(nf90_put_var(this%ncid, this%var_ids%mesh_face_xbnds, &
553  bnds, start=(/1, cnt/), &
554  count=(/maxvert, 1/)), &
555  this%nc_fname)
556  end do
557  end do
558  end do
559 
560  ! cleanup
561  deallocate (bnds)
562  deallocate (verts)
563  deallocate (node_x)
564  deallocate (node_y)
565  deallocate (cell_x)
566  deallocate (cell_y)
567  end subroutine add_mesh_data
568 
569  !> @brief netcdf export 1D integer
570  !<
571  subroutine nc_export_int1d(p_mem, ncid, dim_ids, x_dim, y_dim, var_ids, dis, &
572  idt, mempath, nc_tag, pkgname, gridmap_name, &
573  deflate, shuffle, chunk_face, iper, nc_fname)
574  use tdismodule, only: kper
575  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: p_mem
576  integer(I4B), intent(in) :: ncid
577  type(meshncdimidtype), intent(inout) :: dim_ids
578  integer(I4B), intent(in) :: x_dim
579  integer(I4B), intent(in) :: y_dim
580  type(meshncvaridtype), intent(inout) :: var_ids
581  type(distype), pointer, intent(in) :: dis
582  type(inputparamdefinitiontype), pointer :: idt
583  character(len=*), intent(in) :: mempath
584  character(len=*), intent(in) :: nc_tag
585  character(len=*), intent(in) :: pkgname
586  character(len=*), intent(in) :: gridmap_name
587  integer(I4B), intent(in) :: deflate
588  integer(I4B), intent(in) :: shuffle
589  integer(I4B), intent(in) :: chunk_face
590  integer(I4B), intent(in) :: iper
591  character(len=*), intent(in) :: nc_fname
592  integer(I4B), dimension(:, :, :), pointer, contiguous :: int3d
593  integer(I4B), dimension(:), pointer, contiguous :: int1d
594  integer(I4B) :: axis_dim, nvals, k
595  integer(I4B), dimension(:), allocatable :: var_id
596  character(len=LINELENGTH) :: longname, varname
597 
598  if (idt%shape == 'NROW' .or. &
599  idt%shape == 'NCOL' .or. &
600  idt%shape == 'NCPL' .or. &
601  idt%shape == 'NAUX NCPL') then
602 
603  if (iper == 0) then
604 
605  select case (idt%shape)
606  case ('NROW')
607  axis_dim = y_dim
608  case ('NCOL')
609  axis_dim = x_dim
610  case ('NCPL', 'NAUX NCPL')
611  axis_dim = dim_ids%nmesh_face
612  end select
613 
614  ! set names
615  varname = export_varname(pkgname, idt%tagname, mempath)
616  longname = export_longname(idt%longname, pkgname, idt%tagname, mempath)
617 
618  allocate (var_id(1))
619 
620  ! reenter define mode and create variable
621  call nf_verify(nf90_redef(ncid), nc_fname)
622  call nf_verify(nf90_def_var(ncid, varname, nf90_int, &
623  (/axis_dim/), var_id(1)), &
624  nc_fname)
625 
626  ! NROW/NCOL shapes use default chunking
627  call ncvar_deflate(ncid, var_id(1), deflate, shuffle, nc_fname)
628 
629  ! put attr
630  call nf_verify(nf90_put_att(ncid, var_id(1), '_FillValue', &
631  (/nf90_fill_int/)), nc_fname)
632  call nf_verify(nf90_put_att(ncid, var_id(1), 'long_name', &
633  longname), nc_fname)
634 
635  ! add mf6 attr
636  call ncvar_mf6attr(ncid, var_id(1), 0, 0, nc_tag, nc_fname)
637 
638  ! exit define mode and write data
639  call nf_verify(nf90_enddef(ncid), nc_fname)
640  call nf_verify(nf90_put_var(ncid, var_id(1), p_mem), &
641  nc_fname)
642  else
643  nvals = dis%nrow * dis%ncol
644  call nf_verify(nf90_put_var(ncid, &
645  var_ids%export(1), p_mem, &
646  start=(/1, kper/), &
647  count=(/nvals, 1/)), nc_fname)
648  end if
649 
650  else
651  ! reshape input
652  int3d(1:dis%ncol, 1:dis%nrow, 1:dis%nlay) => p_mem(1:dis%nodesuser)
653 
654  ! set nvals as ncpl
655  nvals = dis%nrow * dis%ncol
656 
657  if (iper == 0) then
658  ! not a timeseries, create variables and write griddata
659  allocate (var_id(dis%nlay))
660 
661  ! reenter define mode and create variable
662  call nf_verify(nf90_redef(ncid), nc_fname)
663  do k = 1, dis%nlay
664  ! set names
665  varname = export_varname(pkgname, idt%tagname, mempath, &
666  layer=k)
667  longname = export_longname(idt%longname, pkgname, idt%tagname, &
668  mempath, layer=k)
669 
670  call nf_verify(nf90_def_var(ncid, varname, nf90_int, &
671  (/dim_ids%nmesh_face/), var_id(k)), &
672  nc_fname)
673 
674  ! apply chunking parameters
675  call ncvar_chunk(ncid, var_id(k), chunk_face, nc_fname)
676  ! deflate and shuffle
677  call ncvar_deflate(ncid, var_id(k), deflate, shuffle, nc_fname)
678 
679  ! put attr
680  call nf_verify(nf90_put_att(ncid, var_id(k), '_FillValue', &
681  (/nf90_fill_int/)), nc_fname)
682  call nf_verify(nf90_put_att(ncid, var_id(k), 'long_name', &
683  longname), nc_fname)
684 
685  ! add grid mapping and mf6 attr
686  call ncvar_gridmap(ncid, var_id(k), gridmap_name, nc_fname)
687  call ncvar_mf6attr(ncid, var_id(k), k, 0, nc_tag, nc_fname)
688  end do
689 
690  ! exit define mode and write data
691  call nf_verify(nf90_enddef(ncid), nc_fname)
692  do k = 1, dis%nlay
693  int1d(1:nvals) => int3d(:, :, k)
694  call nf_verify(nf90_put_var(ncid, var_id(k), int1d), nc_fname)
695  end do
696 
697  ! cleanup
698  deallocate (var_id)
699  else
700  ! timeseries, add period data
701  do k = 1, dis%nlay
702  int1d(1:nvals) => int3d(:, :, k)
703  call nf_verify(nf90_put_var(ncid, &
704  var_ids%export(k), int1d, &
705  start=(/1, kper/), &
706  count=(/nvals, 1/)), nc_fname)
707  end do
708  end if
709  end if
710  end subroutine nc_export_int1d
711 
712  !> @brief netcdf export 2D integer
713  !<
714  subroutine nc_export_int2d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, &
715  nc_tag, pkgname, gridmap_name, deflate, shuffle, &
716  chunk_face, nc_fname)
717  integer(I4B), dimension(:, :), pointer, contiguous, intent(in) :: p_mem
718  integer(I4B), intent(in) :: ncid
719  type(meshncdimidtype), intent(inout) :: dim_ids
720  type(meshncvaridtype), intent(inout) :: var_ids
721  type(distype), pointer, intent(in) :: dis
722  type(inputparamdefinitiontype), pointer :: idt
723  character(len=*), intent(in) :: mempath
724  character(len=*), intent(in) :: nc_tag
725  character(len=*), intent(in) :: pkgname
726  character(len=*), intent(in) :: gridmap_name
727  integer(I4B), intent(in) :: deflate
728  integer(I4B), intent(in) :: shuffle
729  integer(I4B), intent(in) :: chunk_face
730  character(len=*), intent(in) :: nc_fname
731  integer(I4B) :: var_id, nvals
732  integer(I4B), dimension(:), pointer, contiguous :: int1d
733  character(len=LINELENGTH) :: longname, varname
734 
735  ! set names
736  varname = export_varname(pkgname, idt%tagname, mempath)
737  longname = export_longname(idt%longname, pkgname, idt%tagname, mempath)
738 
739  ! reenter define mode and create variable
740  call nf_verify(nf90_redef(ncid), nc_fname)
741  call nf_verify(nf90_def_var(ncid, varname, nf90_int, &
742  (/dim_ids%nmesh_face/), var_id), &
743  nc_fname)
744 
745  ! apply chunking parameters
746  call ncvar_chunk(ncid, var_id, chunk_face, nc_fname)
747  ! deflate and shuffle
748  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
749 
750  ! put attr
751  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
752  (/nf90_fill_int/)), nc_fname)
753  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
754  longname), nc_fname)
755 
756  ! add grid mapping and mf6 attr
757  call ncvar_gridmap(ncid, var_id, gridmap_name, nc_fname)
758  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
759 
760  ! exit define mode and write data
761  call nf_verify(nf90_enddef(ncid), nc_fname)
762  nvals = dis%nrow * dis%ncol
763  int1d(1:nvals) => p_mem
764  call nf_verify(nf90_put_var(ncid, var_id, int1d), nc_fname)
765  end subroutine nc_export_int2d
766 
767  !> @brief netcdf export 3D integer
768  !<
769  subroutine nc_export_int3d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, &
770  nc_tag, pkgname, gridmap_name, deflate, shuffle, &
771  chunk_face, nc_fname)
772  integer(I4B), dimension(:, :, :), pointer, contiguous, intent(in) :: p_mem
773  integer(I4B), intent(in) :: ncid
774  type(meshncdimidtype), intent(inout) :: dim_ids
775  type(meshncvaridtype), intent(inout) :: var_ids
776  type(distype), pointer, intent(in) :: dis
777  type(inputparamdefinitiontype), pointer :: idt
778  character(len=*), intent(in) :: mempath
779  character(len=*), intent(in) :: nc_tag
780  character(len=*), intent(in) :: pkgname
781  character(len=*), intent(in) :: gridmap_name
782  integer(I4B), intent(in) :: deflate
783  integer(I4B), intent(in) :: shuffle
784  integer(I4B), intent(in) :: chunk_face
785  character(len=*), intent(in) :: nc_fname
786  integer(I4B), dimension(:), allocatable :: var_id
787  integer(I4B), dimension(:), pointer, contiguous :: int1d
788  character(len=LINELENGTH) :: longname, varname
789  integer(I4B) :: k, nvals
790 
791  allocate (var_id(dis%nlay))
792 
793  ! reenter define mode and create variable
794  call nf_verify(nf90_redef(ncid), nc_fname)
795  do k = 1, dis%nlay
796  ! set names
797  varname = export_varname(pkgname, idt%tagname, mempath, layer=k)
798  longname = export_longname(idt%longname, pkgname, idt%tagname, &
799  mempath, layer=k)
800 
801  call nf_verify(nf90_def_var(ncid, varname, nf90_int, &
802  (/dim_ids%nmesh_face/), var_id(k)), &
803  nc_fname)
804 
805  ! apply chunking parameters
806  call ncvar_chunk(ncid, var_id(k), chunk_face, nc_fname)
807  ! deflate and shuffle
808  call ncvar_deflate(ncid, var_id(k), deflate, shuffle, nc_fname)
809 
810  ! put attr
811  call nf_verify(nf90_put_att(ncid, var_id(k), '_FillValue', &
812  (/nf90_fill_int/)), nc_fname)
813  call nf_verify(nf90_put_att(ncid, var_id(k), 'long_name', &
814  longname), nc_fname)
815 
816  ! add grid mapping and mf6 attr
817  call ncvar_gridmap(ncid, var_id(k), gridmap_name, nc_fname)
818  call ncvar_mf6attr(ncid, var_id(k), k, 0, nc_tag, nc_fname)
819  end do
820 
821  ! exit define mode and write data
822  call nf_verify(nf90_enddef(ncid), nc_fname)
823  nvals = dis%nrow * dis%ncol
824  do k = 1, dis%nlay
825  int1d(1:nvals) => p_mem(:, :, k)
826  call nf_verify(nf90_put_var(ncid, var_id(k), int1d), nc_fname)
827  end do
828 
829  ! cleanup
830  deallocate (var_id)
831  end subroutine nc_export_int3d
832 
833  !> @brief netcdf export 1D double
834  !<
835  subroutine nc_export_dbl1d(p_mem, ncid, dim_ids, x_dim, y_dim, var_ids, dis, &
836  idt, mempath, nc_tag, pkgname, gridmap_name, &
837  deflate, shuffle, chunk_face, iper, iaux, nc_fname)
838  use tdismodule, only: kper
839  real(DP), dimension(:), pointer, contiguous, intent(in) :: p_mem
840  integer(I4B), intent(in) :: ncid
841  type(meshncdimidtype), intent(inout) :: dim_ids
842  integer(I4B), intent(in) :: x_dim
843  integer(I4B), intent(in) :: y_dim
844  type(meshncvaridtype), intent(in) :: var_ids
845  type(distype), pointer, intent(in) :: dis
846  type(inputparamdefinitiontype), pointer :: idt
847  character(len=*), intent(in) :: mempath
848  character(len=*), intent(in) :: nc_tag
849  character(len=*), intent(in) :: pkgname
850  character(len=*), intent(in) :: gridmap_name
851  integer(I4B), intent(in) :: deflate
852  integer(I4B), intent(in) :: shuffle
853  integer(I4B), intent(in) :: chunk_face
854  integer(I4B), intent(in) :: iper
855  integer(I4B), intent(in) :: iaux
856  character(len=*), intent(in) :: nc_fname
857  real(DP), dimension(:, :, :), pointer, contiguous :: dbl3d
858  real(DP), dimension(:), pointer, contiguous :: dbl1d
859  integer(I4B) :: axis_dim, nvals, k
860  integer(NF90_INT), dimension(:), allocatable :: var_id
861  character(len=LINELENGTH) :: longname, varname
862 
863  if (idt%shape == 'NROW' .or. &
864  idt%shape == 'NCOL' .or. &
865  idt%shape == 'NCPL' .or. &
866  idt%shape == 'NAUX NCPL') then
867 
868  if (iper == 0) then
869 
870  select case (idt%shape)
871  case ('NROW')
872  axis_dim = y_dim
873  case ('NCOL')
874  axis_dim = x_dim
875  case ('NCPL', 'NAUX NCPL')
876  axis_dim = dim_ids%nmesh_face
877  end select
878 
879  ! set names
880  varname = export_varname(pkgname, idt%tagname, mempath, iaux=iaux)
881  longname = export_longname(idt%longname, pkgname, idt%tagname, &
882  mempath, iaux=iaux)
883 
884  allocate (var_id(1))
885 
886  ! reenter define mode and create variable
887  call nf_verify(nf90_redef(ncid), nc_fname)
888  call nf_verify(nf90_def_var(ncid, varname, nf90_double, &
889  (/axis_dim/), var_id(1)), &
890  nc_fname)
891 
892  ! NROW/NCOL shapes use default chunking
893  call ncvar_deflate(ncid, var_id(1), deflate, shuffle, nc_fname)
894 
895  ! put attr
896  call nf_verify(nf90_put_att(ncid, var_id(1), '_FillValue', &
897  (/nf90_fill_double/)), nc_fname)
898  call nf_verify(nf90_put_att(ncid, var_id(1), 'long_name', &
899  longname), nc_fname)
900 
901  ! add mf6 attr
902  call ncvar_mf6attr(ncid, var_id(1), 0, iaux, nc_tag, nc_fname)
903 
904  ! exit define mode and write data
905  call nf_verify(nf90_enddef(ncid), nc_fname)
906  call nf_verify(nf90_put_var(ncid, var_id(1), p_mem), &
907  nc_fname)
908  else
909  nvals = dis%nrow * dis%ncol
910  call nf_verify(nf90_put_var(ncid, &
911  var_ids%export(1), p_mem, &
912  start=(/1, kper/), &
913  count=(/nvals, 1/)), nc_fname)
914  end if
915 
916  else
917  ! reshape input
918  dbl3d(1:dis%ncol, 1:dis%nrow, 1:dis%nlay) => p_mem(1:dis%nodesuser)
919 
920  ! set nvals as ncpl
921  nvals = dis%nrow * dis%ncol
922 
923  if (iper == 0) then
924  ! not a timeseries, create variables and write griddata
925 
926  ! allocate local variable id storage
927  allocate (var_id(dis%nlay))
928 
929  ! reenter define mode and create layer variables
930  call nf_verify(nf90_redef(ncid), nc_fname)
931  do k = 1, dis%nlay
932  ! set names
933  varname = export_varname(pkgname, idt%tagname, mempath, layer=k, &
934  iaux=iaux)
935  longname = export_longname(idt%longname, pkgname, idt%tagname, &
936  mempath, layer=k, iaux=iaux)
937 
938  ! create layer variable
939  call nf_verify(nf90_def_var(ncid, varname, nf90_double, &
940  (/dim_ids%nmesh_face/), var_id(k)), &
941  nc_fname)
942 
943  ! apply chunking parameters
944  call ncvar_chunk(ncid, var_id(k), chunk_face, nc_fname)
945  ! deflate and shuffle
946  call ncvar_deflate(ncid, var_id(k), deflate, shuffle, nc_fname)
947 
948  ! put attr
949  call nf_verify(nf90_put_att(ncid, var_id(k), '_FillValue', &
950  (/nf90_fill_double/)), nc_fname)
951  call nf_verify(nf90_put_att(ncid, var_id(k), 'long_name', &
952  longname), nc_fname)
953 
954  ! add grid mapping and mf6 attr
955  call ncvar_gridmap(ncid, var_id(k), gridmap_name, nc_fname)
956  call ncvar_mf6attr(ncid, var_id(k), k, iaux, nc_tag, nc_fname)
957  end do
958 
959  ! exit define mode
960  call nf_verify(nf90_enddef(ncid), nc_fname)
961 
962  ! write layer data
963  do k = 1, dis%nlay
964  dbl1d(1:nvals) => dbl3d(:, :, k)
965  call nf_verify(nf90_put_var(ncid, var_id(k), dbl1d), nc_fname)
966  end do
967 
968  ! cleanup
969  deallocate (var_id)
970  else
971  ! timeseries, add period data
972  do k = 1, dis%nlay
973  dbl1d(1:nvals) => dbl3d(:, :, k)
974  call nf_verify(nf90_put_var(ncid, &
975  var_ids%export(k), dbl1d, &
976  start=(/1, kper/), &
977  count=(/nvals, 1/)), nc_fname)
978  end do
979  end if
980  end if
981  end subroutine nc_export_dbl1d
982 
983  !> @brief netcdf export 2D double
984  !<
985  subroutine nc_export_dbl2d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, &
986  nc_tag, pkgname, gridmap_name, deflate, shuffle, &
987  chunk_face, nc_fname)
988  real(DP), dimension(:, :), pointer, contiguous, intent(in) :: p_mem
989  integer(I4B), intent(in) :: ncid
990  type(meshncdimidtype), intent(inout) :: dim_ids
991  type(meshncvaridtype), intent(inout) :: var_ids
992  type(distype), pointer, intent(in) :: dis
993  type(inputparamdefinitiontype), pointer :: idt
994  character(len=*), intent(in) :: mempath
995  character(len=*), intent(in) :: nc_tag
996  character(len=*), intent(in) :: pkgname
997  character(len=*), intent(in) :: gridmap_name
998  integer(I4B), intent(in) :: deflate
999  integer(I4B), intent(in) :: shuffle
1000  integer(I4B), intent(in) :: chunk_face
1001  character(len=*), intent(in) :: nc_fname
1002  integer(I4B) :: var_id, nvals
1003  character(len=LINELENGTH) :: longname, varname
1004  real(DP), dimension(:), pointer, contiguous :: dbl1d
1005 
1006  ! set names
1007  varname = export_varname(pkgname, idt%tagname, mempath)
1008  longname = export_longname(idt%longname, pkgname, idt%tagname, mempath)
1009 
1010  ! reenter define mode and create variable
1011  call nf_verify(nf90_redef(ncid), nc_fname)
1012  call nf_verify(nf90_def_var(ncid, varname, nf90_double, &
1013  (/dim_ids%nmesh_face/), var_id), &
1014  nc_fname)
1015 
1016  ! apply chunking parameters
1017  call ncvar_chunk(ncid, var_id, chunk_face, nc_fname)
1018  ! deflate and shuffle
1019  call ncvar_deflate(ncid, var_id, deflate, shuffle, nc_fname)
1020 
1021  ! put attr
1022  call nf_verify(nf90_put_att(ncid, var_id, '_FillValue', &
1023  (/nf90_fill_double/)), nc_fname)
1024  call nf_verify(nf90_put_att(ncid, var_id, 'long_name', &
1025  longname), nc_fname)
1026 
1027  ! add grid mapping and mf6 attr
1028  call ncvar_gridmap(ncid, var_id, gridmap_name, nc_fname)
1029  call ncvar_mf6attr(ncid, var_id, 0, 0, nc_tag, nc_fname)
1030 
1031  ! exit define mode and write data
1032  call nf_verify(nf90_enddef(ncid), nc_fname)
1033  nvals = dis%nrow * dis%ncol
1034  dbl1d(1:nvals) => p_mem
1035  call nf_verify(nf90_put_var(ncid, var_id, dbl1d), nc_fname)
1036  end subroutine nc_export_dbl2d
1037 
1038  !> @brief netcdf export 3D double
1039  !<
1040  subroutine nc_export_dbl3d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, &
1041  nc_tag, pkgname, gridmap_name, deflate, shuffle, &
1042  chunk_face, nc_fname)
1043  real(DP), dimension(:, :, :), pointer, contiguous, intent(in) :: p_mem
1044  integer(I4B), intent(in) :: ncid
1045  type(meshncdimidtype), intent(inout) :: dim_ids
1046  type(meshncvaridtype), intent(inout) :: var_ids
1047  type(distype), pointer, intent(in) :: dis
1048  type(inputparamdefinitiontype), pointer :: idt
1049  character(len=*), intent(in) :: mempath
1050  character(len=*), intent(in) :: nc_tag
1051  character(len=*), intent(in) :: pkgname
1052  character(len=*), intent(in) :: gridmap_name
1053  integer(I4B), intent(in) :: deflate
1054  integer(I4B), intent(in) :: shuffle
1055  integer(I4B), intent(in) :: chunk_face
1056  character(len=*), intent(in) :: nc_fname
1057  integer(I4B), dimension(:), allocatable :: var_id
1058  real(DP), dimension(:), pointer, contiguous :: dbl1d
1059  character(len=LINELENGTH) :: longname, varname
1060  integer(I4B) :: k, nvals
1061 
1062  ! set nvals as ncpl
1063  nvals = dis%nrow * dis%ncol
1064 
1065  allocate (var_id(dis%nlay))
1066 
1067  ! reenter define mode and create variable
1068  call nf_verify(nf90_redef(ncid), nc_fname)
1069  do k = 1, dis%nlay
1070  ! set names
1071  varname = export_varname(pkgname, idt%tagname, mempath, layer=k)
1072  longname = export_longname(idt%longname, pkgname, idt%tagname, &
1073  mempath, layer=k)
1074 
1075  call nf_verify(nf90_def_var(ncid, varname, nf90_double, &
1076  (/dim_ids%nmesh_face/), var_id(k)), &
1077  nc_fname)
1078 
1079  ! apply chunking parameters
1080  call ncvar_chunk(ncid, var_id(k), chunk_face, nc_fname)
1081  ! deflate and shuffle
1082  call ncvar_deflate(ncid, var_id(k), deflate, shuffle, nc_fname)
1083 
1084  ! put attr
1085  call nf_verify(nf90_put_att(ncid, var_id(k), '_FillValue', &
1086  (/nf90_fill_double/)), nc_fname)
1087  call nf_verify(nf90_put_att(ncid, var_id(k), 'long_name', &
1088  longname), nc_fname)
1089 
1090  ! add grid mapping and mf6 attr
1091  call ncvar_gridmap(ncid, var_id(k), gridmap_name, nc_fname)
1092  call ncvar_mf6attr(ncid, var_id(k), k, 0, nc_tag, nc_fname)
1093  end do
1094 
1095  ! exit define mode and write data
1096  call nf_verify(nf90_enddef(ncid), nc_fname)
1097  do k = 1, dis%nlay
1098  dbl1d(1:nvals) => p_mem(:, :, k)
1099  call nf_verify(nf90_put_var(ncid, var_id(k), dbl1d), nc_fname)
1100  end do
1101 
1102  ! cleanup
1103  deallocate (var_id)
1104  end subroutine nc_export_dbl3d
1105 
1106 end module meshdismodelmodule
subroutine init()
Definition: GridSorting.f90:25
subroutine, public dis_transform_xy(x, y, xorigin, yorigin, angrot, xglo, yglo)
Get global (x, y) coordinates from cell-local coordinates.
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 InputDefinitionModule.
This module defines variable data types.
Definition: kind.f90:8
This module contains the MeshDisModelModule.
Definition: DisNCMesh.f90:8
subroutine nc_export_dbl2d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, nc_fname)
netcdf export 2D double
Definition: DisNCMesh.f90:988
subroutine nc_export_int1d(p_mem, ncid, dim_ids, x_dim, y_dim, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, iper, nc_fname)
netcdf export 1D integer
Definition: DisNCMesh.f90:574
subroutine define_dim(this)
netcdf export define dimensions
Definition: DisNCMesh.f90:389
subroutine add_mesh_data(this)
netcdf export add mesh information
Definition: DisNCMesh.f90:433
subroutine nc_export_dbl3d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, nc_fname)
netcdf export 3D double
Definition: DisNCMesh.f90:1043
subroutine nc_export_int2d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, nc_fname)
netcdf export 2D integer
Definition: DisNCMesh.f90:717
subroutine dis_export_init(this, modelname, modeltype, modelfname, nc_fname, disenum, nctype, iout)
netcdf export dis init
Definition: DisNCMesh.f90:52
subroutine step(this)
netcdf export step
Definition: DisNCMesh.f90:120
subroutine package_step(this, export_pkg)
netcdf export package dynamic input
Definition: DisNCMesh.f90:186
subroutine dis_export_destroy(this)
netcdf export dis destroy
Definition: DisNCMesh.f90:77
subroutine nc_export_int3d(p_mem, ncid, dim_ids, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, nc_fname)
netcdf export 3D integer
Definition: DisNCMesh.f90:772
subroutine nc_export_dbl1d(p_mem, ncid, dim_ids, x_dim, y_dim, var_ids, dis, idt, mempath, nc_tag, pkgname, gridmap_name, deflate, shuffle, chunk_face, iper, iaux, nc_fname)
netcdf export 1D double
Definition: DisNCMesh.f90:838
subroutine export_input_array(this, pkgtype, pkgname, mempath, idt)
netcdf export an input array
Definition: DisNCMesh.f90:323
subroutine df(this)
netcdf export define
Definition: DisNCMesh.f90:87
This module contains the MeshModelModule.
Definition: MeshNCModel.f90:7
subroutine, public ncvar_mf6attr(ncid, varid, layer, iaux, nc_tag, nc_fname)
put variable internal attributes
subroutine, public ncvar_gridmap(ncid, varid, gridmap_name, nc_fname)
put variable gridmap attributes
subroutine, public ncvar_chunk(ncid, varid, chunk_face, nc_fname)
define variable chunking
subroutine, public ncvar_deflate(ncid, varid, deflate, shuffle, nc_fname)
define variable compression
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_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
integer(i4b) isim_mode
simulation mode
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
type for storing model export dimension ids
Definition: MeshNCModel.f90:33
type for storing model export variable ids
Definition: MeshNCModel.f90:43