MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
GhostNode.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b
4  use constantsmodule, only: linelength
9 
10  implicit none
11 
12  private
13  public :: ghostnodetype
14  public :: gnc_cr
15 
17  logical, pointer :: smgnc => null() ! single model gnc
18  logical, pointer :: implicit => null() ! lhs or rhs
19  logical, pointer :: i2kn => null() ! not used
20  integer(I4B), pointer :: nexg => null() ! number of gncs
21  integer(I4B), pointer :: numjs => null() ! number of connecting nodes
22  class(numericalmodeltype), pointer :: m1 => null() ! pointer to model 1
23  class(numericalmodeltype), pointer :: m2 => null() ! pointer to model 2
24  integer(I4B), dimension(:), pointer, contiguous :: nodem1 => null() ! array of nodes in model 1
25  integer(I4B), dimension(:), pointer, contiguous :: nodem2 => null() ! array of nodes in model 2
26  integer(I4B), dimension(:, :), pointer, contiguous :: nodesj => null() ! array of interpolation nodes
27  real(dp), dimension(:), pointer, contiguous :: cond => null() ! array of conductance
28  integer(I4B), dimension(:), pointer, contiguous :: idxglo => null() ! connection position in amat
29  integer(I4B), dimension(:), pointer, contiguous :: idxsymglo => null() ! symmetric position in amat
30  real(dp), dimension(:, :), pointer, contiguous :: alphasj => null() ! interpolation factors
31  integer(I4B), dimension(:), pointer, contiguous :: idiagn => null() ! amat diagonal position of n
32  integer(I4B), dimension(:), pointer, contiguous :: idiagm => null() ! amat diagonal position of m
33  integer(I4B), dimension(:, :), pointer, contiguous :: jposinrown => null() ! amat j position in row n
34  integer(I4B), dimension(:, :), pointer, contiguous :: jposinrowm => null() ! amat j position in row m
35 
36  contains
37 
38  procedure :: gnc_df
39  procedure :: gnc_ac
40  procedure :: gnc_mc
41  procedure, private :: gnc_fmsav
42  procedure :: gnc_fc
43  procedure :: gnc_fn
44  procedure :: gnc_cq
45  procedure :: gnc_ot
46  procedure :: gnc_da
47  procedure :: deltaqgnc
48  procedure :: allocate_scalars
49  procedure, private :: allocate_arrays
50  procedure, private :: read_options
51  procedure, private :: read_dimensions
52  procedure, private :: read_data
53  procedure, private :: nodeu_to_noder
54  end type ghostnodetype
55 
56 contains
57 
58  !> @brief Create new GNC exchange object
59  !<
60  subroutine gnc_cr(gncobj, name_parent, inunit, iout)
61  ! -- dummy
62  type(ghostnodetype), pointer, intent(inout) :: gncobj
63  character(len=*), intent(in) :: name_parent
64  integer(I4B), intent(in) :: inunit
65  integer(I4B), intent(in) :: iout
66  !
67  ! -- Allocate the gnc exchange object
68  allocate (gncobj)
69  !
70  ! -- create name and memory path. name_parent will either be model name or the
71  ! exchange name.
72  call gncobj%set_names(1, name_parent, 'GNC', 'GNC')
73  !
74  ! -- allocate scalars
75  call gncobj%allocate_scalars()
76  !
77  ! -- Set variables
78  gncobj%inunit = inunit
79  gncobj%iout = iout
80  end subroutine gnc_cr
81 
82  !> @brief Initialize a gnc object
83  !<
84  subroutine gnc_df(this, m1, m2)
85  ! -- modules
88  use simvariablesmodule, only: errmsg
89  ! -- dummy
90  class(ghostnodetype) :: this
91  class(numericalmodeltype), target :: m1
92  class(numericalmodeltype), target, optional :: m2
93  !
94  ! -- Point or set attributes
95  this%m1 => m1
96  this%m2 => m1
97  !
98  ! -- If m2 is present, then GNC spans two models
99  if (present(m2)) then
100  this%m2 => m2
101  this%smgnc = .false.
102  end if
103  !
104  ! -- Initialize block parser
105  call this%parser%Initialize(this%inunit, this%iout)
106  !
107  ! -- read gnc options
108  call this%read_options()
109  !
110  ! -- read gnc dimensions
111  call this%read_dimensions()
112  !
113  ! -- allocate arrays
114  call this%allocate_arrays()
115  !
116  ! -- Allocate and read the gnc entries
117  call this%read_data()
118  !
119  ! -- Trap for implicit gnc but models are in different solutions
120  if (this%m1%idsoln /= this%m2%idsoln) then
121  if (this%implicit) then
122  write (errmsg, '(a)') 'GNC is implicit but models are in '// &
123  'different solutions.'
124  call store_error(errmsg)
125  call store_error_unit(this%inunit)
126  end if
127  end if
128  end subroutine gnc_df
129 
130  !> @brief Single or Two-Model GNC Add Connections
131  !!
132  !! For implicit GNC, expand the sparse solution matrix
133  !<
134  subroutine gnc_ac(this, sparse)
135  ! -- modules
136  use sparsemodule, only: sparsematrix
137  ! -- dummy
138  class(ghostnodetype) :: this
139  type(sparsematrix), intent(inout) :: sparse
140  ! -- local
141  integer(I4B) :: ignc, jidx, noden, nodem, nodej
142  !
143  ! -- Expand the sparse matrix for ghost node connections. No need to add
144  ! connection between n and m as they must be connected some other way
145  ! that will calculate the conductance.
146  if (this%implicit) then
147  do ignc = 1, this%nexg
148  noden = this%nodem1(ignc) + this%m1%moffset
149  nodem = this%nodem2(ignc) + this%m2%moffset
150  jloop: do jidx = 1, this%numjs
151  nodej = this%nodesj(jidx, ignc)
152  if (nodej == 0) cycle
153  nodej = nodej + this%m1%moffset
154  call sparse%addconnection(nodem, nodej, 1)
155  call sparse%addconnection(nodej, nodem, 1)
156  call sparse%addconnection(noden, nodej, 1)
157  call sparse%addconnection(nodej, noden, 1)
158  end do jloop
159  end do
160  end if
161  end subroutine gnc_ac
162 
163  !> @brief Single or Two-Model GNC Map Connections
164  !!
165  !! Fill the following mapping arrays:
166  !! this%idiagn, this%idiagm (diagonal positions in solution amat)
167  !! this%idxglo (nm connection in solution amat)
168  !! this%idxsymglo (mn connection in solution amat)
169  !! this%jposinrown (position of j in row n of solution amat)
170  !! this%jposinrowm (position of j in row m of solution amat)
171  !<
172  subroutine gnc_mc(this, matrix_sln)
173  ! -- modules
175  use simvariablesmodule, only: errmsg
176  ! -- dummy
177  class(ghostnodetype) :: this
178  class(matrixbasetype), pointer :: matrix_sln
179  ! -- local
180  integer(I4B) :: noden, nodem, ipos, ignc, jidx, nodej
181  ! -- formats
182  character(len=*), parameter :: fmterr = &
183  "('GHOST NODE ERROR. Cell ', i0, ' in model ', a, &
184  &' is not connected to cell ', i0, ' in model ', a)"
185  !
186  ! -- Find the location of Cnm in the global solution and store it in
187  ! this%idxglo
188  do ignc = 1, this%nexg
189  noden = this%nodem1(ignc) + this%m1%moffset
190  nodem = this%nodem2(ignc) + this%m2%moffset
191  !
192  ! -- store diagonal positions in idiagn and idiagm
193  this%idiagn(ignc) = matrix_sln%get_position_diag(noden)
194  this%idiagm(ignc) = matrix_sln%get_position_diag(nodem)
195  !if(this%implicit) then
196  ! this%idiagn(ignc) = iasln(noden)
197  ! this%idiagm(ignc) = iasln(nodem)
198  !endif
199  !
200  ! -- find location of m in row n of global solution, and v.v.
201  this%idxglo(ignc) = matrix_sln%get_position(noden, nodem)
202  this%idxsymglo(ignc) = matrix_sln%get_position(nodem, noden)
203  !
204  ! -- Check to make sure idxglo is set
205  if (this%idxglo(ignc) == -1) then
206  write (errmsg, fmterr) this%nodem1(ignc), trim(this%m1%name), &
207  this%nodem2(ignc), trim(this%m2%name)
208  call store_error(errmsg)
209  end if
210  !
211  end do
212  !
213  ! -- Stop if errors
214  if (count_errors() > 0) then
215  call store_error_unit(this%inunit)
216  end if
217  !
218  ! -- find locations of j in rows n and row m of global solution
219  if (this%implicit) then
220  do ignc = 1, this%nexg
221  noden = this%nodem1(ignc) + this%m1%moffset
222  nodem = this%nodem2(ignc) + this%m2%moffset
223  !
224  do jidx = 1, this%numjs
225  nodej = this%nodesj(jidx, ignc)
226  if (nodej > 0) nodej = nodej + this%m1%moffset
227  !
228  ! -- search for nodej in row n, unless it is 0
229  if (nodej == 0) then
230  ipos = 0
231  this%jposinrown(jidx, ignc) = ipos
232  else
233  this%jposinrown(jidx, ignc) = matrix_sln%get_position(noden, nodej)
234  end if
235  !
236  ! -- search for nodej in row m
237  if (nodej == 0) then
238  ipos = 0
239  this%jposinrowm(jidx, ignc) = ipos
240  else
241  this%jposinrowm(jidx, ignc) = matrix_sln%get_position(nodem, nodej)
242  end if
243  end do
244  end do
245  end if
246  end subroutine gnc_mc
247 
248  !> @brief Store the n-m Picard conductance in cond prior to the Newton terms
249  !! terms being added
250  !<
251  subroutine gnc_fmsav(this, kiter, matrix)
252  ! -- modules
253  use constantsmodule, only: dzero
254  ! -- dummy
255  class(ghostnodetype) :: this
256  integer(I4B), intent(in) :: kiter
257  class(matrixbasetype), pointer :: matrix
258  ! -- local
259  integer(I4B) :: ignc, ipos
260  real(DP) :: cond
261  !
262  ! -- An ipos value of zero indicates that noden is not connected to
263  ! nodem, and therefore the conductance is zero.
264  gncloop: do ignc = 1, this%nexg
265  ipos = this%idxglo(ignc)
266  if (ipos > 0) then
267  cond = matrix%get_value_pos(ipos)
268  else
269  cond = dzero
270  end if
271  this%cond(ignc) = cond
272  end do gncloop
273  end subroutine gnc_fmsav
274 
275  !> @brief Fill matrix terms
276  !!
277  !! Add the GNC terms to the solution matrix or model rhs depending on whether
278  !! whether GNC is implicit or explicit
279  !<
280  subroutine gnc_fc(this, kiter, matrix)
281  ! -- modules
282  use constantsmodule, only: dzero
283  ! -- dummy
284  class(ghostnodetype) :: this
285  integer(I4B), intent(in) :: kiter
286  class(matrixbasetype), pointer :: matrix
287  ! -- local
288  integer(I4B) :: ignc, j, noden, nodem, ipos, jidx, iposjn, iposjm
289  real(DP) :: cond, alpha, aterm, rterm
290  !
291  ! -- If this is a single model gnc (not an exchange across models), then
292  ! pull conductances out of the system matrix and store them in this%cond
293  if (this%smgnc) call this%gnc_fmsav(kiter, matrix)
294  !
295  ! -- Add gnc terms to rhs or to the matrix depending on whether gnc is implicit
296  ! or explicit
297  gncloop: do ignc = 1, this%nexg
298  noden = this%nodem1(ignc)
299  nodem = this%nodem2(ignc)
300  if (this%m1%ibound(noden) == 0 .or. &
301  this%m2%ibound(nodem) == 0) cycle gncloop
302  ipos = this%idxglo(ignc)
303  cond = this%cond(ignc)
304  jloop: do jidx = 1, this%numjs
305  j = this%nodesj(jidx, ignc)
306  if (j == 0) cycle
307  alpha = this%alphasj(jidx, ignc)
308  if (alpha == dzero) cycle
309  aterm = alpha * cond
310  if (this%implicit) then
311  iposjn = this%jposinrown(jidx, ignc)
312  iposjm = this%jposinrowm(jidx, ignc)
313  call matrix%add_value_pos(this%idiagn(ignc), aterm)
314  call matrix%add_value_pos(iposjn, -aterm)
315  call matrix%add_value_pos(this%idxsymglo(ignc), -aterm)
316  call matrix%add_value_pos(iposjm, aterm)
317  else
318  rterm = aterm * (this%m1%x(noden) - this%m1%x(j))
319  this%m1%rhs(noden) = this%m1%rhs(noden) - rterm
320  this%m2%rhs(nodem) = this%m2%rhs(nodem) + rterm
321  end if
322  end do jloop
323  end do gncloop
324  end subroutine gnc_fc
325 
326  !> @brief Fill GNC Newton terms
327  !!
328  !! Required arguments:
329  !! kiter : outer iteration number
330  !! matrix_sln: the solution matrix
331  !! condsat is of size(njas) if single model, otherwise nexg
332  !!
333  !! Optional arguments:
334  !! ihc_opt : an optional vector of size(nexg), which contains a horizontal
335  !! connection code (0=vertical, 1=horizontal, 2=vertically staggered)
336  !! ivarcv_opt : variable vertical conductance flag (default is 0)
337  !! ictm1_opt : icelltype for model 1 integer vector (default is 1)
338  !! ictm2_opt : icelltype for model 2 integer vector (default is 1)
339  !<
340  subroutine gnc_fn(this, kiter, matrix_sln, condsat, ihc_opt, &
341  ivarcv_opt, ictm1_opt, ictm2_opt)
342  ! -- modules
343  use constantsmodule, only: dzero
345  ! -- dummy
346  class(ghostnodetype) :: this
347  integer(I4B) :: kiter
348  class(matrixbasetype), pointer :: matrix_sln
349  real(DP), dimension(:), intent(in) :: condsat
350  integer(I4B), dimension(:), optional :: ihc_opt
351  integer(I4B), optional :: ivarcv_opt
352  integer(I4B), dimension(:), optional :: ictm1_opt
353  integer(I4B), dimension(:), optional :: ictm2_opt
354  ! -- local
355  integer(I4B) :: ignc, jidx, ipos, isympos, ihc, ivarcv
356  integer(I4B) :: nodej, noden, nodem
357  integer(I4B) :: iups, ictup
358  real(DP) :: csat, alpha, consterm, term, derv
359  real(DP) :: xup, topup, botup
360  !
361  ! -- Set the ivarcv to indicate whether or not the vertical conductance
362  ! is a function of water table
363  ivarcv = 0
364  if (present(ivarcv_opt)) ivarcv = ivarcv_opt
365  !
366  gncloop: do ignc = 1, this%nexg
367  noden = this%nodem1(ignc)
368  nodem = this%nodem2(ignc)
369  if (this%m1%ibound(noden) == 0 .or. &
370  this%m2%ibound(nodem) == 0) cycle gncloop
371  !
372  ! -- Assign variables depending on whether single model gnc or exchange
373  ! gnc
374  if (this%smgnc) then
375  ipos = this%m1%dis%con%getjaindex(noden, nodem)
376  isympos = this%m1%dis%con%jas(ipos)
377  ihc = this%m1%dis%con%ihc(isympos)
378  csat = condsat(isympos)
379  else
380  ihc = ihc_opt(ignc)
381  csat = condsat(ignc)
382  end if
383  !
384  ! If vertical connection and not variable cv, then cycle
385  if (ihc == 0 .and. ivarcv == 0) cycle
386  !
387  ! determine upstream node (0 is noden, 1 is nodem)
388  iups = 0
389  if (this%m2%x(nodem) > this%m1%x(noden)) iups = 1
390  !
391  ! -- Set the upstream top and bot, and then recalculate for a
392  ! vertically staggered horizontal connection
393  if (iups == 0) then
394  topup = this%m1%dis%top(noden)
395  botup = this%m1%dis%bot(noden)
396  ictup = 1
397  if (present(ictm1_opt)) ictup = ictm1_opt(noden)
398  xup = this%m1%x(noden)
399  else
400  topup = this%m2%dis%top(nodem)
401  botup = this%m2%dis%bot(nodem)
402  ictup = 1
403  if (present(ictm2_opt)) ictup = ictm2_opt(nodem)
404  xup = this%m2%x(nodem)
405  end if
406  !
407  ! -- No newton terms if upstream cell is confined
408  if (ictup == 0) cycle
409  !
410  ! -- Handle vertically staggered horizontal connection
411  if (ihc == 2) then
412  topup = min(this%m1%dis%top(noden), this%m2%dis%top(nodem))
413  botup = max(this%m1%dis%bot(noden), this%m2%dis%bot(nodem))
414  end if
415  !
416  ! -- Process each contributing node
417  jloop: do jidx = 1, this%numjs
418  nodej = this%nodesj(jidx, ignc)
419  if (nodej == 0) cycle
420  if (this%m1%ibound(nodej) == 0) cycle
421  alpha = this%alphasj(jidx, ignc)
422  if (alpha == dzero) cycle
423  consterm = csat * alpha * (this%m1%x(noden) - this%m1%x(nodej))
424  derv = squadraticsaturationderivative(topup, botup, xup)
425  term = consterm * derv
426  if (iups == 0) then
427  call matrix_sln%add_value_pos(this%idiagn(ignc), term)
428  if (this%m2%ibound(nodem) > 0) then
429  call matrix_sln%add_value_pos(this%idxsymglo(ignc), -term)
430  end if
431  this%m1%rhs(noden) = this%m1%rhs(noden) + term * this%m1%x(noden)
432  this%m2%rhs(nodem) = this%m2%rhs(nodem) - term * this%m1%x(noden)
433  else
434  call matrix_sln%add_value_pos(this%idiagm(ignc), -term)
435  if (this%m1%ibound(noden) > 0) then
436  call matrix_sln%add_value_pos(this%idxglo(ignc), term)
437  end if
438  this%m1%rhs(noden) = this%m1%rhs(noden) + term * this%m2%x(nodem)
439  this%m2%rhs(nodem) = this%m2%rhs(nodem) - term * this%m2%x(nodem)
440  end if
441  end do jloop
442  end do gncloop
443  end subroutine gnc_fn
444 
445  !> @brief Single Model GNC Output
446  !!
447  !! Output GNC deltaQgnc values
448  !<
449  subroutine gnc_ot(this, ibudfl)
450  ! -- dummy
451  class(ghostnodetype) :: this
452  integer(I4B), intent(in) :: ibudfl
453  ! -- local
454  integer(I4B) :: ignc
455  real(DP) :: deltaQgnc
456  character(len=LINELENGTH) :: nodenstr, nodemstr
457  ! -- format
458  character(len=*), parameter :: fmtgnc = "(i10, 2a10, 2(1pg15.6))"
459  !
460  ! -- Process each gnc and output deltaQgnc
461  if (ibudfl /= 0 .and. this%iprflow /= 0) then
462  write (this%iout, '(//, a)') 'GHOST NODE CORRECTION RESULTS'
463  write (this%iout, '(3a10, 2a15)') 'GNC NUM', 'NODEN', 'NODEM', &
464  'DELTAQGNC', 'CONDNM'
465  do ignc = 1, this%nexg
466  deltaqgnc = this%deltaQgnc(ignc)
467  call this%m1%dis%noder_to_string(this%nodem1(ignc), nodenstr)
468  call this%m2%dis%noder_to_string(this%nodem2(ignc), nodemstr)
469  write (this%iout, fmtgnc) ignc, trim(adjustl(nodenstr)), &
470  trim(adjustl(nodemstr)), &
471  deltaqgnc, this%cond(ignc)
472  end do
473  end if
474  end subroutine gnc_ot
475 
476  !> @brief Add GNC to flowja
477  !<
478  subroutine gnc_cq(this, flowja)
479  ! -- dummy
480  class(ghostnodetype) :: this
481  real(DP), dimension(:), intent(inout) :: flowja
482  ! -- local
483  integer(I4B) :: ignc, n1, n2, ipos, isympos
484  real(DP) :: deltaQgnc
485  !
486  ! -- go through each gnc and add deltagnc to flowja
487  do ignc = 1, this%nexg
488  !
489  ! -- calculate correction term between n1 and n2 connection
490  n1 = this%nodem1(ignc)
491  n2 = this%nodem2(ignc)
492  deltaqgnc = this%deltaQgnc(ignc)
493  !
494  ! -- find the positions of this connection in the csr array
495  ipos = this%m1%dis%con%getjaindex(n1, n2)
496  isympos = this%m1%dis%con%isym(ipos)
497  !
498  ! -- add/subtract the corrections
499  flowja(ipos) = flowja(ipos) + deltaqgnc
500  flowja(isympos) = flowja(isympos) - deltaqgnc
501  !
502  end do
503  end subroutine gnc_cq
504 
505  !> @brief Single Model deltaQgnc (ghost node correction flux)
506  !!
507  !! Calculate the deltaQgnc value for any GNC in the GNC list
508  !<
509  function deltaqgnc(this, ignc)
510  ! -- modules
511  use constantsmodule, only: dzero
512  ! -- Return
513  real(dp) :: deltaqgnc
514  ! -- dummy
515  class(ghostnodetype) :: this
516  integer(I4B), intent(in) :: ignc
517  ! -- local
518  integer(I4B) :: noden, nodem, nodej, jidx
519  real(dp) :: sigalj, alpha, hd, aterm, cond
520  !
521  ! -- initialize values
522  deltaqgnc = dzero
523  sigalj = dzero
524  hd = dzero
525  noden = this%nodem1(ignc)
526  nodem = this%nodem2(ignc)
527  !
528  ! -- calculate deltaQgnc
529  if (this%m1%ibound(noden) /= 0 .and. this%m2%ibound(nodem) /= 0) then
530  jloop: do jidx = 1, this%numjs
531  nodej = this%nodesj(jidx, ignc)
532  if (nodej == 0) cycle jloop
533  if (this%m1%ibound(nodej) == 0) cycle jloop
534  alpha = this%alphasj(jidx, ignc)
535  sigalj = sigalj + alpha
536  hd = hd + alpha * this%m1%x(nodej)
537  end do jloop
538  aterm = sigalj * this%m1%x(noden) - hd
539  cond = this%cond(ignc)
540  deltaqgnc = aterm * cond
541  end if
542  end function deltaqgnc
543 
544  !> @brief Allocate gnc scalar variables
545  !<
546  subroutine allocate_scalars(this)
547  ! -- modules
549  ! -- dummy
550  class(ghostnodetype) :: this
551  !
552  ! -- allocate scalars in NumericalPackageType
553  call this%NumericalPackageType%allocate_scalars()
554  !
555  call mem_allocate(this%smgnc, 'SMGNC', this%memoryPath)
556  call mem_allocate(this%implicit, 'IMPLICIT', this%memoryPath)
557  call mem_allocate(this%i2kn, 'I2KN', this%memoryPath)
558  call mem_allocate(this%nexg, 'NEXG', this%memoryPath)
559  call mem_allocate(this%numjs, 'NUMJS', this%memoryPath)
560  !
561  ! -- Initialize values
562  this%smgnc = .true.
563  this%implicit = .true.
564  this%i2kn = .false.
565  this%nexg = 0
566  this%numjs = 0
567  end subroutine allocate_scalars
568 
569  !> @brief Allocate gnc scalar variables
570  !<
571  subroutine allocate_arrays(this)
572  ! -- modules
574  ! -- dummy
575  class(ghostnodetype) :: this
576  !
577  ! -- allocate memory for arrays
578  call mem_allocate(this%nodem1, this%nexg, 'NODEM1', this%memoryPath)
579  call mem_allocate(this%nodem2, this%nexg, 'NODEM2', this%memoryPath)
580  call mem_allocate(this%nodesj, this%numjs, this%nexg, 'NODESJ', &
581  this%memoryPath)
582  call mem_allocate(this%alphasj, this%numjs, this%nexg, 'ALPHASJ', &
583  this%memoryPath)
584  call mem_allocate(this%cond, this%nexg, 'COND', this%memoryPath)
585  call mem_allocate(this%idxglo, this%nexg, 'IDXGLO', this%memoryPath)
586  call mem_allocate(this%idiagn, this%nexg, 'IDIAGN', this%memoryPath)
587  call mem_allocate(this%idiagm, this%nexg, 'IDIAGM', this%memoryPath)
588  call mem_allocate(this%idxsymglo, this%nexg, 'IDXSYMGLO', this%memoryPath)
589  if (this%implicit) then
590  call mem_allocate(this%jposinrown, this%numjs, this%nexg, 'JPOSINROWN', &
591  this%memoryPath)
592  call mem_allocate(this%jposinrowm, this%numjs, this%nexg, 'JPOSINROWM', &
593  this%memoryPath)
594  else
595  call mem_allocate(this%jposinrown, 0, 0, 'JPOSINROWN', this%memoryPath)
596  call mem_allocate(this%jposinrowm, 0, 0, 'JPOSINROWM', this%memoryPath)
597  end if
598  end subroutine allocate_arrays
599 
600  !> @brief Deallocate memory
601  !<
602  subroutine gnc_da(this)
603  ! -- modules
605  ! -- dummy
606  class(ghostnodetype) :: this
607  !
608  call mem_deallocate(this%smgnc)
609  call mem_deallocate(this%implicit)
610  call mem_deallocate(this%i2kn)
611  call mem_deallocate(this%nexg)
612  call mem_deallocate(this%numjs)
613  !
614  ! -- Arrays
615  if (this%inunit > 0) then
616  call mem_deallocate(this%nodem1)
617  call mem_deallocate(this%nodem2)
618  call mem_deallocate(this%nodesj)
619  call mem_deallocate(this%alphasj)
620  call mem_deallocate(this%cond)
621  call mem_deallocate(this%idxglo)
622  call mem_deallocate(this%idiagn)
623  call mem_deallocate(this%idiagm)
624  call mem_deallocate(this%idxsymglo)
625  call mem_deallocate(this%jposinrown)
626  call mem_deallocate(this%jposinrowm)
627  end if
628  !
629  ! -- deallocate NumericalPackageType
630  call this%NumericalPackageType%da()
631  end subroutine gnc_da
632 
633  !> @brief Read a gnc options block
634  !!
635  !! Read options from input file
636  !<
637  subroutine read_options(this)
638  ! -- modules
639  use simmodule, only: store_error
640  use simvariablesmodule, only: errmsg
641  ! -- dummy
642  class(ghostnodetype) :: this
643  ! -- local
644  character(len=LINELENGTH) :: keyword
645  integer(I4B) :: ierr
646  logical :: isfound, endOfBlock
647  !
648  ! -- get options block
649  call this%parser%GetBlock('OPTIONS', isfound, ierr, &
650  supportopenclose=.true., blockrequired=.false.)
651  !
652  ! -- parse options block if detected
653  if (isfound) then
654  write (this%iout, '(1x,a)') 'PROCESSING GNC OPTIONS'
655  do
656  call this%parser%GetNextLine(endofblock)
657  if (endofblock) exit
658  call this%parser%GetStringCaps(keyword)
659  select case (keyword)
660  case ('PRINT_INPUT')
661  this%iprpak = 1
662  write (this%iout, '(4x,a)') &
663  'THE LIST OF GHOST-NODE CORRECTIONS WILL BE PRINTED.'
664  case ('PRINT_FLOWS')
665  this%iprflow = 1
666  write (this%iout, '(4x,a)') &
667  'DELTAQGNC VALUES WILL BE PRINTED TO THE LIST FILE.'
668  case ('I2KN')
669  this%i2kn = .true.
670  write (this%iout, '(4x,a)') &
671  'SECOND ORDER CORRECTION WILL BE APPLIED.'
672  case ('EXPLICIT')
673  this%implicit = .false.
674  write (this%iout, '(4x,a)') 'GHOST NODE CORRECTION IS EXPLICIT.'
675  case default
676  write (errmsg, '(a,a)') 'Unknown GNC option: ', &
677  trim(keyword)
678  call store_error(errmsg)
679  call this%parser%StoreErrorUnit()
680  end select
681  end do
682  write (this%iout, '(1x,a)') 'END OF GNC OPTIONS'
683  end if
684  !
685  ! -- Set the iasym flag if the correction is implicit
686  if (this%implicit) this%iasym = 1
687  end subroutine read_options
688 
689  !> @brief Single Model GNC Read Dimensions
690  !!
691  !! Read dimensions (size of gnc list) from input file
692  !<
693  subroutine read_dimensions(this)
694  ! -- modules
695  use simmodule, only: store_error
696  use simvariablesmodule, only: errmsg
697  ! -- dummy
698  class(ghostnodetype) :: this
699  ! -- local
700  character(len=LINELENGTH) :: keyword
701  integer(I4B) :: ierr
702  logical :: isfound, endOfBlock
703  !
704  ! -- get options block
705  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
706  supportopenclose=.true.)
707  !
708  ! -- parse options block if detected
709  if (isfound) then
710  write (this%iout, '(1x,a)') 'PROCESSING GNC DIMENSIONS'
711  do
712  call this%parser%GetNextLine(endofblock)
713  if (endofblock) exit
714  call this%parser%GetStringCaps(keyword)
715  select case (keyword)
716  case ('NUMGNC')
717  this%nexg = this%parser%GetInteger()
718  write (this%iout, '(4x,a,i7)') 'NUMGNC = ', this%nexg
719  case ('NUMALPHAJ')
720  this%numjs = this%parser%GetInteger()
721  write (this%iout, '(4x,a,i7)') 'NUMAPHAJ = ', this%numjs
722  case default
723  write (errmsg, '(a,a)') 'Unknown GNC dimension: ', &
724  trim(keyword)
725  call store_error(errmsg)
726  call this%parser%StoreErrorUnit()
727  end select
728  end do
729  write (this%iout, '(1x,a)') 'END OF GNC DIMENSIONS'
730  else
731  call store_error('Required DIMENSIONS block not found.', terminate=.true.)
732  end if
733  end subroutine read_dimensions
734 
735  !> @brief Read a GNCDATA block
736  !!
737  !! Read list of GNCs from input file
738  !<
739  subroutine read_data(this)
740  ! -- modules
742  use simvariablesmodule, only: errmsg
743  ! -- dummy
744  class(ghostnodetype) :: this
745  ! -- local
746  character(len=LINELENGTH) :: line, nodestr, fmtgnc, cellid, &
747  cellidm, cellidn
748  integer(I4B) :: lloc, ierr, ival
749  integer(I4B) :: ignc, jidx, nodeun, nodeum, nerr
750  integer(I4B), dimension(:), allocatable :: nodesuj
751  logical :: isfound, endOfBlock
752  !
753  ! -- Construct the fmtgnc format
754  write (fmtgnc, '("(2i10,",i0,"i10,",i0, "(1pg15.6))")') this%numjs, &
755  this%numjs
756  !
757  ! -- Allocate the temporary nodesuj, which stores the user-based nodej
758  ! node numbers
759  allocate (nodesuj(this%numjs))
760  !
761  ! -- get GNCDATA block
762  call this%parser%GetBlock('GNCDATA', isfound, ierr, supportopenclose=.true.)
763  !
764  ! -- process GNC data
765  if (isfound) then
766  write (this%iout, '(1x,a)') 'PROCESSING GNCDATA'
767  do ignc = 1, this%nexg
768  call this%parser%GetNextLine(endofblock)
769  if (endofblock) exit
770  call this%parser%GetCurrentLine(line)
771  lloc = 1
772  !
773  ! -- cellidn (read as cellid and convert to user node)
774  call this%parser%GetCellid(this%m1%dis%ndim, cellidn)
775  nodeun = this%m1%dis%nodeu_from_cellid(cellidn, this%parser%iuactive, &
776  this%iout)
777  !
778  ! -- convert user node to reduced node number
779  call this%nodeu_to_noder(nodeun, this%nodem1(ignc), this%m1)
780  !
781  ! -- cellidm (read as cellid and convert to user node)
782  call this%parser%GetCellid(this%m2%dis%ndim, cellidm)
783  nodeum = this%m2%dis%nodeu_from_cellid(cellidm, this%parser%iuactive, &
784  this%iout)
785  !
786  ! -- convert user node to reduced node number
787  call this%nodeu_to_noder(nodeum, this%nodem2(ignc), this%m2)
788  !
789  ! -- cellidsj (read as cellid)
790  do jidx = 1, this%numjs
791  ! read cellidj as cellid of model 1
792  call this%parser%GetCellid(this%m1%dis%ndim, cellid)
793  ival = this%m1%dis%nodeu_from_cellid(cellid, this%parser%iuactive, &
794  this%iout, allow_zero=.true.)
795  nodesuj(jidx) = ival
796  if (ival > 0) then
797  call this%nodeu_to_noder(ival, this%nodesj(jidx, ignc), this%m1)
798  else
799  this%nodesj(jidx, ignc) = 0
800  end if
801  end do
802  !
803  ! -- alphaj
804  do jidx = 1, this%numjs
805  this%alphasj(jidx, ignc) = this%parser%GetDouble()
806  end do
807  !
808  ! -- Echo if requested
809  if (this%iprpak /= 0) &
810  write (this%iout, fmtgnc) nodeun, nodeum, &
811  (nodesuj(jidx), jidx=1, this%numjs), &
812  (this%alphasj(jidx, ignc), jidx=1, this%numjs)
813  !
814  ! -- Check to see if noden is outside of active domain
815  if (this%nodem1(ignc) <= 0) then
816  call this%m1%dis%nodeu_to_string(nodeun, nodestr)
817  write (errmsg, *) &
818  trim(adjustl(this%m1%name))// &
819  ' Cell is outside active grid domain: '// &
820  trim(adjustl(nodestr))
821  call store_error(errmsg)
822  end if
823  !
824  ! -- Check to see if nodem is outside of active domain
825  if (this%nodem2(ignc) <= 0) then
826  call this%m2%dis%nodeu_to_string(nodeum, nodestr)
827  write (errmsg, *) &
828  trim(adjustl(this%m2%name))// &
829  ' Cell is outside active grid domain: '// &
830  trim(adjustl(nodestr))
831  call store_error(errmsg)
832  end if
833  !
834  ! -- Check to see if any nodejs are outside of active domain
835  do jidx = 1, this%numjs
836  if (this%nodesj(jidx, ignc) < 0) then
837  call this%m1%dis%nodeu_to_string(nodesuj(jidx), nodestr)
838  write (errmsg, *) &
839  trim(adjustl(this%m1%name))// &
840  ' Cell is outside active grid domain: '// &
841  trim(adjustl(nodestr))
842  call store_error(errmsg)
843  end if
844  end do
845  !
846  end do
847  !
848  ! -- Stop if errors
849  nerr = count_errors()
850  if (nerr > 0) then
851  call store_error('Errors encountered in GNC input file.')
852  call this%parser%StoreErrorUnit()
853  end if
854  !
855  write (this%iout, '(1x,a)') 'END OF GNCDATA'
856  else
857  write (errmsg, '(a)') 'Required GNCDATA block not found.'
858  call store_error(errmsg)
859  call this%parser%StoreErrorUnit()
860  end if
861  !
862  ! -- deallocate nodesuj array
863  deallocate (nodesuj)
864  end subroutine read_data
865 
866  !> @brief Convert the user-based node number into a reduced number
867  !<
868  subroutine nodeu_to_noder(this, nodeu, noder, model)
869  ! -- modules
871  use simmodule, only: store_error
872  use simvariablesmodule, only: errmsg
873  ! -- dummy
874  class(ghostnodetype) :: this
875  integer(I4B), intent(in) :: nodeu
876  integer(I4B), intent(inout) :: noder
877  class(numericalmodeltype), intent(in) :: model
878  !
879  if (nodeu < 1 .or. nodeu > model%dis%nodesuser) then
880  write (errmsg, *) &
881  trim(adjustl(model%name))// &
882  ' node number < 0 or > model nodes: ', nodeu
883  call store_error(errmsg)
884  else
885  noder = model%dis%get_nodenumber(nodeu, 0)
886  end if
887  end subroutine nodeu_to_noder
888 
889 end module ghostnodemodule
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
subroutine read_dimensions(this)
Single Model GNC Read Dimensions.
Definition: GhostNode.f90:694
subroutine nodeu_to_noder(this, nodeu, noder, model)
Convert the user-based node number into a reduced number.
Definition: GhostNode.f90:869
subroutine gnc_da(this)
Deallocate memory.
Definition: GhostNode.f90:603
subroutine gnc_fn(this, kiter, matrix_sln, condsat, ihc_opt, ivarcv_opt, ictm1_opt, ictm2_opt)
Fill GNC Newton terms.
Definition: GhostNode.f90:342
subroutine, public gnc_cr(gncobj, name_parent, inunit, iout)
Create new GNC exchange object.
Definition: GhostNode.f90:61
subroutine read_data(this)
Read a GNCDATA block.
Definition: GhostNode.f90:740
subroutine allocate_scalars(this)
Allocate gnc scalar variables.
Definition: GhostNode.f90:547
subroutine gnc_fc(this, kiter, matrix)
Fill matrix terms.
Definition: GhostNode.f90:281
subroutine gnc_df(this, m1, m2)
Initialize a gnc object.
Definition: GhostNode.f90:85
subroutine read_options(this)
Read a gnc options block.
Definition: GhostNode.f90:638
subroutine allocate_arrays(this)
Allocate gnc scalar variables.
Definition: GhostNode.f90:572
subroutine gnc_ot(this, ibudfl)
Single Model GNC Output.
Definition: GhostNode.f90:450
subroutine gnc_cq(this, flowja)
Add GNC to flowja.
Definition: GhostNode.f90:479
subroutine gnc_mc(this, matrix_sln)
Single or Two-Model GNC Map Connections.
Definition: GhostNode.f90:173
subroutine gnc_fmsav(this, kiter, matrix)
Store the n-m Picard conductance in cond prior to the Newton terms terms being added.
Definition: GhostNode.f90:252
subroutine gnc_ac(this, sparse)
Single or Two-Model GNC Add Connections.
Definition: GhostNode.f90:135
real(dp) function deltaqgnc(this, ignc)
Single Model deltaQgnc (ghost node correction flux)
Definition: GhostNode.f90:510
This module defines variable data types.
Definition: kind.f90:8
This module contains the base numerical package type.
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
real(dp) function squadraticsaturationderivative(top, bot, x, eps)
@ brief Derivative of the quadratic saturation function