MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
ImsLinearSettings.f90
Go to the documentation of this file.
2  use kindmodule
7  implicit none
8  private
9 
10  integer(I4B), public, parameter :: cg_method = 1
11  integer(I4B), public, parameter :: bcgs_method = 2
12 
13  type, public :: imslinearsettingstype
14  character(len=LENMEMPATH) :: memory_path
15  real(dp), pointer :: dvclose => null() !< dependent variable closure criterion
16  real(dp), pointer :: rclose => null() !< residual closure criterion
17  integer(I4B), pointer :: icnvgopt => null() !< convergence option
18  integer(I4B), pointer :: iter1 => null() !< max. iterations
19  integer(I4B), pointer :: ilinmeth => null() !< linear solver method
20  integer(I4B), pointer :: iscl => null() !< scaling method
21  integer(I4B), pointer :: iord => null() !< reordering method
22  integer(I4B), pointer :: north => null() !< number of orthogonalizations
23  real(dp), pointer :: relax => null() !< relaxation factor
24  integer(I4B), pointer :: level => null() !< nr. of preconditioner levels
25  real(dp), pointer :: droptol => null() !< drop tolerance for preconditioner
26  integer(I4B), pointer :: ifdparam => null() !< complexity option
27  contains
28  procedure :: init
29  procedure :: preset_config
30  procedure :: read_from_file
31  procedure :: check_settings
32  procedure :: destroy
33  end type
34 
35 contains
36 
37  subroutine init(this, mem_path)
39  class(imslinearsettingstype) :: this !< linear settings
40  character(len=LENMEMPATH) :: mem_path !< solution memory path
41 
42  this%memory_path = create_mem_path(mem_path, 'IMSLINEAR')
43 
44  call mem_allocate(this%dvclose, 'DVCLOSE', this%memory_path)
45  call mem_allocate(this%rclose, 'RCLOSE', this%memory_path)
46  call mem_allocate(this%icnvgopt, 'ICNVGOPT', this%memory_path)
47  call mem_allocate(this%iter1, 'ITER1', this%memory_path)
48  call mem_allocate(this%ilinmeth, 'ILINMETH', this%memory_path)
49  call mem_allocate(this%iscl, 'ISCL', this%memory_path)
50  call mem_allocate(this%iord, 'IORD', this%memory_path)
51  call mem_allocate(this%north, 'NORTH', this%memory_path)
52  call mem_allocate(this%relax, 'RELAX', this%memory_path)
53  call mem_allocate(this%level, 'LEVEL', this%memory_path)
54  call mem_allocate(this%droptol, 'DROPTOL', this%memory_path)
55  call mem_allocate(this%ifdparam, 'IDFPARAM', this%memory_path)
56 
57  ! defaults
58  this%dvclose = dzero
59  this%rclose = dzero
60  this%icnvgopt = 0
61  this%iter1 = 0
62  this%ilinmeth = 0
63  this%iscl = 0
64  this%iord = 0
65  this%north = 0
66  this%relax = dzero
67  this%level = 0
68  this%droptol = dzero
69  this%ifdparam = 0
70 
71  end subroutine init
72 
73  !> @brief Set solver pre-configured settings based on complexity option
74  !<
75  subroutine preset_config(this, idfparam)
76  class(imslinearsettingstype) :: this !< linear settings
77  integer(I4B) :: idfparam !< complexity option
78 
79  this%ifdparam = idfparam
80 
81  select case (idfparam)
82  case (1) ! Simple option
83  this%iter1 = 50
84  this%ilinmeth = 1
85  this%iscl = 0
86  this%iord = 0
87  this%dvclose = dem3
88  this%rclose = dem1
89  this%relax = dzero
90  this%level = 0
91  this%droptol = dzero
92  this%north = 0
93  case (2) ! Moderate
94  this%iter1 = 100
95  this%ilinmeth = 2
96  this%iscl = 0
97  this%iord = 0
98  this%dvclose = dem2
99  this%rclose = dem1
100  this%relax = 0.97d0
101  this%level = 0
102  this%droptol = dzero
103  this%north = 0
104  case (3) ! Complex
105  this%iter1 = 500
106  this%ilinmeth = 2
107  this%iscl = 0
108  this%iord = 0
109  this%dvclose = dem1
110  this%rclose = dem1
111  this%relax = dzero
112  this%level = 5
113  this%droptol = dem4
114  this%north = 2
115  end select
116 
117  end subroutine preset_config
118 
119  !> @brief Read the settings for the linear solver from the .ims file,
120  !< overriding a possible pre-set configuration with set_complexity
121  subroutine read_from_file(this, parser, iout)
122  class(imslinearsettingstype) :: this !< linear settings
123  type(blockparsertype) :: parser !< block parser
124  integer(I4B) :: iout !< listing file
125  ! local
126  logical(LGP) :: block_found, end_of_block
127  integer(I4B) :: ierr
128  character(len=LINELENGTH) :: errmsg
129  character(len=LINELENGTH) :: warnmsg
130  character(len=LINELENGTH) :: keyword
131  integer(I4B) :: iscaling, iordering
132 
133  call parser%GetBlock('LINEAR', block_found, ierr, supportopenclose=.true., &
134  blockrequired=.false.)
135 
136  if (block_found) then
137  write (iout, '(/1x,a)') 'PROCESSING LINEAR DATA'
138  do
139  call parser%GetNextLine(end_of_block)
140  if (end_of_block) exit
141  call parser%GetStringCaps(keyword)
142  ! -- parse keyword
143  select case (keyword)
144  case ('INNER_DVCLOSE')
145  this%dvclose = parser%GetDouble()
146  case ('INNER_RCLOSE')
147  this%rclose = parser%GetDouble()
148  ! -- look for additional key words
149  call parser%GetStringCaps(keyword)
150  if (keyword == 'STRICT') then
151  this%icnvgopt = 1
152  else if (keyword == 'L2NORM_RCLOSE') then
153  this%icnvgopt = 2
154  else if (keyword == 'RELATIVE_RCLOSE') then
155  this%icnvgopt = 3
156  else if (keyword == 'L2NORM_RELATIVE_RCLOSE') then
157  this%icnvgopt = 4
158  end if
159  case ('INNER_MAXIMUM')
160  this%iter1 = parser%GetInteger()
161  case ('LINEAR_ACCELERATION')
162  call parser%GetStringCaps(keyword)
163  if (keyword .eq. 'CG') then
164  this%ilinmeth = 1
165  else if (keyword .eq. 'BICGSTAB') then
166  this%ilinmeth = 2
167  else
168  this%ilinmeth = 0
169  write (errmsg, '(3a)') &
170  'Unknown IMSLINEAR LINEAR_ACCELERATION method (', &
171  trim(keyword), ').'
172  call store_error(errmsg)
173  end if
174  case ('SCALING_METHOD')
175  call parser%GetStringCaps(keyword)
176  iscaling = 0
177  if (keyword .eq. 'NONE') then
178  iscaling = 0
179  else if (keyword .eq. 'DIAGONAL') then
180  iscaling = 1
181  else if (keyword .eq. 'L2NORM') then
182  iscaling = 2
183  else
184  write (errmsg, '(3a)') &
185  'Unknown IMSLINEAR SCALING_METHOD (', trim(keyword), ').'
186  call store_error(errmsg)
187  end if
188  this%iscl = iscaling
189  case ('RED_BLACK_ORDERING')
190  iordering = 0
191  case ('REORDERING_METHOD')
192  call parser%GetStringCaps(keyword)
193  iordering = 0
194  if (keyword == 'NONE') then
195  iordering = 0
196  else if (keyword == 'RCM') then
197  iordering = 1
198  else if (keyword == 'MD') then
199  iordering = 2
200  else
201  write (errmsg, '(3a)') &
202  'Unknown IMSLINEAR REORDERING_METHOD (', trim(keyword), ').'
203  call store_error(errmsg)
204  end if
205  this%iord = iordering
206  case ('NUMBER_ORTHOGONALIZATIONS')
207  this%north = parser%GetInteger()
208  case ('RELAXATION_FACTOR')
209  this%relax = parser%GetDouble()
210  case ('PRECONDITIONER_LEVELS')
211  this%level = parser%GetInteger()
212  if (this%level < 0) then
213  write (errmsg, '(a,1x,a)') &
214  'IMSLINEAR PRECONDITIONER_LEVELS must be greater than', &
215  'or equal to zero'
216  call store_error(errmsg)
217  end if
218  case ('PRECONDITIONER_DROP_TOLERANCE')
219  this%droptol = parser%GetDouble()
220  if (this%droptol < dzero) then
221  write (errmsg, '(a,1x,a)') &
222  'IMSLINEAR PRECONDITIONER_DROP_TOLERANCE', &
223  'must be greater than or equal to zero'
224  call store_error(errmsg)
225  end if
226  !
227  ! -- deprecated variables
228  case ('INNER_HCLOSE')
229  this%dvclose = parser%GetDouble()
230  !
231  ! -- create warning message
232  write (warnmsg, '(a)') &
233  'SETTING INNER_DVCLOSE TO INNER_HCLOSE VALUE'
234  !
235  ! -- create deprecation warning
236  call deprecation_warning('LINEAR', 'INNER_HCLOSE', '6.1.1', &
237  warnmsg, parser%GetUnit())
238  !
239  ! -- default
240  case default
241  write (errmsg, '(3a)') &
242  'Unknown IMSLINEAR keyword (', trim(keyword), ').'
243  call store_error(errmsg)
244  end select
245  end do
246  write (iout, '(1x,a)') 'END OF LINEAR DATA'
247  else
248  if (this%ifdparam == 0) THEN
249  write (errmsg, '(a)') 'NO LINEAR block detected.'
250  call store_error(errmsg)
251  end if
252  end if
253 
254  end subroutine read_from_file
255 
256  !> @brief Check the settings after reading the configuration from file
257  !<
258  subroutine check_settings(this)
259  class(imslinearsettingstype) :: this !< linear settings
260  ! local
261  character(len=LINELENGTH) :: warnmsg
262 
263  if (this%level == 0 .and. this%droptol > 0.0_dp) then
264  write (warnmsg, '(a)') "PRECONDITIONER_DROP_TOLERANCE is ignored because &
265  &PRECONDITIONER_LEVELS equals zero."
266  call store_warning(warnmsg)
267  end if
268 
269  end subroutine check_settings
270 
271  subroutine destroy(this)
272  class(imslinearsettingstype) :: this !< linear settings
273 
274  call mem_deallocate(this%dvclose)
275  call mem_deallocate(this%rclose)
276  call mem_deallocate(this%icnvgopt)
277  call mem_deallocate(this%iter1)
278  call mem_deallocate(this%ilinmeth)
279  call mem_deallocate(this%iscl)
280  call mem_deallocate(this%iord)
281  call mem_deallocate(this%north)
282  call mem_deallocate(this%relax)
283  call mem_deallocate(this%level)
284  call mem_deallocate(this%droptol)
285  call mem_deallocate(this%ifdparam)
286 
287  end subroutine destroy
288 
289 end module
subroutine init()
Definition: GridSorting.f90:24
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dem1
real constant 1e-1
Definition: Constants.f90:103
real(dp), parameter dem3
real constant 1e-3
Definition: Constants.f90:106
real(dp), parameter dem4
real constant 1e-4
Definition: Constants.f90:107
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dem2
real constant 1e-2
Definition: Constants.f90:105
integer(i4b), parameter, public cg_method
subroutine read_from_file(this, parser, iout)
Read the settings for the linear solver from the .ims file,.
subroutine preset_config(this, idfparam)
Set solver pre-configured settings based on complexity option.
subroutine check_settings(this)
Check the settings after reading the configuration from file.
integer(i4b), parameter, public bcgs_method
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
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public deprecation_warning(cblock, cvar, cver, endmsg, iunit)
Store deprecation warning message.
Definition: Sim.f90:256