MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
NCModel.f90
Go to the documentation of this file.
1 !> @brief This module contains the NCModelExportModule
2 !!
3 !! This module defines a model export and base type for
4 !! supported netcdf files and is not dependent on
5 !! netcdf libraries.
6 !!
7 !<
9 
10  use kindmodule, only: dp, i4b, lgp
13  dis, disu, disv
19  use listmodule, only: listtype
20 
21  implicit none
22  private
24  public :: ncexportannotation
25  public :: exportpackagetype
27  public :: export_longname
28 
29  !> @brief netcdf export types enumerator
30  !<
31  ENUM, BIND(C)
32  ENUMERATOR :: netcdf_undef = 0 !< undefined netcdf export type
33  ENUMERATOR :: netcdf_structured = 1 !< netcdf structrured export
34  ENUMERATOR :: netcdf_mesh2d = 2 !< netcdf ugrid layered mesh export
35  END ENUM
36 
38  type(modflowinputtype) :: mf6_input !< description of modflow6 input
39  character(len=LINELENGTH), dimension(:), allocatable :: param_names !< dynamic param tagnames
40  type(readstatevartype), dimension(:), allocatable :: param_reads !< param read states
41  integer(I4B), dimension(:), pointer, contiguous :: mshape => null() !< model shape
42  integer(I4B), pointer :: iper !< most recent package rp load
43  integer(I4B) :: iper_export !< most recent period of netcdf package export
44  integer(I4B) :: nparam !< number of in scope params
45  contains
46  procedure :: init => epkg_init
47  procedure :: destroy => epkg_destroy
48  end type exportpackagetype
49 
50  !> @brief netcdf export attribute annotations
51  !<
53  character(len=LINELENGTH) :: title !< file scoped title attribute
54  character(len=LINELENGTH) :: model !< file scoped model attribute
55  character(len=LINELENGTH) :: grid !< grid type
56  character(len=LINELENGTH) :: history !< file scoped history attribute
57  character(len=LINELENGTH) :: source !< file scoped source attribute
58  character(len=LINELENGTH) :: conventions !< file scoped conventions attribute
59  character(len=LINELENGTH) :: stdname !< dependent variable standard name
60  character(len=LINELENGTH) :: longname !< dependent variable long name
61  contains
62  procedure :: set
63  end type ncexportannotation
64 
65  !> @brief base class for an export model
66  !<
68  type(listtype) :: pkglist
69  character(len=LENMODELNAME) :: modelname !< name of model
70  character(len=LENCOMPONENTNAME) :: modeltype !< type of model
71  character(len=LINELENGTH) :: modelfname !< name of model input file
72  character(len=LINELENGTH) :: nc_fname !< name of netcdf export file
73  character(len=LINELENGTH) :: gridmap_name !< name of grid mapping variable
74  character(len=LINELENGTH) :: mesh_name = 'mesh' !< name of mesh container variable
75  character(len=LENMEMPATH) :: dis_mempath !< discretization input mempath
76  character(len=LENMEMPATH) :: ncf_mempath !< netcdf utility package input mempath
77  character(len=LENBIGLINE) :: wkt !< wkt user string
78  character(len=LINELENGTH) :: datetime !< export file creation time
79  character(len=LINELENGTH) :: xname !< dependent variable name
80  type(ncexportannotation) :: annotation !< export file annotation
81  real(dp), dimension(:), pointer, contiguous :: x !< dependent variable pointer
82  integer(I4B) :: disenum !< type of discretization
83  integer(I4B) :: ncid !< netcdf file descriptor
84  integer(I4B) :: stepcnt !< simulation step count
85  integer(I4B) :: totnstp !< simulation total number of steps
86  integer(I4B), pointer :: deflate !< variable deflate level
87  integer(I4B), pointer :: shuffle !< variable shuffle filter
88  integer(I4B), pointer :: input_attr !< assign variable input attr
89  integer(I4B), pointer :: chunk_time !< chunking parameter for time dimension
90  integer(I4B) :: iout !< lst file descriptor
91  logical(LGP) :: chunking_active !< have chunking parameters been provided
92  contains
93  procedure :: init => export_init
94  procedure :: get => export_get
95  procedure :: input_attribute
96  procedure :: destroy => export_destroy
97  end type ncmodelexporttype
98 
99  !> @brief abstract type for model netcdf export type
100  !<
101  type, abstract, extends(ncmodelexporttype) :: ncbasemodelexporttype
102  contains
103  procedure :: export_input
104  procedure(model_define), deferred :: df
105  procedure(model_step), deferred :: step
106  procedure(package_export), deferred :: package_step
107  procedure(package_export_ilayer), deferred :: package_step_ilayer
108  end type ncbasemodelexporttype
109 
110  !> @brief abstract interfaces for model netcdf export type
111  !<
112  abstract interface
113  subroutine model_define(this)
114  import ncbasemodelexporttype
115  class(ncbasemodelexporttype), intent(inout) :: this
116  end subroutine
117  subroutine model_step(this)
118  import ncbasemodelexporttype
119  class(ncbasemodelexporttype), intent(inout) :: this
120  end subroutine
121  subroutine package_export(this, export_pkg)
123  class(ncbasemodelexporttype), intent(inout) :: this
124  class(exportpackagetype), pointer, intent(in) :: export_pkg
125  end subroutine
126  subroutine package_export_ilayer(this, export_pkg, ilayer_varname, &
127  ilayer)
129  class(ncbasemodelexporttype), intent(inout) :: this
130  class(exportpackagetype), pointer, intent(in) :: export_pkg
131  character(len=*), intent(in) :: ilayer_varname
132  integer(I4B), intent(in) :: ilayer
133  end subroutine
134  end interface
135 
136 contains
137 
138  !> @brief initialize dynamic package export object
139  !<
140  subroutine epkg_init(this, mf6_input, mshape, param_names, &
141  nparam)
146  class(exportpackagetype), intent(inout) :: this
147  type(modflowinputtype), intent(in) :: mf6_input
148  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: mshape !< model shape
149  character(len=LINELENGTH), dimension(:), allocatable, &
150  intent(in) :: param_names
151  integer(I4B), intent(in) :: nparam
152  integer(I4B) :: n
153  character(len=LENVARNAME) :: rs_varname
154  character(len=LENMEMPATH) :: input_mempath
155  integer(I4B), pointer :: rsvar
156 
157  this%mf6_input = mf6_input
158  this%mshape => mshape
159  this%nparam = nparam
160  this%iper_export = 0
161 
162  input_mempath = create_mem_path(component=mf6_input%component_name, &
163  subcomponent=mf6_input%subcomponent_name, &
164  context=idm_context)
165 
166  ! allocate param arrays
167  allocate (this%param_names(nparam))
168  allocate (this%param_reads(nparam))
169 
170  ! set param arrays
171  do n = 1, nparam
172  this%param_names(n) = param_names(n)
173  rs_varname = rsv_name(param_names(n))
174  call mem_setptr(rsvar, rs_varname, mf6_input%mempath)
175  this%param_reads(n)%invar => rsvar
176  end do
177 
178  ! set pointer to loaded input period
179  call mem_setptr(this%iper, 'IPER', mf6_input%mempath)
180  end subroutine epkg_init
181 
182  !> @brief destroy dynamic package export object
183  !<
184  subroutine epkg_destroy(this)
186  class(exportpackagetype), intent(inout) :: this
187  if (allocated(this%param_names)) deallocate (this%param_names)
188  end subroutine epkg_destroy
189 
190  !> @brief set netcdf file scoped attributes
191  !<
192  subroutine set(this, modelname, modeltype, modelfname, nctype)
193  use versionmodule, only: version
194  class(ncexportannotation), intent(inout) :: this
195  character(len=*), intent(in) :: modelname
196  character(len=*), intent(in) :: modeltype
197  character(len=*), intent(in) :: modelfname
198  integer(I4B), intent(in) :: nctype
199  character(len=LINELENGTH) :: fullname
200  integer :: values(8)
201 
202  this%title = ''
203  this%model = ''
204  this%grid = ''
205  this%history = ''
206  this%source = ''
207  this%conventions = ''
208  this%stdname = ''
209  this%longname = ''
210 
211  ! set file conventions
212  this%conventions = 'CF-1.11'
213  if (nctype == netcdf_mesh2d) this%conventions = &
214  trim(this%conventions)//' UGRID-1.0'
215 
216  ! set model specific attributes
217  select case (modeltype)
218  case ('GWF')
219  fullname = 'Groundwater Flow'
220  this%title = trim(modelname)//' hydraulic head'
221  this%longname = 'head'
222  case ('GWT')
223  fullname = 'Groundwater Transport'
224  this%title = trim(modelname)//' concentration'
225  this%longname = 'concentration'
226  case ('GWE')
227  fullname = 'Groundwater Energy'
228  this%title = trim(modelname)//' temperature'
229  this%longname = 'temperature'
230  case default
231  errmsg = trim(modeltype)//' models not supported for NetCDF export.'
232  call store_error(errmsg)
233  call store_error_filename(modelfname)
234  end select
235 
236  if (isim_mode == mvalidate) then
237  this%title = trim(this%title)//' array input'
238  end if
239 
240  ! set export type
241  if (nctype == netcdf_mesh2d) then
242  this%grid = 'LAYERED MESH'
243  else if (nctype == netcdf_structured) then
244  this%grid = 'STRUCTURED'
245  end if
246 
247  ! model description string
248  this%model = trim(modelname)//': MODFLOW 6 '//trim(fullname)// &
249  ' ('//trim(modeltype)//') model'
250 
251  ! modflow6 version string
252  this%source = 'MODFLOW 6 '//trim(adjustl(version))
253 
254  ! create timestamp
255  call date_and_time(values=values)
256  write (this%history, '(a,i0,a,i0,a,i0,a,i0,a,i0,a,i0,a,i0)') &
257  'first created ', values(1), '/', values(2), '/', values(3), ' ', &
258  values(5), ':', values(6), ':', values(7), '.', values(8)
259  end subroutine set
260 
261  !> @brief initialization of model netcdf export
262  !<
263  subroutine export_init(this, modelname, modeltype, modelfname, nc_fname, &
264  disenum, nctype, iout)
265  use tdismodule, only: datetime0, nstp
269  use inputoutputmodule, only: lowcase
271  class(ncmodelexporttype), intent(inout) :: this
272  character(len=*), intent(in) :: modelname
273  character(len=*), intent(in) :: modeltype
274  character(len=*), intent(in) :: modelfname
275  character(len=*), intent(in) :: nc_fname
276  integer(I4B), intent(in) :: disenum
277  integer(I4B), intent(in) :: nctype
278  integer(I4B), intent(in) :: iout
279  character(len=LENMEMPATH) :: model_mempath
280  type(utlncfparamfoundtype) :: ncf_found
281  logical(LGP) :: found_mempath
282 
283  ! allocate
284  allocate (this%deflate)
285  allocate (this%shuffle)
286  allocate (this%input_attr)
287  allocate (this%chunk_time)
288 
289  ! initialize
290  this%modelname = modelname
291  this%modeltype = modeltype
292  this%modelfname = modelfname
293  this%nc_fname = nc_fname
294  this%gridmap_name = ''
295  this%ncf_mempath = ''
296  this%wkt = ''
297  this%datetime = ''
298  this%xname = ''
299  this%disenum = disenum
300  this%ncid = 0
301  this%stepcnt = 0
302  this%totnstp = 0
303  this%deflate = -1
304  this%shuffle = 0
305  this%input_attr = 1
306  this%chunk_time = -1
307  this%iout = iout
308  this%chunking_active = .false.
309 
310  ! set file scoped attributes
311  call this%annotation%set(modelname, modeltype, modelfname, nctype)
312 
313  ! set dependent variable basename
314  select case (modeltype)
315  case ('GWF')
316  this%xname = 'head'
317  case ('GWT')
318  this%xname = 'concentration'
319  case ('GWE')
320  this%xname = 'temperature'
321  case default
322  errmsg = trim(modeltype)//' models not supported for NetCDF export.'
323  call store_error(errmsg)
324  call store_error_filename(modelfname)
325  end select
326 
327  ! set discretization input mempath
328  if (disenum == dis) then
329  this%dis_mempath = create_mem_path(modelname, 'DIS', idm_context)
330  else if (disenum == disu) then
331  this%dis_mempath = create_mem_path(modelname, 'DISU', idm_context)
332  else if (disenum == disv) then
333  this%dis_mempath = create_mem_path(modelname, 'DISV', idm_context)
334  end if
335 
336  ! set dependent variable pointer
337  model_mempath = create_mem_path(component=modelname)
338  call mem_setptr(this%x, 'X', model_mempath)
339 
340  ! set ncf_mempath if provided
341  call mem_set_value(this%ncf_mempath, 'NCF6_MEMPATH', this%dis_mempath, &
342  found_mempath)
343 
344  if (found_mempath) then
345  call mem_set_value(this%wkt, 'WKT', this%ncf_mempath, &
346  ncf_found%wkt)
347  call mem_set_value(this%deflate, 'DEFLATE', this%ncf_mempath, &
348  ncf_found%deflate)
349  call mem_set_value(this%shuffle, 'SHUFFLE', this%ncf_mempath, &
350  ncf_found%shuffle)
351  call mem_set_value(this%input_attr, 'ATTR_OFF', this%ncf_mempath, &
352  ncf_found%attr_off)
353  call mem_set_value(this%chunk_time, 'CHUNK_TIME', this%ncf_mempath, &
354  ncf_found%chunk_time)
355  end if
356 
357  if (ncf_found%wkt) then
358  this%gridmap_name = 'projection'
359  end if
360 
361  ! ATTR_OFF turns off modflow 6 input attributes
362  if (ncf_found%attr_off) then
363  this%input_attr = 0
364  end if
365 
366  ! set datetime string
367  if (datetime0 /= '') then
368  this%datetime = 'days since '//trim(datetime0)
369  else
370  ! January 1, 1970 at 00:00:00 UTC
371  this%datetime = 'days since 1970-01-01T00:00:00'
372  end if
373 
374  ! set total nstp
375  this%totnstp = sum(nstp)
376  end subroutine export_init
377 
378  !> @brief retrieve dynamic export object from package list
379  !<
380  function export_get(this, idx) result(res)
381  use listmodule, only: listtype
382  class(ncmodelexporttype), intent(inout) :: this
383  integer(I4B), intent(in) :: idx
384  class(exportpackagetype), pointer :: res
385  class(*), pointer :: obj
386  nullify (res)
387  obj => this%pkglist%GetItem(idx)
388  if (associated(obj)) then
389  select type (obj)
390  class is (exportpackagetype)
391  res => obj
392  end select
393  end if
394  end function export_get
395 
396  !> @brief build modflow6_input attribute string
397  !<
398  function input_attribute(this, pkgname, idt) result(attr)
399  use inputoutputmodule, only: lowcase
402  class(ncmodelexporttype), intent(inout) :: this
403  character(len=*), intent(in) :: pkgname
404  type(inputparamdefinitiontype), pointer, intent(in) :: idt
405  character(len=LINELENGTH) :: attr
406  attr = ''
407  if (this%input_attr > 0) then
408  attr = trim(this%modelname)//mempathseparator//trim(pkgname)// &
409  mempathseparator//trim(idt%mf6varname)
410  end if
411  end function input_attribute
412 
413  !> @brief build netcdf variable longname
414  !<
415  function export_longname(longname, pkgname, tagname, layer, iper) result(lname)
416  use inputoutputmodule, only: lowcase
417  character(len=*), intent(in) :: longname
418  character(len=*), intent(in) :: pkgname
419  character(len=*), intent(in) :: tagname
420  integer(I4B), intent(in) :: layer
421  integer(I4B), optional, intent(in) :: iper
422  character(len=LINELENGTH) :: lname
423  character(len=LINELENGTH) :: pname, vname
424  pname = pkgname
425  vname = tagname
426  call lowcase(pname)
427  call lowcase(vname)
428  if (longname == '') then
429  lname = trim(pname)//' '//trim(vname)
430  else
431  lname = longname
432  end if
433  if (layer > 0) then
434  write (lname, '(a,i0)') trim(lname)//' layer=', layer
435  end if
436  if (present(iper)) then
437  if (iper > 0) then
438  write (lname, '(a,i0)') trim(lname)//' period=', iper
439  end if
440  end if
441  end function export_longname
442 
443  !> @brief netcdf dynamic package period export
444  !<
445  subroutine export_input(this)
446  use tdismodule, only: kper
447  use arrayhandlersmodule, only: ifind
448  class(ncbasemodelexporttype), intent(inout) :: this
449  integer(I4B) :: idx, ilayer
450  class(exportpackagetype), pointer :: export_pkg
451  character(len=LENVARNAME) :: ilayer_varname
452 
453  do idx = 1, this%pkglist%Count()
454  export_pkg => this%get(idx)
455  ! last loaded data is not current period
456  if (export_pkg%iper /= kper) cycle
457  ! period input already exported
458  if (export_pkg%iper_export >= export_pkg%iper) cycle
459  ! set exported iper
460  export_pkg%iper_export = export_pkg%iper
461 
462  ! initialize ilayer
463  ilayer = 0
464 
465  ! set expected ilayer index variable name
466  ilayer_varname = 'I'//trim(export_pkg%mf6_input%subcomponent_type(1:3))
467 
468  ! is ilayer variable in param name list
469  ilayer = ifind(export_pkg%param_names, ilayer_varname)
470 
471  ! layer index variable is required to be first defined in period block
472  if (ilayer == 1) then
473  call this%package_step_ilayer(export_pkg, ilayer_varname, ilayer)
474  else
475  call this%package_step(export_pkg)
476  end if
477  end do
478  end subroutine export_input
479 
480  !> @brief destroy model netcdf export object
481  !<
482  subroutine export_destroy(this)
485  class(ncmodelexporttype), intent(inout) :: this
486  ! override in derived class
487  deallocate (this%deflate)
488  deallocate (this%shuffle)
489  deallocate (this%input_attr)
490  deallocate (this%chunk_time)
491  ! Deallocate idm memory
492  if (this%ncf_mempath /= '') then
493  call memorystore_remove(this%modelname, 'NCF', idm_context)
494  end if
495  end subroutine export_destroy
496 
497 end module ncmodelexportmodule
subroutine init()
Definition: GridSorting.f90:24
abstract interfaces for model netcdf export type
Definition: NCModel.f90:113
This module contains the BoundInputContextModule.
character(len=lenvarname) function, public rsv_name(mf6varname)
create read state variable name
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
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
@ disu
DISV6 discretization.
Definition: Constants.f90:157
@ dis
DIS6 discretization.
Definition: Constants.f90:155
@ disv
DISU6 discretization.
Definition: Constants.f90:156
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
This module contains the InputDefinitionModule.
This module contains the InputLoadTypeModule.
subroutine, public lowcase(word)
Convert to lower case.
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmemseparator), parameter mempathseparator
used to build up the memory address for the stored variables
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public memorystore_remove(component, subcomponent, context)
This module contains the ModflowInputModule.
Definition: ModflowInput.f90:9
This module contains the NCModelExportModule.
Definition: NCModel.f90:8
class(exportpackagetype) function, pointer export_get(this, idx)
retrieve dynamic export object from package list
Definition: NCModel.f90:381
subroutine epkg_init(this, mf6_input, mshape, param_names, nparam)
initialize dynamic package export object
Definition: NCModel.f90:142
@, public netcdf_structured
netcdf structrured export
Definition: NCModel.f90:33
character(len=linelength) function, public export_longname(longname, pkgname, tagname, layer, iper)
build netcdf variable longname
Definition: NCModel.f90:416
subroutine export_destroy(this)
destroy model netcdf export object
Definition: NCModel.f90:483
subroutine export_init(this, modelname, modeltype, modelfname, nc_fname, disenum, nctype, iout)
initialization of model netcdf export
Definition: NCModel.f90:265
subroutine set(this, modelname, modeltype, modelfname, nctype)
set netcdf file scoped attributes
Definition: NCModel.f90:193
@, public netcdf_mesh2d
netcdf ugrid layered mesh export
Definition: NCModel.f90:34
@, public netcdf_undef
undefined netcdf export type
Definition: NCModel.f90:32
character(len=linelength) function input_attribute(this, pkgname, idt)
build modflow6_input attribute string
Definition: NCModel.f90:399
subroutine epkg_destroy(this)
destroy dynamic package export object
Definition: NCModel.f90:185
subroutine export_input(this)
netcdf dynamic package period export
Definition: NCModel.f90:446
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
character(len=linelength) idm_context
integer(i4b) isim_mode
simulation mode
integer(i4b), dimension(:), pointer, public, contiguous nstp
number of time steps in each stress period
Definition: tdis.f90:39
character(len=lendatetime), pointer, public datetime0
starting date and time for the simulation
Definition: tdis.f90:41
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
This module contains version information.
Definition: version.f90:7
character(len=40), parameter version
Definition: version.f90:22
Pointer type for read state variable.
type for storing a dynamic package load list
A generic heterogeneous doubly-linked list.
Definition: List.f90:14
derived type for storing input definition for a file
abstract type for model netcdf export type
Definition: NCModel.f90:101
netcdf export attribute annotations
Definition: NCModel.f90:52
base class for an export model
Definition: NCModel.f90:67