MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
IdmLogger.f90
Go to the documentation of this file.
1 !> @brief This module contains the Input Data Model Logger Module
2 !!
3 !! This module contains the subroutines for logging messages
4 !! to the list file as the input data model loads model input.
5 !!
6 !<
8 
9  use kindmodule, only: dp, lgp, i4b
11  use simmodule, only: store_error
14 
15  implicit none
16  private
17  public :: idm_log_header
18  public :: idm_log_close
19  public :: idm_log_period_header
20  public :: idm_log_period_close
21  public :: idm_export
22  public :: idm_log_var
23 
24  interface idm_log_var
25  module procedure idm_log_var_logical, idm_log_var_int, &
31  end interface idm_log_var
32 
33  interface idm_export
34  module procedure idm_export_int1d, idm_export_int2d, &
37  end interface idm_export
38 
39 contains
40 
41  !> @ brief log a header message
42  !<
43  subroutine idm_log_header(component, subcomponent, iout)
44  character(len=*), intent(in) :: component !< component name
45  character(len=*), intent(in) :: subcomponent !< subcomponent name
46  integer(I4B), intent(in) :: iout
47  if (iparamlog > 0 .and. iout > 0) then
48  write (iout, '(1x,a)') 'Loading input for '//trim(component)//&
49  &'/'//trim(subcomponent)
50  end if
51  end subroutine idm_log_header
52 
53  !> @ brief log the closing message
54  !<
55  subroutine idm_log_close(component, subcomponent, iout)
56  character(len=*), intent(in) :: component !< component name
57  character(len=*), intent(in) :: subcomponent !< subcomponent name
58  integer(I4B), intent(in) :: iout
59  if (iparamlog > 0 .and. iout > 0) then
60  write (iout, '(1x,a)') 'Loading input complete...'
61  end if
62  end subroutine idm_log_close
63 
64  !> @ brief log a dynamic header message
65  !<
66  subroutine idm_log_period_header(component, iout)
67  use tdismodule, only: kper, kstp
68  character(len=*), intent(in) :: component !< component name
69  integer(I4B), intent(in) :: iout
70  if (iparamlog > 0 .and. iout > 0 .and. kstp == 1) then
71  write (iout, '(/1x,a,i0,a)') 'IDP PERIOD ', kper, &
72  ' load for component: '//trim(component)
73  end if
74  end subroutine idm_log_period_header
75 
76  !> @ brief log the period closing message
77  !<
78  subroutine idm_log_period_close(iout)
79  use tdismodule, only: kstp
80  integer(I4B), intent(in) :: iout
81  if (iparamlog > 0 .and. iout > 0 .and. kstp == 1) then
82  !backspace iout
83  write (iout, '(1x,a,/)') 'IDP component dynamic load complete...'
84  end if
85  end subroutine idm_log_period_close
86 
87  !> @ brief log the period closing message
88  !<
89  subroutine idm_log_var_ts(varname, mempath, iout, is_tas)
90  character(len=*), intent(in) :: varname !< variable name
91  character(len=*), intent(in) :: mempath !< variable memory path
92  integer(I4B), intent(in) :: iout
93  logical(LGP), intent(in) :: is_tas
94  if (iparamlog > 0 .and. iout > 0) then
95  if (is_tas) then
96  write (iout, '(3x, a, ": ", a)') &
97  'Time-array-series controlled dynamic variable detected', trim(varname)
98  else
99  write (iout, '(3x, a, ": ", a)') &
100  'Time-series controlled dynamic variable detected', trim(varname)
101  end if
102  end if
103  end subroutine idm_log_var_ts
104 
105  !> @brief Log type specific information logical
106  !<
107  subroutine idm_log_var_logical(p_mem, varname, mempath, iout)
108  logical(LGP), intent(in) :: p_mem !< logical scalar
109  character(len=*), intent(in) :: varname !< variable name
110  character(len=*), intent(in) :: mempath !< variable memory path
111  integer(I4B), intent(in) :: iout
112  character(len=LINELENGTH) :: description
113  if (iparamlog > 0 .and. iout > 0) then
114  description = 'Logical detected'
115  write (iout, '(3x, a, ": ", a, " = ", l1)') &
116  trim(description), trim(varname), p_mem
117  end if
118  end subroutine idm_log_var_logical
119 
120  !> @brief Log type specific information integer
121  !<
122  subroutine idm_log_var_int(p_mem, varname, mempath, datatype, iout)
123  integer(I4B), intent(in) :: p_mem !< int scalar
124  character(len=*), intent(in) :: varname !< variable name
125  character(len=*), intent(in) :: mempath !< variable memory path
126  character(len=*), intent(in) :: datatype !< variable data type
127  integer(I4B), intent(in) :: iout
128  character(len=LINELENGTH) :: description
129  if (iparamlog > 0 .and. iout > 0) then
130  if (datatype == 'KEYWORD') then
131  description = 'Keyword detected'
132  write (iout, '(3x, a, ": ", a)') trim(description), trim(varname)
133  else
134  description = 'Integer detected'
135  write (iout, '(3x, a, ": ", a, " = ", i0)') &
136  trim(description), trim(varname), p_mem
137  end if
138  end if
139  end subroutine idm_log_var_int
140 
141  !> @brief Log type specific information int1d
142  !<
143  subroutine idm_log_var_int1d(p_mem, varname, mempath, iout)
144  integer(I4B), dimension(:), contiguous, intent(in) :: p_mem !< 1d int array
145  character(len=*), intent(in) :: varname !< variable name
146  character(len=*), intent(in) :: mempath !< variable memory path
147  integer(I4B), intent(in) :: iout
148  integer(I4B) :: min_val, max_val
149  character(len=LINELENGTH) :: description
150  if (iparamlog > 0 .and. iout > 0) then
151  min_val = minval(p_mem)
152  max_val = maxval(p_mem)
153  if (min_val == max_val) then
154  description = 'Integer 1D constant array detected'
155  write (iout, '(3x, a, ": ", a, " = ", i0)') &
156  trim(description), trim(varname), min_val
157  else
158  description = 'Integer 1D array detected'
159  write (iout, '(3x, a, ": ", a, a, i0, a, i0)') &
160  trim(description), trim(varname), &
161  ' ranges from ', min_val, ' to ', max_val
162  end if
163  end if
164  end subroutine idm_log_var_int1d
165 
166  !> @brief Log type specific information int2d
167  !<
168  subroutine idm_log_var_int2d(p_mem, varname, mempath, iout)
169  integer(I4B), dimension(:, :), contiguous, intent(in) :: p_mem !< 2d int array
170  character(len=*), intent(in) :: varname !< variable name
171  character(len=*), intent(in) :: mempath !< variable memory path
172  integer(I4B), intent(in) :: iout
173  integer(I4B) :: min_val, max_val
174  character(len=LINELENGTH) :: description
175  if (iparamlog > 0 .and. iout > 0) then
176  min_val = minval(p_mem)
177  max_val = maxval(p_mem)
178  if (min_val == max_val) then
179  description = 'Integer 2D constant array detected'
180  write (iout, '(3x, a, ": ", a, " = ", i0)') &
181  trim(description), trim(varname), min_val
182  else
183  description = 'Integer 2D array detected'
184  write (iout, '(3x, a, ": ", a, a, i0, a, i0)') &
185  trim(description), trim(varname), &
186  ' ranges from ', min_val, ' to ', max_val
187  end if
188  end if
189  end subroutine idm_log_var_int2d
190 
191  !> @brief Log type specific information int3d
192  !<
193  subroutine idm_log_var_int3d(p_mem, varname, mempath, iout)
194  integer(I4B), dimension(:, :, :), contiguous, intent(in) :: p_mem !< 3d int array
195  character(len=*), intent(in) :: varname !< variable name
196  character(len=*), intent(in) :: mempath !< variable memory path
197  integer(I4B), intent(in) :: iout
198  integer(I4B) :: min_val, max_val
199  character(len=LINELENGTH) :: description
200  if (iparamlog > 0 .and. iout > 0) then
201  min_val = minval(p_mem)
202  max_val = maxval(p_mem)
203  if (min_val == max_val) then
204  description = 'Integer 3D constant array detected'
205  write (iout, '(3x, a, ": ", a, " = ", i0)') &
206  trim(description), trim(varname), min_val
207  else
208  description = 'Integer 3D array detected'
209  write (iout, '(3x, a, ": ", a, a, i0, a, i0)') &
210  trim(description), trim(varname), &
211  ' ranges from ', min_val, ' to ', max_val
212  end if
213  end if
214  end subroutine idm_log_var_int3d
215 
216  !> @brief Log type specific information double
217  !<
218  subroutine idm_log_var_dbl(p_mem, varname, mempath, iout)
219  real(DP), intent(in) :: p_mem !< dbl scalar
220  character(len=*), intent(in) :: varname !< variable name
221  character(len=*), intent(in) :: mempath !< variable memory path
222  integer(I4B), intent(in) :: iout
223  character(len=LINELENGTH) :: description
224  if (iparamlog > 0 .and. iout > 0) then
225  description = 'Double detected'
226  write (iout, '(3x, a, ": ", a, " = ", G0)') &
227  trim(description), trim(varname), p_mem
228  end if
229  end subroutine idm_log_var_dbl
230 
231  !> @brief Log type specific information dbl1d
232  !<
233  subroutine idm_log_var_dbl1d(p_mem, varname, mempath, iout)
234  real(DP), dimension(:), contiguous, intent(in) :: p_mem !< 1d real array
235  character(len=*), intent(in) :: varname !< variable name
236  character(len=*), intent(in) :: mempath !< variable memory path
237  integer(I4B), intent(in) :: iout
238  real(DP) :: min_val, max_val
239  character(len=LINELENGTH) :: description
240  if (iparamlog > 0 .and. iout > 0) then
241  min_val = minval(p_mem)
242  max_val = maxval(p_mem)
243  if (min_val == max_val) then
244  description = 'Double precision 1D constant array detected'
245  write (iout, '(3x, a, ": ", a, " = ", G0)') &
246  trim(description), trim(varname), min_val
247  else
248  description = 'Double precision 1D array detected'
249  write (iout, '(3x, a, ": ", a, a, G0, a, G0)') &
250  trim(description), trim(varname), &
251  ' ranges from ', min_val, ' to ', max_val
252  end if
253  end if
254  end subroutine idm_log_var_dbl1d
255 
256  !> @brief Log type specific information dbl2d
257  !<
258  subroutine idm_log_var_dbl2d(p_mem, varname, mempath, iout)
259  real(DP), dimension(:, :), contiguous, intent(in) :: p_mem !< 2d dbl array
260  character(len=*), intent(in) :: varname !< variable name
261  character(len=*), intent(in) :: mempath !< variable memory path
262  integer(I4B), intent(in) :: iout
263  real(DP) :: min_val, max_val
264  character(len=LINELENGTH) :: description
265  if (iparamlog > 0 .and. iout > 0) then
266  min_val = minval(p_mem)
267  max_val = maxval(p_mem)
268  if (min_val == max_val) then
269  description = 'Double precision 2D constant array detected'
270  write (iout, '(3x, a, ": ", a, " = ", G0)') &
271  trim(description), trim(varname), min_val
272  else
273  description = 'Double precision 2D array detected'
274  write (iout, '(3x, a, ": ", a, a, G0, a, G0)') &
275  trim(description), trim(varname), &
276  ' ranges from ', min_val, ' to ', max_val
277  end if
278  end if
279  end subroutine idm_log_var_dbl2d
280 
281  !> @brief Log type specific information dbl3d
282  !<
283  subroutine idm_log_var_dbl3d(p_mem, varname, mempath, iout)
284  real(DP), dimension(:, :, :), contiguous, intent(in) :: p_mem !< 3d dbl array
285  character(len=*), intent(in) :: varname !< variable name
286  character(len=*), intent(in) :: mempath !< variable memory path
287  integer(I4B), intent(in) :: iout
288  real(DP) :: min_val, max_val
289  character(len=LINELENGTH) :: description
290  if (iparamlog > 0 .and. iout > 0) then
291  min_val = minval(p_mem)
292  max_val = maxval(p_mem)
293  if (min_val == max_val) then
294  description = 'Double precision 3D constant array detected'
295  write (iout, '(3x, a, ": ", a, " = ", G0)') &
296  trim(description), trim(varname), min_val
297  else
298  description = 'Double precision 3D array detected'
299  write (iout, '(3x, a, ": ", a, a, G0, a, G0)') &
300  trim(description), trim(varname), &
301  ' ranges from ', min_val, ' to ', max_val
302  end if
303  end if
304  end subroutine idm_log_var_dbl3d
305 
306  !> @brief Log type specific information str
307  !<
308  subroutine idm_log_var_str(p_mem, varname, mempath, iout)
309  character(len=*), intent(in) :: p_mem !< pointer to str scalar
310  character(len=*), intent(in) :: varname !< variable name
311  character(len=*), intent(in) :: mempath !< variable memory path
312  integer(I4B), intent(in) :: iout
313  character(len=LINELENGTH) :: description
314  if (iparamlog > 0 .and. iout > 0) then
315  description = 'String detected'
316  write (iout, '(3x, a, ": ", a, " = ", a)') &
317  trim(description), trim(varname), trim(p_mem)
318  end if
319  end subroutine idm_log_var_str
320 
321  !> @brief Create export file int1d
322  !!
323  !! export layered int1d parameter files
324  !!
325  !<
326  subroutine idm_export_int1d(p_mem, varname, mempath, shapestr, iout)
329  integer(I4B), dimension(:), contiguous, intent(in) :: p_mem !< 1d integer array
330  character(len=*), intent(in) :: varname !< variable name
331  character(len=*), intent(in) :: mempath !< variable memory path
332  character(len=*), intent(in) :: shapestr !< dfn shape string
333  integer(I4B), intent(in) :: iout
334  integer(I4B), dimension(:), pointer, contiguous :: model_shape
335  integer(I4B), dimension(:, :, :), pointer, contiguous :: int3d
336  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
337  integer(I4B), dimension(3) :: dis3d_shape
338  integer(I4B), dimension(2) :: dis2d_shape
339  integer(I4B), pointer :: distype
340  character(LENMEMPATH) :: input_mempath
341  character(LENCOMPONENTNAME) :: comp, subcomp
342  integer(I4B) :: i, j, k, inunit, export_dim
343  logical(LGP) :: is_layered
344 
345  ! set pointer to DISENUM and MODEL_SHAPE
346  call split_mem_path(mempath, comp, subcomp)
347  input_mempath = create_mem_path(component=comp, context=idm_context)
348  call mem_setptr(distype, 'DISENUM', input_mempath)
349  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
350 
351  ! set export_dim
352  export_dim = distype_export_dim(distype, shapestr, is_layered)
353 
354  ! create export file(s)
355  select case (export_dim)
356  case (3)
357  ! set reshape array
358  dis3d_shape(1) = model_shape(3)
359  dis3d_shape(2) = model_shape(2)
360  dis3d_shape(3) = model_shape(1)
361  ! allocate and reshape
362  allocate (int3d(dis3d_shape(1), dis3d_shape(2), dis3d_shape(3)))
363  int3d = reshape(p_mem, dis3d_shape)
364  ! write export files 3D array
365  do k = 1, dis3d_shape(3)
366  inunit = create_export_file(varname, mempath, k, iout)
367  do i = 1, model_shape(2)
368  write (inunit, '(*(i0, " "))') (int3d(j, i, k), j=1, &
369  dis3d_shape(1))
370  end do
371  close (inunit)
372  end do
373  ! cleanup
374  deallocate (int3d)
375  case (2)
376  ! set reshape array
377  dis2d_shape(1) = model_shape(2)
378  dis2d_shape(2) = model_shape(1)
379  ! allocate and reshape
380  allocate (int2d(dis2d_shape(1), dis2d_shape(2)))
381  int2d = reshape(p_mem, dis2d_shape)
382  if (is_layered) then
383  ! write layered export files 2D array
384  do i = 1, dis2d_shape(2)
385  inunit = create_export_file(varname, mempath, i, iout)
386  write (inunit, '(*(i0, " "))') (int2d(j, i), j=1, dis2d_shape(1))
387  close (inunit)
388  end do
389  else
390  ! write export file 2D array
391  inunit = create_export_file(varname, mempath, 0, iout)
392  do i = 1, dis2d_shape(2)
393  write (inunit, '(*(i0, " "))') (int2d(j, i), j=1, dis2d_shape(1))
394  end do
395  close (inunit)
396  end if
397  ! cleanup
398  deallocate (int2d)
399  case (1)
400  ! write export file 1D array
401  inunit = create_export_file(varname, mempath, 0, iout)
402  write (inunit, '(*(i0, " "))') p_mem
403  close (inunit)
404  case default
405  write (errmsg, '(a,i0)') 'EXPORT unsupported int1d export_dim=', &
406  export_dim
407  call store_error(errmsg, .true.)
408  end select
409  end subroutine idm_export_int1d
410 
411  !> @brief Create export file int2d
412  !<
413  subroutine idm_export_int2d(p_mem, varname, mempath, shapestr, iout)
416  integer(I4B), dimension(:, :), contiguous, intent(in) :: p_mem !< 2d dbl array
417  character(len=*), intent(in) :: varname !< variable name
418  character(len=*), intent(in) :: mempath !< variable memory path
419  character(len=*), intent(in) :: shapestr !< dfn shape string
420  integer(I4B), intent(in) :: iout
421  integer(I4B), dimension(:), pointer, contiguous :: model_shape
422  integer(I4B), pointer :: distype
423  character(LENMEMPATH) :: input_mempath
424  character(LENCOMPONENTNAME) :: comp, subcomp
425  integer(I4B) :: i, j, inunit, export_dim
426  logical(LGP) :: is_layered
427 
428  ! set pointer to DISENUM
429  call split_mem_path(mempath, comp, subcomp)
430  input_mempath = create_mem_path(component=comp, context=idm_context)
431  call mem_setptr(distype, 'DISENUM', input_mempath)
432  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
433 
434  ! set export_dim
435  export_dim = distype_export_dim(distype, shapestr, is_layered)
436 
437  select case (export_dim)
438  case (1)
439  ! write export file 1D array
440  inunit = create_export_file(varname, mempath, 0, iout)
441  do i = 1, size(p_mem, dim=2)
442  write (inunit, '(*(i0, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
443  end do
444  close (inunit)
445  case (2)
446  if (is_layered) then
447  ! write layered export files 2D array
448  do i = 1, size(p_mem, dim=2)
449  inunit = create_export_file(varname, mempath, i, iout)
450  write (inunit, '(*(i0, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
451  close (inunit)
452  end do
453  else
454  ! write export file 2D array
455  inunit = create_export_file(varname, mempath, 0, iout)
456  do i = 1, size(p_mem, dim=2)
457  write (inunit, '(*(i0, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
458  end do
459  close (inunit)
460  end if
461  case default
462  write (errmsg, '(a,i0)') 'EXPORT unsupported int2d export_dim=', &
463  export_dim
464  call store_error(errmsg, .true.)
465  end select
466  end subroutine idm_export_int2d
467 
468  !> @brief Create export file int3d
469  !<
470  subroutine idm_export_int3d(p_mem, varname, mempath, shapestr, iout)
473  integer(I4B), dimension(:, :, :), contiguous, intent(in) :: p_mem !< 2d dbl array
474  character(len=*), intent(in) :: varname !< variable name
475  character(len=*), intent(in) :: mempath !< variable memory path
476  character(len=*), intent(in) :: shapestr !< dfn shape string
477  integer(I4B), intent(in) :: iout
478  integer(I4B), dimension(:), pointer, contiguous :: model_shape
479  integer(I4B), pointer :: distype
480  character(LENMEMPATH) :: input_mempath
481  character(LENCOMPONENTNAME) :: comp, subcomp
482  integer(I4B) :: i, j, k, inunit, export_dim
483  logical(LGP) :: is_layered
484 
485  ! set pointer to DISENUM
486  call split_mem_path(mempath, comp, subcomp)
487  input_mempath = create_mem_path(component=comp, context=idm_context)
488  call mem_setptr(distype, 'DISENUM', input_mempath)
489  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
490 
491  ! set export_dim
492  export_dim = distype_export_dim(distype, shapestr, is_layered)
493 
494  select case (export_dim)
495  case (3)
496  ! write export files 3D array
497  do k = 1, size(p_mem, dim=3)
498  inunit = create_export_file(varname, mempath, k, iout)
499  do i = 1, size(p_mem, dim=2)
500  write (inunit, '(*(i0, " "))') (p_mem(j, i, k), j=1, size(p_mem, dim=1))
501  end do
502  close (inunit)
503  end do
504  case default
505  write (errmsg, '(a,i0)') 'EXPORT unsupported int3d export_dim=', &
506  export_dim
507  call store_error(errmsg, .true.)
508  end select
509  end subroutine idm_export_int3d
510 
511  !> @brief Create export file dbl1d
512  !!
513  !! export layered dbl1d parameters with NODES shape
514  !!
515  !<
516  subroutine idm_export_dbl1d(p_mem, varname, mempath, shapestr, iout)
519  real(DP), dimension(:), contiguous, intent(in) :: p_mem !< 1d dbl array
520  character(len=*), intent(in) :: varname !< variable name
521  character(len=*), intent(in) :: mempath !< variable memory path
522  character(len=*), intent(in) :: shapestr !< dfn shape string
523  integer(I4B), intent(in) :: iout
524  integer(I4B), dimension(:), pointer, contiguous :: model_shape
525  real(DP), dimension(:, :, :), pointer, contiguous :: dbl3d
526  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
527  integer(I4B), dimension(3) :: dis3d_shape
528  integer(I4B), dimension(2) :: dis2d_shape
529  integer(I4B), pointer :: distype
530  character(LENMEMPATH) :: input_mempath
531  character(LENCOMPONENTNAME) :: comp, subcomp
532  integer(I4B) :: i, j, k, inunit, export_dim
533  logical(LGP) :: is_layered
534 
535  ! set pointer to DISENUM and MODEL_SHAPE
536  call split_mem_path(mempath, comp, subcomp)
537  input_mempath = create_mem_path(component=comp, context=idm_context)
538  call mem_setptr(distype, 'DISENUM', input_mempath)
539  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
540 
541  ! set export_dim
542  export_dim = distype_export_dim(distype, shapestr, is_layered)
543 
544  ! create export file(s)
545  select case (export_dim)
546  case (3)
547  ! set reshape array
548  dis3d_shape(1) = model_shape(3)
549  dis3d_shape(2) = model_shape(2)
550  ! allocate and reshape
551  dis3d_shape(3) = model_shape(1)
552  allocate (dbl3d(dis3d_shape(1), dis3d_shape(2), dis3d_shape(3)))
553  dbl3d = reshape(p_mem, dis3d_shape)
554  do k = 1, dis3d_shape(3)
555  ! write export files 3D array
556  inunit = create_export_file(varname, mempath, k, iout)
557  do i = 1, model_shape(2)
558  write (inunit, '(*(G0.10, " "))') (dbl3d(j, i, k), j=1, &
559  dis3d_shape(1))
560  end do
561  close (inunit)
562  end do
563  ! cleanup
564  deallocate (dbl3d)
565  case (2)
566  ! set reshape array
567  dis2d_shape(1) = model_shape(2)
568  dis2d_shape(2) = model_shape(1)
569  ! allocate and reshape
570  allocate (dbl2d(dis2d_shape(1), dis2d_shape(2)))
571  dbl2d = reshape(p_mem, dis2d_shape)
572  if (is_layered) then
573  ! write layered export files 2D array
574  do i = 1, dis2d_shape(2)
575  inunit = create_export_file(varname, mempath, i, iout)
576  write (inunit, '(*(G0.10, " "))') (dbl2d(j, i), j=1, dis2d_shape(1))
577  close (inunit)
578  end do
579  else
580  ! write export file 2D array
581  inunit = create_export_file(varname, mempath, 0, iout)
582  do i = 1, dis2d_shape(2)
583  write (inunit, '(*(G0.10, " "))') (dbl2d(j, i), j=1, dis2d_shape(1))
584  end do
585  close (inunit)
586  end if
587  ! cleanup
588  deallocate (dbl2d)
589  case (1)
590  ! write export file 1D array
591  inunit = create_export_file(varname, mempath, 0, iout)
592  write (inunit, '(*(G0.10, " "))') p_mem
593  close (inunit)
594  case default
595  write (errmsg, '(a,i0)') 'EXPORT unsupported dbl1d export_dim=', &
596  export_dim
597  call store_error(errmsg, .true.)
598  end select
599  end subroutine idm_export_dbl1d
600 
601  !> @brief Create export file dbl2d
602  !<
603  subroutine idm_export_dbl2d(p_mem, varname, mempath, shapestr, iout)
606  real(DP), dimension(:, :), contiguous, intent(in) :: p_mem !< 2d dbl array
607  character(len=*), intent(in) :: varname !< variable name
608  character(len=*), intent(in) :: mempath !< variable memory path
609  character(len=*), intent(in) :: shapestr !< dfn shape string
610  integer(I4B), intent(in) :: iout
611  integer(I4B), dimension(:), pointer, contiguous :: model_shape
612  integer(I4B), pointer :: distype
613  character(LENMEMPATH) :: input_mempath
614  character(LENCOMPONENTNAME) :: comp, subcomp
615  integer(I4B) :: i, j, inunit, export_dim
616  logical(LGP) :: is_layered
617 
618  ! set pointer to DISENUM
619  call split_mem_path(mempath, comp, subcomp)
620  input_mempath = create_mem_path(component=comp, context=idm_context)
621  call mem_setptr(distype, 'DISENUM', input_mempath)
622  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
623 
624  ! set export_dim
625  export_dim = distype_export_dim(distype, shapestr, is_layered)
626 
627  select case (export_dim)
628  case (1)
629  ! write export file 1D array
630  inunit = create_export_file(varname, mempath, 0, iout)
631  do i = 1, size(p_mem, dim=2)
632  write (inunit, '(*(G0.10, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
633  end do
634  close (inunit)
635  case (2)
636  if (is_layered) then
637  ! write layered export files 2D array
638  do i = 1, size(p_mem, dim=2)
639  inunit = create_export_file(varname, mempath, i, iout)
640  write (inunit, '(*(G0.10, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
641  close (inunit)
642  end do
643  else
644  ! write export file 2D array
645  inunit = create_export_file(varname, mempath, 0, iout)
646  do i = 1, size(p_mem, dim=2)
647  write (inunit, '(*(G0.10, " "))') (p_mem(j, i), j=1, size(p_mem, dim=1))
648  end do
649  close (inunit)
650  end if
651  case default
652  write (errmsg, '(a,i0)') 'EXPORT unsupported dbl2d export_dim=', &
653  export_dim
654  call store_error(errmsg, .true.)
655  end select
656  end subroutine idm_export_dbl2d
657 
658  !> @brief Create export file dbl3d
659  !<
660  subroutine idm_export_dbl3d(p_mem, varname, mempath, shapestr, iout)
663  real(DP), dimension(:, :, :), contiguous, intent(in) :: p_mem !< 2d dbl array
664  character(len=*), intent(in) :: varname !< variable name
665  character(len=*), intent(in) :: mempath !< variable memory path
666  character(len=*), intent(in) :: shapestr !< dfn shape string
667  integer(I4B), intent(in) :: iout
668  integer(I4B), dimension(:), pointer, contiguous :: model_shape
669  integer(I4B), pointer :: distype
670  character(LENMEMPATH) :: input_mempath
671  character(LENCOMPONENTNAME) :: comp, subcomp
672  integer(I4B) :: i, j, k, inunit, export_dim
673  logical(LGP) :: is_layered
674 
675  ! set pointer to DISENUM
676  call split_mem_path(mempath, comp, subcomp)
677  input_mempath = create_mem_path(component=comp, context=idm_context)
678  call mem_setptr(distype, 'DISENUM', input_mempath)
679  call mem_setptr(model_shape, 'MODEL_SHAPE', input_mempath)
680 
681  ! set export_dim
682  export_dim = distype_export_dim(distype, shapestr, is_layered)
683 
684  select case (export_dim)
685  case (3)
686  ! write export files 3D array
687  do k = 1, size(p_mem, dim=3)
688  inunit = create_export_file(varname, mempath, k, iout)
689  do i = 1, size(p_mem, dim=2)
690  write (inunit, '(*(G0.10, " "))') (p_mem(j, i, k), j=1, &
691  size(p_mem, dim=1))
692  end do
693  close (inunit)
694  end do
695  case default
696  write (errmsg, '(a,i0)') 'EXPORT unsupported dbl3d export_dim=', &
697  export_dim
698  call store_error(errmsg, .true.)
699  end select
700  end subroutine idm_export_dbl3d
701 
702  !> @brief Set dis type export_dim
703  !!
704  !! Set the dimension of the export
705  !<
706  function distype_export_dim(distype, shapestr, is_layered) &
707  result(export_dim)
708  integer(I4B), pointer, intent(in) :: distype
709  character(len=*), intent(in) :: shapestr !< dfn shape string
710  logical(LGP), intent(inout) :: is_layered !< does this data represent layers
711  integer(I4B) :: export_dim
712 
713  ! initialize is_layered to false
714  is_layered = .false.
715 
716  select case (distype)
717  case (dis)
718  if (shapestr == 'NODES') then
719  export_dim = 3
720  is_layered = .true.
721  else if (shapestr == 'NCOL NROW NLAY') then
722  export_dim = 3
723  is_layered = .true.
724  else
725  export_dim = 1
726  end if
727  case (disv)
728  if (shapestr == 'NODES') then
729  export_dim = 2
730  is_layered = .true.
731  else if (shapestr == 'NCPL NLAY') then
732  export_dim = 2
733  is_layered = .true.
734  else
735  export_dim = 1
736  end if
737  case (dis2d)
738  if (shapestr == 'NODES') then
739  export_dim = 2
740  else if (shapestr == 'NCOL NROW') then
741  export_dim = 2
742  else
743  export_dim = 1
744  end if
745  case (disu, disv1d)
746  export_dim = 1
747  case default
748  export_dim = 0
749  end select
750  end function distype_export_dim
751 
752  !> @brief Create export file
753  !!
754  !! Name formats where l=layer, a=auxiliary, p=period
755  !! : <comp>-<subcomp>.varname.txt
756  !! : <comp>-<subcomp>.varname.l<num>.txt
757  !! : <comp>-<subcomp>.varname.p<num>.txt
758  !! : <comp>-<subcomp>.varname.a<num>.p<num>.txt
759  !<
760  function create_export_file(varname, mempath, layer, iout) &
761  result(inunit)
762  use constantsmodule, only: lenvarname
764  use inputoutputmodule, only: upcase, lowcase
766  character(len=*), intent(in) :: varname !< variable name
767  character(len=*), intent(in) :: mempath !< variable memory path
768  integer(I4B), intent(in) :: layer
769  integer(I4B), intent(in) :: iout
770  integer(I4B) :: inunit
771  character(len=LENCOMPONENTNAME) :: comp, subcomp
772  character(len=LINELENGTH) :: filename, suffix
773 
774  ! split the mempath
775  call split_mem_path(mempath, comp, subcomp)
776  call lowcase(comp)
777  call lowcase(subcomp)
778 
779  ! build suffix
780  suffix = varname
781  call lowcase(suffix)
782  if (layer > 0) then
783  write (suffix, '(a,i0)') trim(suffix)//'.l', layer
784  end if
785  suffix = trim(suffix)//'.txt'
786 
787  ! set filename
788  filename = trim(comp)//'-'//trim(subcomp)//'.'//trim(suffix)
789 
790  ! silently create the array file
791  inunit = getunit()
792  call openfile(inunit, 0, filename, 'EXPORT', filstat_opt='REPLACE')
793  end function create_export_file
794 
795 end module idmloggermodule
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
@ disu
DISV6 discretization.
Definition: Constants.f90:157
@ dis
DIS6 discretization.
Definition: Constants.f90:155
@ disv1d
DISV1D6 discretization.
Definition: Constants.f90:160
@ dis2d
DIS2D6 discretization.
Definition: Constants.f90:163
@ disv
DISU6 discretization.
Definition: Constants.f90:156
@ disundef
undefined discretization
Definition: Constants.f90:153
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 Input Data Model Logger Module.
Definition: IdmLogger.f90:7
subroutine idm_log_var_str(p_mem, varname, mempath, iout)
Log type specific information str.
Definition: IdmLogger.f90:309
integer(i4b) function create_export_file(varname, mempath, layer, iout)
Create export file.
Definition: IdmLogger.f90:762
subroutine idm_log_var_int(p_mem, varname, mempath, datatype, iout)
Log type specific information integer.
Definition: IdmLogger.f90:123
integer(i4b) function distype_export_dim(distype, shapestr, is_layered)
Set dis type export_dim.
Definition: IdmLogger.f90:708
subroutine idm_export_int2d(p_mem, varname, mempath, shapestr, iout)
Create export file int2d.
Definition: IdmLogger.f90:414
subroutine, public idm_log_close(component, subcomponent, iout)
@ brief log the closing message
Definition: IdmLogger.f90:56
subroutine idm_export_dbl2d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl2d.
Definition: IdmLogger.f90:604
subroutine, public idm_log_period_header(component, iout)
@ brief log a dynamic header message
Definition: IdmLogger.f90:67
subroutine idm_log_var_dbl3d(p_mem, varname, mempath, iout)
Log type specific information dbl3d.
Definition: IdmLogger.f90:284
subroutine idm_export_int3d(p_mem, varname, mempath, shapestr, iout)
Create export file int3d.
Definition: IdmLogger.f90:471
subroutine, public idm_log_header(component, subcomponent, iout)
@ brief log a header message
Definition: IdmLogger.f90:44
subroutine idm_log_var_dbl2d(p_mem, varname, mempath, iout)
Log type specific information dbl2d.
Definition: IdmLogger.f90:259
subroutine idm_log_var_ts(varname, mempath, iout, is_tas)
@ brief log the period closing message
Definition: IdmLogger.f90:90
subroutine idm_export_dbl3d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl3d.
Definition: IdmLogger.f90:661
subroutine idm_log_var_int1d(p_mem, varname, mempath, iout)
Log type specific information int1d.
Definition: IdmLogger.f90:144
subroutine, public idm_log_period_close(iout)
@ brief log the period closing message
Definition: IdmLogger.f90:79
subroutine idm_log_var_dbl(p_mem, varname, mempath, iout)
Log type specific information double.
Definition: IdmLogger.f90:219
subroutine idm_log_var_dbl1d(p_mem, varname, mempath, iout)
Log type specific information dbl1d.
Definition: IdmLogger.f90:234
subroutine idm_log_var_int2d(p_mem, varname, mempath, iout)
Log type specific information int2d.
Definition: IdmLogger.f90:169
subroutine idm_log_var_int3d(p_mem, varname, mempath, iout)
Log type specific information int3d.
Definition: IdmLogger.f90:194
subroutine idm_log_var_logical(p_mem, varname, mempath, iout)
Log type specific information logical.
Definition: IdmLogger.f90:108
subroutine idm_export_dbl1d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl1d.
Definition: IdmLogger.f90:517
subroutine idm_export_int1d(p_mem, varname, mempath, shapestr, iout)
Create export file int1d.
Definition: IdmLogger.f90:327
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public lowcase(word)
Convert to lower case.
subroutine, public upcase(word)
Convert to upper case.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
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 split_mem_path(mem_path, component, subcomponent)
Split the memory path into component(s)
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
integer(i4b) iparamlog
input (idm) parameter logging to simulation listing file
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23