17 logical,
pointer :: smgnc => null()
18 logical,
pointer ::
implicit => null()
19 logical,
pointer :: i2kn => null()
20 integer(I4B),
pointer :: nexg => null()
21 integer(I4B),
pointer :: numjs => null()
24 integer(I4B),
dimension(:),
pointer,
contiguous :: nodem1 => null()
25 integer(I4B),
dimension(:),
pointer,
contiguous :: nodem2 => null()
26 integer(I4B),
dimension(:, :),
pointer,
contiguous :: nodesj => null()
27 real(dp),
dimension(:),
pointer,
contiguous :: cond => null()
28 integer(I4B),
dimension(:),
pointer,
contiguous :: idxglo => null()
29 integer(I4B),
dimension(:),
pointer,
contiguous :: idxsymglo => null()
30 real(dp),
dimension(:, :),
pointer,
contiguous :: alphasj => null()
31 integer(I4B),
dimension(:),
pointer,
contiguous :: idiagn => null()
32 integer(I4B),
dimension(:),
pointer,
contiguous :: idiagm => null()
33 integer(I4B),
dimension(:, :),
pointer,
contiguous :: jposinrown => null()
34 integer(I4B),
dimension(:, :),
pointer,
contiguous :: jposinrowm => null()
60 subroutine gnc_cr(gncobj, name_parent, inunit, iout)
63 character(len=*),
intent(in) :: name_parent
64 integer(I4B),
intent(in) :: inunit
65 integer(I4B),
intent(in) :: iout
72 call gncobj%set_names(1, name_parent,
'GNC',
'GNC')
75 call gncobj%allocate_scalars()
78 gncobj%inunit = inunit
105 call this%parser%Initialize(this%inunit, this%iout)
108 call this%read_options()
111 call this%read_dimensions()
114 call this%allocate_arrays()
117 call this%read_data()
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.'
141 integer(I4B) :: ignc, jidx, noden, nodem, nodej
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)
180 integer(I4B) :: noden, nodem, ipos, ignc, jidx, nodej
182 character(len=*),
parameter :: fmterr = &
183 "('GHOST NODE ERROR. Cell ', i0, ' in model ', a, &
184 &' is not connected to cell ', i0, ' in model ', a)"
188 do ignc = 1, this%nexg
189 noden = this%nodem1(ignc) + this%m1%moffset
190 nodem = this%nodem2(ignc) + this%m2%moffset
193 this%idiagn(ignc) = matrix_sln%get_position_diag(noden)
194 this%idiagm(ignc) = matrix_sln%get_position_diag(nodem)
201 this%idxglo(ignc) = matrix_sln%get_position(noden, nodem)
202 this%idxsymglo(ignc) = matrix_sln%get_position(nodem, noden)
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)
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
224 do jidx = 1, this%numjs
225 nodej = this%nodesj(jidx, ignc)
226 if (nodej > 0) nodej = nodej + this%m1%moffset
231 this%jposinrown(jidx, ignc) = ipos
233 this%jposinrown(jidx, ignc) = matrix_sln%get_position(noden, nodej)
239 this%jposinrowm(jidx, ignc) = ipos
241 this%jposinrowm(jidx, ignc) = matrix_sln%get_position(nodem, nodej)
256 integer(I4B),
intent(in) :: kiter
259 integer(I4B) :: ignc, ipos
264 gncloop:
do ignc = 1, this%nexg
265 ipos = this%idxglo(ignc)
267 cond = matrix%get_value_pos(ipos)
271 this%cond(ignc) = cond
285 integer(I4B),
intent(in) :: kiter
288 integer(I4B) :: ignc, j, noden, nodem, ipos, jidx, iposjn, iposjm
289 real(DP) :: cond, alpha, aterm, rterm
293 if (this%smgnc)
call this%gnc_fmsav(kiter, matrix)
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)
307 alpha = this%alphasj(jidx, ignc)
308 if (alpha ==
dzero) cycle
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)
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
340 subroutine gnc_fn(this, kiter, matrix_sln, condsat, ihc_opt, &
341 ivarcv_opt, ictm1_opt, ictm2_opt)
347 integer(I4B) :: kiter
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
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
364 if (
present(ivarcv_opt)) ivarcv = ivarcv_opt
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
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)
385 if (ihc == 0 .and. ivarcv == 0) cycle
389 if (this%m2%x(nodem) > this%m1%x(noden)) iups = 1
394 topup = this%m1%dis%top(noden)
395 botup = this%m1%dis%bot(noden)
397 if (
present(ictm1_opt)) ictup = ictm1_opt(noden)
398 xup = this%m1%x(noden)
400 topup = this%m2%dis%top(nodem)
401 botup = this%m2%dis%bot(nodem)
403 if (
present(ictm2_opt)) ictup = ictm2_opt(nodem)
404 xup = this%m2%x(nodem)
408 if (ictup == 0) cycle
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))
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))
425 term = consterm * derv
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)
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)
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)
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)
452 integer(I4B),
intent(in) :: ibudfl
455 real(DP) :: deltaQgnc
456 character(len=LINELENGTH) :: nodenstr, nodemstr
458 character(len=*),
parameter :: fmtgnc =
"(i10, 2a10, 2(1pg15.6))"
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)
481 real(DP),
dimension(:),
intent(inout) :: flowja
483 integer(I4B) :: ignc, n1, n2, ipos, isympos
484 real(DP) :: deltaQgnc
487 do ignc = 1, this%nexg
490 n1 = this%nodem1(ignc)
491 n2 = this%nodem2(ignc)
492 deltaqgnc = this%deltaQgnc(ignc)
495 ipos = this%m1%dis%con%getjaindex(n1, n2)
496 isympos = this%m1%dis%con%isym(ipos)
499 flowja(ipos) = flowja(ipos) + deltaqgnc
500 flowja(isympos) = flowja(isympos) - deltaqgnc
516 integer(I4B),
intent(in) :: ignc
518 integer(I4B) :: noden, nodem, nodej, jidx
519 real(dp) :: sigalj, alpha, hd, aterm, cond
525 noden = this%nodem1(ignc)
526 nodem = this%nodem2(ignc)
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)
538 aterm = sigalj * this%m1%x(noden) - hd
539 cond = this%cond(ignc)
553 call this%NumericalPackageType%allocate_scalars()
556 call mem_allocate(this%implicit,
'IMPLICIT', this%memoryPath)
563 this%implicit = .true.
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', &
582 call mem_allocate(this%alphasj, this%numjs, this%nexg,
'ALPHASJ', &
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', &
592 call mem_allocate(this%jposinrowm, this%numjs, this%nexg,
'JPOSINROWM', &
595 call mem_allocate(this%jposinrown, 0, 0,
'JPOSINROWN', this%memoryPath)
596 call mem_allocate(this%jposinrowm, 0, 0,
'JPOSINROWM', this%memoryPath)
615 if (this%inunit > 0)
then
630 call this%NumericalPackageType%da()
644 character(len=LINELENGTH) :: keyword
646 logical :: isfound, endOfBlock
649 call this%parser%GetBlock(
'OPTIONS', isfound, ierr, &
650 supportopenclose=.true., blockrequired=.false.)
654 write (this%iout,
'(1x,a)')
'PROCESSING GNC OPTIONS'
656 call this%parser%GetNextLine(endofblock)
658 call this%parser%GetStringCaps(keyword)
659 select case (keyword)
662 write (this%iout,
'(4x,a)') &
663 'THE LIST OF GHOST-NODE CORRECTIONS WILL BE PRINTED.'
666 write (this%iout,
'(4x,a)') &
667 'DELTAQGNC VALUES WILL BE PRINTED TO THE LIST FILE.'
670 write (this%iout,
'(4x,a)') &
671 'SECOND ORDER CORRECTION WILL BE APPLIED.'
673 this%implicit = .false.
674 write (this%iout,
'(4x,a)')
'GHOST NODE CORRECTION IS EXPLICIT.'
676 write (
errmsg,
'(a,a)')
'Unknown GNC option: ', &
679 call this%parser%StoreErrorUnit()
682 write (this%iout,
'(1x,a)')
'END OF GNC OPTIONS'
686 if (this%implicit) this%iasym = 1
700 character(len=LINELENGTH) :: keyword
702 logical :: isfound, endOfBlock
705 call this%parser%GetBlock(
'DIMENSIONS', isfound, ierr, &
706 supportopenclose=.true.)
710 write (this%iout,
'(1x,a)')
'PROCESSING GNC DIMENSIONS'
712 call this%parser%GetNextLine(endofblock)
714 call this%parser%GetStringCaps(keyword)
715 select case (keyword)
717 this%nexg = this%parser%GetInteger()
718 write (this%iout,
'(4x,a,i7)')
'NUMGNC = ', this%nexg
720 this%numjs = this%parser%GetInteger()
721 write (this%iout,
'(4x,a,i7)')
'NUMAPHAJ = ', this%numjs
723 write (
errmsg,
'(a,a)')
'Unknown GNC dimension: ', &
726 call this%parser%StoreErrorUnit()
729 write (this%iout,
'(1x,a)')
'END OF GNC DIMENSIONS'
731 call store_error(
'Required DIMENSIONS block not found.', terminate=.true.)
746 character(len=LINELENGTH) :: line, nodestr, fmtgnc, cellid, &
748 integer(I4B) :: lloc, ierr, ival
749 integer(I4B) :: ignc, jidx, nodeun, nodeum, nerr
750 integer(I4B),
dimension(:),
allocatable :: nodesuj
751 logical :: isfound, endOfBlock
754 write (fmtgnc,
'("(2i10,",i0,"i10,",i0, "(1pg15.6))")') this%numjs, &
759 allocate (nodesuj(this%numjs))
762 call this%parser%GetBlock(
'GNCDATA', isfound, ierr, supportopenclose=.true.)
766 write (this%iout,
'(1x,a)')
'PROCESSING GNCDATA'
767 do ignc = 1, this%nexg
768 call this%parser%GetNextLine(endofblock)
770 call this%parser%GetCurrentLine(line)
774 call this%parser%GetCellid(this%m1%dis%ndim, cellidn)
775 nodeun = this%m1%dis%nodeu_from_cellid(cellidn, this%parser%iuactive, &
779 call this%nodeu_to_noder(nodeun, this%nodem1(ignc), this%m1)
782 call this%parser%GetCellid(this%m2%dis%ndim, cellidm)
783 nodeum = this%m2%dis%nodeu_from_cellid(cellidm, this%parser%iuactive, &
787 call this%nodeu_to_noder(nodeum, this%nodem2(ignc), this%m2)
790 do jidx = 1, this%numjs
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.)
797 call this%nodeu_to_noder(ival, this%nodesj(jidx, ignc), this%m1)
799 this%nodesj(jidx, ignc) = 0
804 do jidx = 1, this%numjs
805 this%alphasj(jidx, ignc) = this%parser%GetDouble()
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)
815 if (this%nodem1(ignc) <= 0)
then
816 call this%m1%dis%nodeu_to_string(nodeun, nodestr)
818 trim(adjustl(this%m1%name))// &
819 ' Cell is outside active grid domain: '// &
820 trim(adjustl(nodestr))
825 if (this%nodem2(ignc) <= 0)
then
826 call this%m2%dis%nodeu_to_string(nodeum, nodestr)
828 trim(adjustl(this%m2%name))// &
829 ' Cell is outside active grid domain: '// &
830 trim(adjustl(nodestr))
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)
839 trim(adjustl(this%m1%name))// &
840 ' Cell is outside active grid domain: '// &
841 trim(adjustl(nodestr))
851 call store_error(
'Errors encountered in GNC input file.')
852 call this%parser%StoreErrorUnit()
855 write (this%iout,
'(1x,a)')
'END OF GNCDATA'
857 write (
errmsg,
'(a)')
'Required GNCDATA block not found.'
859 call this%parser%StoreErrorUnit()
875 integer(I4B),
intent(in) :: nodeu
876 integer(I4B),
intent(inout) :: noder
879 if (nodeu < 1 .or. nodeu > model%dis%nodesuser)
then
881 trim(adjustl(model%name))// &
882 ' node number < 0 or > model nodes: ', nodeu
885 noder = model%dis%get_nodenumber(nodeu, 0)
This module contains block parser methods.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
real(dp), parameter dzero
real constant zero
subroutine read_dimensions(this)
Single Model GNC Read Dimensions.
subroutine nodeu_to_noder(this, nodeu, noder, model)
Convert the user-based node number into a reduced number.
subroutine gnc_da(this)
Deallocate memory.
subroutine gnc_fn(this, kiter, matrix_sln, condsat, ihc_opt, ivarcv_opt, ictm1_opt, ictm2_opt)
Fill GNC Newton terms.
subroutine, public gnc_cr(gncobj, name_parent, inunit, iout)
Create new GNC exchange object.
subroutine read_data(this)
Read a GNCDATA block.
subroutine allocate_scalars(this)
Allocate gnc scalar variables.
subroutine gnc_fc(this, kiter, matrix)
Fill matrix terms.
subroutine gnc_df(this, m1, m2)
Initialize a gnc object.
subroutine read_options(this)
Read a gnc options block.
subroutine allocate_arrays(this)
Allocate gnc scalar variables.
subroutine gnc_ot(this, ibudfl)
Single Model GNC Output.
subroutine gnc_cq(this, flowja)
Add GNC to flowja.
subroutine gnc_mc(this, matrix_sln)
Single or Two-Model GNC Map Connections.
subroutine gnc_fmsav(this, kiter, matrix)
Store the n-m Picard conductance in cond prior to the Newton terms terms being added.
subroutine gnc_ac(this, sparse)
Single or Two-Model GNC Add Connections.
real(dp) function deltaqgnc(this, ignc)
Single Model deltaQgnc (ghost node correction flux)
This module defines variable data types.
This module contains the base numerical package type.
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
real(dp) function squadraticsaturationderivative(top, bot, x, eps)
@ brief Derivative of the quadratic saturation function