MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
ConnectionBuilder.f90
Go to the documentation of this file.
2  use kindmodule, only: i4b, lgp
4  use simvariablesmodule, only: iout
5  use listmodule, only: listtype, isequaliface, listnodetype
13  cast_as_smc, &
16 
17  implicit none
18  private
19 
20  type, public :: connectionbuildertype
21  logical(LGP) :: dev_always_ifmod = .false. !< development option: force interface model on all exchanges
22  contains
23  procedure, pass(this) :: processsolution
24  procedure, private, pass(this) :: processexchanges
25  procedure, private, pass(this) :: setconnectionstosolution
26  procedure, private, pass(this) :: createmodelconnectivity
27  end type connectionbuildertype
28 
29 contains
30 
31  !> @brief Process the exchanges in the solution into model connections
32  !!
33  !! This routine processes all exchanges in a solution and,
34  !! when required, creates model connections of the proper
35  !! type (GWF-GWF, GWT-GWT, ...) for a subset. It removes this
36  !! subset of exchanges from the solution and replaces them with the
37  !! created connections.
38  !<
39  subroutine processsolution(this, solution)
40  class(connectionbuildertype) :: this !< the connection builder object
41  class(basesolutiontype), pointer :: solution !< the solution for which the exchanges are processed
42  ! local
43  class(numericalsolutiontype), pointer :: numSol
44  type(listtype) :: newConnections
45 
46  ! we only deal with Num. Sol. here
47  select type (solution)
48  class is (numericalsolutiontype)
49  numsol => solution
50  class default
51  return
52  end select
53 
54  ! create the connections and add local exchanges
55  call this%processExchanges(numsol%exchangelist, newconnections)
56  if (newconnections%Count() == 0) then
57  return
58  end if
59 
60  write (iout, '(1x,a,i0,a,a)') 'Created ', newconnections%Count(), &
61  ' model connections for solution ', trim(solution%name)
62 
63  ! create the topology of models participating in the interfaces
64  call this%createModelConnectivity(newconnections)
65 
66  ! replace numerical exchanges in solution with connections
67  call this%setConnectionsToSolution(newconnections, numsol)
68 
69  ! clean up local resources
70  call newconnections%Clear(destroy=.false.)
71 
72  end subroutine processsolution
73 
74  !> @brief Create connections from exchanges
75  !!
76  !! If the configuration demands it, this will create connections,
77  !! for the exchanges (one connection per exchange) add them to
78  !! the global list, and return them as @param newConnections
79  !<
80  subroutine processexchanges(this, exchanges, newConnections)
82  class(connectionbuildertype) :: this !< the connection builder object
83  type(listtype), pointer, intent(in) :: exchanges !< the list of exchanges to process
84  type(listtype), intent(inout) :: newConnections !< the newly created connections
85  ! local
86  class(disconnexchangetype), pointer :: conEx
87  class(baseexchangetype), pointer :: baseEx
88  integer(I4B) :: iex, ibasex
89  class(spatialmodelconnectiontype), pointer :: modelConnection
90  logical(LGP) :: isPeriodic
91 
92  do iex = 1, exchanges%Count()
93  conex => getdisconnexchangefromlist(exchanges, iex)
94  if (.not. associated(conex)) then
95  ! if it is not DisConnExchangeType, we can skip it
96  cycle
97  end if
98 
99  ! for now, if we have XT3D on the interface, we use a connection,
100  ! (this will be more generic in the future)
101  if (conex%use_interface_model() .or. conex%dev_ifmod_on &
102  .or. this%dev_always_ifmod) then
103 
104  ! we should not get period connections here
105  isperiodic = (conex%v_model1 == conex%v_model2)
106  if (isperiodic) then
107  write (*, *) 'Error (which should never happen): interface model '// &
108  'does not support periodic boundary condition'
109  call ustop()
110  end if
111 
112  if (conex%v_model1%is_local) then
113  ! create model connection for model 1
114  modelconnection => createmodelconnection(conex%model1, conex)
115  call add_smc_to_list(baseconnectionlist, modelconnection)
116  call add_smc_to_list(newconnections, modelconnection)
117  end if
118 
119  ! and for model 2
120  if (conex%v_model2%is_local) then
121  modelconnection => createmodelconnection(conex%model2, conex)
122  call add_smc_to_list(baseconnectionlist, modelconnection)
123  call add_smc_to_list(newconnections, modelconnection)
124  end if
125 
126  ! remove this exchange from the base list, ownership
127  ! now lies with the connection
128  do ibasex = 1, baseexchangelist%Count()
129  baseex => getbaseexchangefromlist(baseexchangelist, ibasex)
130  if (conex%id == baseex%id) then
131  call baseexchangelist%RemoveNode(ibasex, .false.)
132  exit
133  end if
134  end do
135 
136  end if
137  end do
138 
139  end subroutine processexchanges
140 
141  !> @brief Create a model connection of a given type
142  !!
143  !! This is a factory method to create the various types
144  !! of model connections
145  !<
146  function createmodelconnection(model, exchange) result(connection)
147  use simmodule, only: ustop
151  use gwfmodule, only: gwfmodeltype
152 
153  class(numericalmodeltype), pointer, intent(in) :: model !< the model for which the connection will be created
154  class(disconnexchangetype), pointer, intent(in) :: exchange !< the type of connection
155  class(spatialmodelconnectiontype), pointer :: connection !< the created connection
156 
157  ! different concrete connection types:
158  class(gwfgwfconnectiontype), pointer :: flowconnection => null()
159  class(gwtgwtconnectiontype), pointer :: transportconnection => null()
160  class(gwegweconnectiontype), pointer :: energytransportconnection => null()
161 
162  connection => null()
163 
164  ! select on type of connection to create
165  select case (exchange%typename)
166  case ('GWF-GWF')
167  allocate (gwfgwfconnectiontype :: flowconnection)
168  call flowconnection%construct(model, exchange)
169  connection => flowconnection
170  flowconnection => null()
171  case ('GWT-GWT')
172  allocate (gwtgwtconnectiontype :: transportconnection)
173  call transportconnection%construct(model, exchange)
174  connection => transportconnection
175  transportconnection => null()
176  case ('GWE-GWE')
177  allocate (gwegweconnectiontype :: energytransportconnection)
178  call energytransportconnection%construct(model, exchange)
179  connection => energytransportconnection
180  energytransportconnection => null()
181  case default
182  write (*, *) 'Error (which should never happen): '// &
183  'undefined exchangetype found'
184  call ustop()
185  end select
186 
187  end function createmodelconnection
188 
189  !> @brief Set connections to the solution
190  !!
191  !! This adds the connections to the solution and removes
192  !! those exchanges which are replaced by a connection
193  !<
194  subroutine setconnectionstosolution(this, connections, solution)
195  class(connectionbuildertype) :: this !< the connection builder object
196  type(listtype), intent(inout) :: connections !< the connections created for the solution
197  class(numericalsolutiontype), pointer, intent(in) :: solution !< the solution to which the connections are set
198  ! local
199  type(listtype) :: keepList
200  class(*), pointer :: exPtr, exPtr2, connPtr
201  class(spatialmodelconnectiontype), pointer :: conn
202  integer(I4B) :: iex, iconn
203  logical(LGP) :: keepExchange
204 
205  ! first add all exchanges not replaced by the connections to a list
206  do iex = 1, solution%exchangelist%Count()
207  exptr => solution%exchangelist%GetItem(iex)
208  ! will this exchange be replaced by a connection?
209  keepexchange = .true.
210  do iconn = 1, connections%Count()
211  conn => get_smc_from_list(connections, iconn)
212  exptr2 => conn%prim_exchange
213  if (associated(exptr2, exptr)) then
214  ! if so, don't add it to the list
215  keepexchange = .false.
216  exit
217  end if
218  end do
219 
220  if (keepexchange) then
221  call keeplist%Add(exptr)
222  end if
223  end do
224 
225  ! first add persisting exchanges
226  call solution%exchangelist%Clear(destroy=.false.)
227  do iex = 1, keeplist%Count()
228  exptr => keeplist%GetItem(iex)
229  call solution%exchangelist%Add(exptr)
230  end do
231 
232  ! now add connections
233  do iconn = 1, connections%Count()
234  connptr => connections%GetItem(iconn)
235  call solution%exchangelist%Add(connptr)
236  end do
237 
238  ! clean up
239  call keeplist%Clear(destroy=.false.)
240 
241  end subroutine setconnectionstosolution
242 
243  !> @brief Create connectivity of models which contribute to the interface
244  !!
245  !! This loops over all connections and creates a halo with all
246  !! models from the numerical solution. The model halo will be used to
247  !! extend the interface grid to include cells from models which are
248  !< indirectly connected, through yet another exchange object.
249  subroutine createmodelconnectivity(this, connections)
250  class(connectionbuildertype) :: this !< the connection builder object
251  type(listtype), intent(inout) :: connections !< all connections that are created for this solution
252  ! local
253  integer(I4B) :: iconn
254  class(spatialmodelconnectiontype), pointer :: modelConn
255 
256  ! create halo for the model connections
257  do iconn = 1, connections%Count()
258  modelconn => get_smc_from_list(connections, iconn)
259  call modelconn%createModelHalo()
260  end do
261 
262  end subroutine createmodelconnectivity
263 
264 end module connectionbuildermodule
class(baseexchangetype) function, pointer, public getbaseexchangefromlist(list, idx)
Retrieve a specific BaseExchangeType object from a list.
subroutine processsolution(this, solution)
Process the exchanges in the solution into model connections.
class(spatialmodelconnectiontype) function, pointer createmodelconnection(model, exchange)
Create a model connection of a given type.
subroutine setconnectionstosolution(this, connections, solution)
Set connections to the solution.
subroutine createmodelconnectivity(this, connections)
Create connectivity of models which contribute to the interface.
subroutine processexchanges(this, exchanges, newConnections)
Create connections from exchanges.
class(disconnexchangetype) function, pointer, public getdisconnexchangefromlist(list, idx)
Definition: gwf.f90:1
This module defines variable data types.
Definition: kind.f90:8
type(listtype), public baseexchangelist
Definition: mf6lists.f90:25
type(listtype), public baseconnectionlist
Definition: mf6lists.f90:28
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public ustop(stopmess, ioutlocal)
Stop the simulation.
Definition: Sim.f90:315
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
This module contains simulation variables.
Definition: SimVariables.f90:9
integer(i4b) iout
file unit number for simulation output
class(spatialmodelconnectiontype) function, pointer, public get_smc_from_list(list, idx)
Get the connection from a list.
class(spatialmodelconnectiontype) function, pointer, public cast_as_smc(obj)
Cast to SpatialModelConnectionType.
subroutine, public add_smc_to_list(list, conn)
Add connection to a list.
Exchange based on connection between discretizations of DisBaseType. The data specifies the connectio...
Connects a GWE model to other GWE models in space. Derives from NumericalExchangeType so the solution...
Connecting a GWF model to other models in space, implements NumericalExchangeType so the solution can...
Connects a GWT model to other GWT models in space. Derives from NumericalExchangeType so the solution...
A generic heterogeneous doubly-linked list.
Definition: List.f90:10
Class to manage spatial connection of a model to one or more models of the same type....