MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
InputLoadType.f90
Go to the documentation of this file.
1 !> @brief This module contains the InputLoadTypeModule
2 !!
3 !! This module defines types that support generic IDM
4 !! static and dynamic input loading.
5 !!
6 !<
8 
9  use kindmodule, only: dp, i4b, lgp
12  use simvariablesmodule, only: errmsg
15  use listmodule, only: listtype
18 
19  implicit none
20  private
21  public :: staticpkgloadbasetype
22  public :: dynamicpkgloadbasetype
23  public :: modeldynamicpkgstype
26  public :: model_inputs
27 
28  !> @brief type representing package subpackage list
30  character(len=LENCOMPONENTNAME), dimension(:), allocatable :: pkgtypes
31  character(len=LENCOMPONENTNAME), dimension(:), allocatable :: component_types
32  character(len=LENCOMPONENTNAME), dimension(:), &
33  allocatable :: subcomponent_types
34  character(len=LINELENGTH), dimension(:), allocatable :: filenames
35  character(len=LENMEMPATH) :: mempath
36  character(len=LENCOMPONENTNAME) :: component_name
37  integer(I4B) :: pnum
38  contains
39  procedure :: create => subpkg_create
40  procedure :: add => subpkg_add
41  procedure :: destroy => subpkg_destroy
42  end type subpackagelisttype
43 
44  !> @brief Static loader type
45  !!
46  !! This type is a base concrete type for a static input loader
47  !!
48  !<
50  type(modflowinputtype) :: mf6_input !< description of modflow6 input
51  type(ncpackagevarstype), pointer :: nc_vars => null()
52  character(len=LENCOMPONENTNAME) :: component_name !< name of component
53  character(len=LINELENGTH) :: component_input_name !< component input name, e.g. model name file
54  character(len=LINELENGTH) :: input_name !< input name, e.g. package *.chd file
55  integer(I4B) :: iperblock !< index of period block on block definition list
56  type(subpackagelisttype) :: subpkg_list !< list of input subpackages
57  contains
58  procedure :: init => static_init
59  procedure :: create_subpkg_list
60  procedure :: destroy => static_destroy
61  end type staticpkgloadtype
62 
63  !> @brief Base abstract type for static input loader
64  !!
65  !! IDM sources should extend and implement this type
66  !!
67  !<
68  type, abstract, extends(staticpkgloadtype) :: staticpkgloadbasetype
69  contains
70  procedure(load_if), deferred :: load
71  end type staticpkgloadbasetype
72 
73  !> @brief Dynamic loader type
74  !!
75  !! This type is a base concrete type for a dynamic (period) input loader
76  !!
77  !<
79  type(modflowinputtype) :: mf6_input !< description of modflow6 input
80  type(ncpackagevarstype), pointer :: nc_vars => null()
81  character(len=LENCOMPONENTNAME) :: component_name !< name of component
82  character(len=LINELENGTH) :: component_input_name !< component input name, e.g. model name file
83  character(len=LINELENGTH) :: input_name !< input name, e.g. package *.chd file
84  character(len=LINELENGTH), dimension(:), allocatable :: param_names !< dynamic param tagnames
85  logical(LGP) :: readasarrays
86  logical(LGP) :: readarraygrid
87  integer(I4B) :: iperblock !< index of period block on block definition list
88  integer(I4B) :: iout !< inunit number for logging
89  integer(I4B) :: nparam !< number of in scope params
90  contains
91  procedure :: init => dynamic_init
92  procedure :: df => dynamic_df
93  procedure :: ad => dynamic_ad
94  procedure :: destroy => dynamic_destroy
95  end type dynamicpkgloadtype
96 
97  !> @brief Base abstract type for dynamic input loader
98  !!
99  !! IDM sources should extend and implement this type
100  !!
101  !<
102  type, abstract, extends(dynamicpkgloadtype) :: dynamicpkgloadbasetype
103  contains
104  procedure(period_load_if), deferred :: rp
105  end type dynamicpkgloadbasetype
106 
107  !> @brief load interfaces for source static and dynamic types
108  !<
109  abstract interface
110  function load_if(this, iout) result(dynamic_loader)
112  class(staticpkgloadbasetype), intent(inout) :: this
113  integer(I4B), intent(in) :: iout
114  class(dynamicpkgloadbasetype), pointer :: dynamic_loader
115  end function load_if
116  subroutine period_load_if(this)
117  import dynamicpkgloadbasetype, i4b
118  class(dynamicpkgloadbasetype), intent(inout) :: this
119  end subroutine
120  end interface
121 
122  !> @brief type for storing a dynamic package load list
123  !!
124  !! This type is used to store a list of package
125  !! dynamic load types for a model
126  !!
127  !<
129  character(len=LENCOMPONENTNAME) :: modeltype !< type of model
130  character(len=LENMODELNAME) :: modelname !< name of model
131  character(len=LINELENGTH) :: modelfname !< name of model input file
132  type(listtype) :: pkglist !< model package list
133  character(len=LINELENGTH) :: nc_fname !< name of model netcdf input
134  integer(I4B) :: ncid !< netcdf file handle
135  integer(I4B) :: iout
136  contains
137  procedure :: init => dynamicpkgs_init
138  procedure :: add => dynamicpkgs_add
139  procedure :: get => dynamicpkgs_get
140  procedure :: rp => dynamicpkgs_rp
141  procedure :: df => dynamicpkgs_df
142  procedure :: ad => dynamicpkgs_ad
143  procedure :: size => dynamicpkgs_size
144  procedure :: destroy => dynamicpkgs_destroy
145  end type modeldynamicpkgstype
146 
148 
149 contains
150 
151  !> @brief create a new package type
152  !<
153  subroutine subpkg_create(this, mempath, component_name)
154  class(subpackagelisttype) :: this
155  character(len=*), intent(in) :: mempath
156  character(len=*), intent(in) :: component_name
157 
158  ! initialize
159  this%pnum = 0
160  this%mempath = mempath
161  this%component_name = component_name
162 
163  ! allocate arrays
164  allocate (this%pkgtypes(0))
165  allocate (this%component_types(0))
166  allocate (this%subcomponent_types(0))
167  allocate (this%filenames(0))
168  end subroutine subpkg_create
169 
170  !> @brief create a new package type
171  !<
172  subroutine subpkg_add(this, pkgtype, component_type, subcomponent_type, &
173  tagname, filename)
178  class(subpackagelisttype) :: this
179  character(len=*), intent(in) :: pkgtype
180  character(len=*), intent(in) :: component_type
181  character(len=*), intent(in) :: subcomponent_type
182  character(len=*), intent(in) :: tagname
183  character(len=*), intent(in) :: filename
184  character(len=LENVARNAME) :: mempath_tag
185  character(len=LENMEMPATH), pointer :: subpkg_mempath
186  character(len=LINELENGTH), pointer :: input_fname
187  integer(I4B) :: idx, trimlen
188 
189  ! reallocate
190  call expandarray(this%pkgtypes)
191  call expandarray(this%component_types)
192  call expandarray(this%subcomponent_types)
193  call expandarray(this%filenames)
194 
195  ! add new package instance
196  this%pnum = this%pnum + 1
197  this%pkgtypes(this%pnum) = pkgtype
198  this%component_types(this%pnum) = component_type
199  this%subcomponent_types(this%pnum) = subcomponent_type
200  this%filenames(this%pnum) = filename
201 
202  ! initialize mempath tag
203  mempath_tag = tagname
204  trimlen = len_trim(tagname)
205  idx = 0
206 
207  ! create mempath tagname
208  idx = index(tagname, '_')
209  if (idx > 0) then
210  if (tagname(idx + 1:trimlen) == 'FILENAME') then
211  write (mempath_tag, '(a)') tagname(1:idx)//'MEMPATH'
212  end if
213  end if
214 
215  ! allocate mempath variable for subpackage
216  call mem_allocate(subpkg_mempath, lenmempath, mempath_tag, &
217  this%mempath)
218 
219  ! create and set the mempath
220  subpkg_mempath = &
221  create_mem_path(this%component_name, &
222  subcomponent_type, idm_context)
223 
224  ! allocate and initialize filename for subpackage
225  call mem_allocate(input_fname, linelength, 'INPUT_FNAME', subpkg_mempath)
226  input_fname = filename
227  end subroutine subpkg_add
228 
229  !> @brief create a new package type
230  !<
231  subroutine subpkg_destroy(this)
232  class(subpackagelisttype) :: this
233  ! allocate arrays
234  deallocate (this%pkgtypes)
235  deallocate (this%component_types)
236  deallocate (this%subcomponent_types)
237  deallocate (this%filenames)
238  end subroutine subpkg_destroy
239 
240  !> @brief initialize static package loader
241  !!
242  !<
243  subroutine static_init(this, mf6_input, component_name, component_input_name, &
244  input_name)
245  class(staticpkgloadtype), intent(inout) :: this
246  type(modflowinputtype), intent(in) :: mf6_input
247  character(len=*), intent(in) :: component_name
248  character(len=*), intent(in) :: component_input_name
249  character(len=*), intent(in) :: input_name
250  integer(I4B) :: iblock
251 
252  this%mf6_input = mf6_input
253  this%component_name = component_name
254  this%component_input_name = component_input_name
255  this%input_name = input_name
256  this%iperblock = 0
257 
258  ! create subpackage list
259  call this%subpkg_list%create(this%mf6_input%mempath, &
260  this%mf6_input%component_name)
261 
262  ! identify period block definition
263  do iblock = 1, size(mf6_input%block_dfns)
264  if (mf6_input%block_dfns(iblock)%blockname == 'PERIOD') then
265  this%iperblock = iblock
266  exit
267  end if
268  end do
269  end subroutine static_init
270 
271  !> @brief create the subpackage list
272  !!
273  !<
274  subroutine create_subpkg_list(this)
278  class(staticpkgloadtype), intent(inout) :: this
279  character(len=16), dimension(:), pointer :: subpkgs
280  character(len=LINELENGTH) :: tag, fname, pkgtype
281  character(len=LENFTYPE) :: c_type, sc_type
282  character(len=16) :: subpkg
283  integer(I4B) :: idx, n
284 
285  ! set pointer to package (idm integrated) subpackage list
286  subpkgs => idm_subpackages(this%mf6_input%component_type, &
287  this%mf6_input%subcomponent_type)
288 
289  ! check if tag matches subpackage
290  do n = 1, size(subpkgs)
291  subpkg = subpkgs(n)
292  idx = index(subpkg, '-')
293  ! split sp string into component/subcomponent
294  if (idx > 0) then
295  ! split string in component/subcomponent types
296  c_type = subpkg(1:idx - 1)
297  sc_type = subpkg(idx + 1:len_trim(subpkg))
298  if (idm_integrated(c_type, sc_type)) then
299  ! set pkgtype and input filename tag
300  pkgtype = trim(sc_type)//'6'
301  tag = trim(pkgtype)//'_FILENAME'
302  ! support single instance of each subpackage
303  if (idm_multi_package(c_type, sc_type)) then
304  errmsg = 'Multi-instance subpackages not supported. Remove dfn &
305  &subpackage tagline for package "'//trim(subpkg)//'".'
306  call store_error(errmsg)
307  call store_error_filename(this%input_name)
308  else
309  if (filein_fname(fname, tag, this%mf6_input%mempath, &
310  this%input_name)) then
311  call this%subpkg_list%add(pkgtype, c_type, sc_type, &
312  trim(tag), trim(fname))
313  end if
314  end if
315  else
316  errmsg = 'Identified subpackage is not IDM integrated. Remove dfn &
317  &subpackage tagline for package "'//trim(subpkg)//'".'
318  call store_error(errmsg)
319  call store_error_filename(this%input_name)
320  end if
321  end if
322  end do
323  end subroutine create_subpkg_list
324 
325  subroutine static_destroy(this)
326  class(staticpkgloadtype), intent(inout) :: this
327  call this%subpkg_list%destroy()
328  if (associated(this%nc_vars)) then
329  call this%nc_vars%destroy()
330  deallocate (this%nc_vars)
331  nullify (this%nc_vars)
332  end if
333  end subroutine static_destroy
334 
335  !> @brief initialize dynamic package loader
336  !!
337  !! Any managed memory pointed to from model/package context
338  !! must be allocated when dynamic loader is initialized.
339  !!
340  !<
341  subroutine dynamic_init(this, mf6_input, component_name, component_input_name, &
342  input_name, iperblock, iout)
343  use simvariablesmodule, only: errmsg
345  class(dynamicpkgloadtype), intent(inout) :: this
346  type(modflowinputtype), intent(in) :: mf6_input
347  character(len=*), intent(in) :: component_name
348  character(len=*), intent(in) :: component_input_name
349  character(len=*), intent(in) :: input_name
350  integer(I4B), intent(in) :: iperblock
351  integer(I4B), intent(in) :: iout
352  type(inputparamdefinitiontype), pointer :: idt
353  integer(I4B) :: iparam
354 
355  this%mf6_input = mf6_input
356  this%component_name = component_name
357  this%component_input_name = component_input_name
358  this%input_name = input_name
359  this%readasarrays = .false.
360  this%readarraygrid = .false.
361  this%iperblock = iperblock
362  this%nparam = 0
363  this%iout = iout
364  nullify (idt)
365 
366  ! throw error and exit if not found
367  if (this%iperblock == 0) then
368  write (errmsg, '(a,a)') &
369  'Programming error. (IDM) PERIOD block not found in '&
370  &'dynamic package input block dfns: ', &
371  trim(mf6_input%subcomponent_name)
372  call store_error(errmsg)
373  call store_error_filename(this%input_name)
374  end if
375 
376  ! set readasarrays and readarraygrid
377  if (mf6_input%block_dfns(iperblock)%aggregate) then
378  ! no-op, list based input
379  else
380  do iparam = 1, size(mf6_input%param_dfns)
381  idt => mf6_input%param_dfns(iparam)
382  if (idt%blockname == 'OPTIONS') then
383  select case (idt%tagname)
384  case ('READASARRAYS')
385  this%readasarrays = .true.
386  case ('READARRAYGRID')
387  this%readarraygrid = .true.
388  case default
389  ! no-op
390  end select
391  end if
392  end do
393  end if
394  end subroutine dynamic_init
395 
396  !> @brief dynamic package loader define
397  !!
398  !<
399  subroutine dynamic_df(this)
400  class(dynamicpkgloadtype), intent(inout) :: this
401  ! override in derived type
402  end subroutine dynamic_df
403 
404  !> @brief dynamic package loader advance
405  !!
406  !<
407  subroutine dynamic_ad(this)
408  class(dynamicpkgloadtype), intent(inout) :: this
409  ! override in derived type
410  end subroutine dynamic_ad
411 
412  !> @brief dynamic package loader destroy
413  !!
414  !<
415  subroutine dynamic_destroy(this)
419  class(dynamicpkgloadtype), intent(inout) :: this
420 
421  ! clean up netcdf variables structure
422  if (associated(this%nc_vars)) then
423  call this%nc_vars%destroy()
424  deallocate (this%nc_vars)
425  nullify (this%nc_vars)
426  end if
427 
428  ! deallocate package static and dynamic input context
429  call memorystore_remove(this%mf6_input%component_name, &
430  this%mf6_input%subcomponent_name, &
431  idm_context)
432  end subroutine dynamic_destroy
433 
434  !> @brief model dynamic packages init
435  !!
436  !<
437  subroutine dynamicpkgs_init(this, modeltype, modelname, modelfname, nc_fname, &
438  ncid, iout)
439  class(modeldynamicpkgstype), intent(inout) :: this
440  character(len=*), intent(in) :: modeltype
441  character(len=*), intent(in) :: modelname
442  character(len=*), intent(in) :: modelfname
443  character(len=*), intent(in) :: nc_fname
444  integer(I4B), intent(in) :: ncid
445  integer(I4B), intent(in) :: iout
446  this%modeltype = modeltype
447  this%modelname = modelname
448  this%modelfname = modelfname
449  this%nc_fname = nc_fname
450  this%ncid = ncid
451  this%iout = iout
452  end subroutine dynamicpkgs_init
453 
454  !> @brief add package to model dynamic packages list
455  !!
456  !<
457  subroutine dynamicpkgs_add(this, dynamic_pkg)
458  class(modeldynamicpkgstype), intent(inout) :: this
459  class(dynamicpkgloadbasetype), pointer, intent(inout) :: dynamic_pkg
460  class(*), pointer :: obj
461  obj => dynamic_pkg
462  call this%pkglist%add(obj)
463  end subroutine dynamicpkgs_add
464 
465  !> @brief retrieve package from model dynamic packages list
466  !!
467  !<
468  function dynamicpkgs_get(this, idx) result(res)
469  class(modeldynamicpkgstype), intent(inout) :: this
470  integer(I4B), intent(in) :: idx
471  class(dynamicpkgloadbasetype), pointer :: res
472  class(*), pointer :: obj
473  nullify (res)
474  obj => this%pkglist%GetItem(idx)
475  if (associated(obj)) then
476  select type (obj)
477  class is (dynamicpkgloadbasetype)
478  res => obj
479  end select
480  end if
481  end function dynamicpkgs_get
482 
483  !> @brief read and prepare model dynamic packages
484  !!
485  !<
486  subroutine dynamicpkgs_rp(this)
488  class(modeldynamicpkgstype), intent(inout) :: this
489  class(dynamicpkgloadbasetype), pointer :: dynamic_pkg
490  integer(I4B) :: n
491  call idm_log_period_header(this%modelname, this%iout)
492  do n = 1, this%pkglist%Count()
493  dynamic_pkg => this%get(n)
494  call dynamic_pkg%rp()
495  end do
496  call idm_log_period_close(this%iout)
497  end subroutine dynamicpkgs_rp
498 
499  !> @brief define model dynamic packages
500  !!
501  !<
502  subroutine dynamicpkgs_df(this)
503  class(modeldynamicpkgstype), intent(inout) :: this
504  class(dynamicpkgloadbasetype), pointer :: dynamic_pkg
505  integer(I4B) :: n
506  do n = 1, this%pkglist%Count()
507  dynamic_pkg => this%get(n)
508  call dynamic_pkg%df()
509  end do
510  end subroutine dynamicpkgs_df
511 
512  !> @brief advance model dynamic packages
513  !!
514  !<
515  subroutine dynamicpkgs_ad(this)
516  class(modeldynamicpkgstype), intent(inout) :: this
517  class(dynamicpkgloadbasetype), pointer :: dynamic_pkg
518  integer(I4B) :: n
519  do n = 1, this%pkglist%Count()
520  dynamic_pkg => this%get(n)
521  call dynamic_pkg%ad()
522  end do
523  end subroutine dynamicpkgs_ad
524 
525  !> @brief get size of model dynamic packages list
526  !!
527  !<
528  function dynamicpkgs_size(this) result(size)
529  class(modeldynamicpkgstype), intent(inout) :: this
530  integer(I4B) :: size
531  size = this%pkglist%Count()
532  end function dynamicpkgs_size
533 
534  !> @brief destroy model dynamic packages object
535  !!
536  !<
537  subroutine dynamicpkgs_destroy(this)
538  class(modeldynamicpkgstype), intent(inout) :: this
539  class(dynamicpkgloadbasetype), pointer :: dynamic_pkg
540  integer(I4B) :: n
541  ! destroy dynamic loaders
542  do n = 1, this%pkglist%Count()
543  dynamic_pkg => this%get(n)
544  call dynamic_pkg%destroy()
545  deallocate (dynamic_pkg)
546  nullify (dynamic_pkg)
547  end do
548  call this%pkglist%Clear()
549  end subroutine dynamicpkgs_destroy
550 
551  !> @brief add model dynamic packages object to list
552  !!
553  !<
554  subroutine adddynamicmodeltolist(list, model_dynamic)
555  type(listtype), intent(inout) :: list !< package list
556  class(modeldynamicpkgstype), pointer, intent(inout) :: model_dynamic
557  class(*), pointer :: obj
558  obj => model_dynamic
559  call list%Add(obj)
560  end subroutine adddynamicmodeltolist
561 
562  !> @brief get model dynamic packages object from list
563  !!
564  !<
565  function getdynamicmodelfromlist(list, idx) result(res)
566  type(listtype), intent(inout) :: list !< spd list
567  integer(I4B), intent(in) :: idx !< package number
568  class(modeldynamicpkgstype), pointer :: res
569  class(*), pointer :: obj
570  ! initialize res
571  nullify (res)
572  ! get the object from the list
573  obj => list%GetItem(idx)
574  if (associated(obj)) then
575  select type (obj)
576  class is (modeldynamicpkgstype)
577  res => obj
578  end select
579  end if
580  end function getdynamicmodelfromlist
581 
582 end module inputloadtypemodule
subroutine init()
Definition: GridSorting.f90:24
load interfaces for source static and dynamic types
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
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
logical function, public idm_integrated(component, subcomponent)
logical function, public idm_multi_package(component, subcomponent)
character(len=16) function, dimension(:), pointer, public idm_subpackages(component, subcomponent)
This module contains the Input Data Model Logger Module.
Definition: IdmLogger.f90:7
subroutine, public idm_log_period_header(component, iout)
@ brief log a dynamic header message
Definition: IdmLogger.f90:67
subroutine, public idm_log_period_close(iout)
@ brief log the period closing message
Definition: IdmLogger.f90:79
This module contains the InputDefinitionModule.
This module contains the InputLoadTypeModule.
subroutine dynamic_ad(this)
dynamic package loader advance
subroutine static_init(this, mf6_input, component_name, component_input_name, input_name)
initialize static package loader
subroutine subpkg_destroy(this)
create a new package type
subroutine dynamicpkgs_init(this, modeltype, modelname, modelfname, nc_fname, ncid, iout)
model dynamic packages init
class(modeldynamicpkgstype) function, pointer, public getdynamicmodelfromlist(list, idx)
get model dynamic packages object from list
subroutine create_subpkg_list(this)
create the subpackage list
integer(i4b) function dynamicpkgs_size(this)
get size of model dynamic packages list
subroutine dynamic_init(this, mf6_input, component_name, component_input_name, input_name, iperblock, iout)
initialize dynamic package loader
type(listtype), public model_inputs
subroutine, public adddynamicmodeltolist(list, model_dynamic)
add model dynamic packages object to list
subroutine dynamicpkgs_add(this, dynamic_pkg)
add package to model dynamic packages list
subroutine dynamicpkgs_rp(this)
read and prepare model dynamic packages
subroutine subpkg_create(this, mempath, component_name)
create a new package type
subroutine static_destroy(this)
subroutine subpkg_add(this, pkgtype, component_type, subcomponent_type, tagname, filename)
create a new package type
subroutine dynamicpkgs_destroy(this)
destroy model dynamic packages object
class(dynamicpkgloadbasetype) function, pointer dynamicpkgs_get(this, idx)
retrieve package from model dynamic packages list
subroutine dynamicpkgs_ad(this)
advance model dynamic packages
subroutine dynamic_destroy(this)
dynamic package loader destroy
subroutine dynamic_df(this)
dynamic package loader define
subroutine dynamicpkgs_df(this)
define model dynamic packages
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 memorystore_remove(component, subcomponent, context)
This module contains the ModflowInputModule.
Definition: ModflowInput.f90:9
This module contains the NCFileVarsModule.
Definition: NCFileVars.f90:7
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
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
logical(lgp) function, public filein_fname(filename, tagname, input_mempath, input_fname)
enforce and set a single input filename provided via FILEIN keyword
Base abstract type for dynamic input loader.
type for storing a dynamic package load list
Base abstract type for static input loader.
type representing package subpackage list
A generic heterogeneous doubly-linked list.
Definition: List.f90:14
derived type for storing input definition for a file
Type describing input variables for a package in NetCDF file.
Definition: NCFileVars.f90:22