boundary_farfield.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 2D hydrodynamical simulation program #
4!# module: boundary_farfield.f90 #
5!# #
6!# Copyright (C) 2006-2024 #
7!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8!# Björn Sperling <sperling@astrophysik.uni-kiel.de> #
9!# #
10!# This program is free software; you can redistribute it and/or modify #
11!# it under the terms of the GNU General Public License as published by #
12!# the Free Software Foundation; either version 2 of the License, or (at #
13!# your option) any later version. #
14!# #
15!# This program is distributed in the hope that it will be useful, but #
16!# WITHOUT ANY WARRANTY; without even the implied warranty of #
17!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18!# NON INFRINGEMENT. See the GNU General Public License for more #
19!# details. #
20!# #
21!# You should have received a copy of the GNU General Public License #
22!# along with this program; if not, write to the Free Software #
23!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24!# #
25!#############################################################################
26
27!----------------------------------------------------------------------------!
37!----------------------------------------------------------------------------!
43 USE common_dict
44 IMPLICIT NONE
45 !--------------------------------------------------------------------------!
46 PRIVATE
48 REAL, DIMENSION(:,:,:), ALLOCATABLE :: rinv, lambda
49 REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: data
50 LOGICAL :: first_call = .true.
51 CONTAINS
53 PROCEDURE :: setboundarydata
54 PROCEDURE :: finalize
55 END TYPE boundary_farfield
56 CHARACTER(LEN=32), PARAMETER :: boundcond_name = "far-field in-/ouflow"
57 !--------------------------------------------------------------------------!
58 PUBLIC :: &
60 !--------------------------------------------------------------------------!
61
62CONTAINS
63
65 SUBROUTINE initboundary_farfield(this,Mesh,Physics,dir,config)
66 IMPLICIT NONE
67 !------------------------------------------------------------------------!
68 CLASS(boundary_farfield), INTENT(INOUT) :: this
69 CLASS(mesh_base), INTENT(IN) :: Mesh
70 CLASS(physics_base), INTENT(IN) :: Physics
71 TYPE(dict_typ), POINTER, INTENT(IN) :: config
72 INTEGER, INTENT(IN) :: dir
73 !------------------------------------------------------------------------!
74 INTEGER :: err = 0
75 !------------------------------------------------------------------------!
76 CALL this%InitBoundary(mesh,physics,farfield,boundcond_name,dir,config)
77 ! check if physics supports absorbing boundary conditions
78 IF (.NOT.physics%supports_farfield) &
79 CALL this%Error("InitBoundary_farfield", &
80 "boundary condition not supported for this type of physics")
81
82 ! allocate memory for boundary data and mask
83!CDIR IEXPAND
84 SELECT CASE(this%direction%GetType())
85 CASE(west,east)
86 ALLOCATE(this%Rinv(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
87 this%lambda(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
88 this%data(mesh%GINUM,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
89 stat=err)
90 CASE(south,north)
91 ALLOCATE(this%Rinv(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
92 this%lambda(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
93 this%data(mesh%IMIN:mesh%IMAX,mesh%GJNUM,mesh%KMIN:mesh%KMAX,physics%VNUM), &
94 stat=err)
95 CASE(bottom,top)
96 ALLOCATE(this%Rinv(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,physics%VNUM), &
97 this%lambda(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,physics%VNUM), &
98 this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%GKNUM,physics%VNUM), &
99 stat=err)
100 END SELECT
101 IF (err.NE.0) THEN
102 CALL this%Error("InitBoundary_farfield", "Unable to allocate memory.")
103 END IF
104 ! this ensures that Rinv is computed once for the data provided in this%data
105 ! by the user during initialization
106 this%first_call = .true.
107 ! reset Rinv and lambda
108 this%Rinv(:,:,:) = 0.0
109 this%lambda(:,:,:) = 0.0
110 this%data(:,:,:,:) = 0.0
111 END SUBROUTINE initboundary_farfield
112
113
115 SUBROUTINE setboundarydata(this,Mesh,Physics,time,pvar)
116 IMPLICIT NONE
117 !------------------------------------------------------------------------!
118 CLASS(boundary_farfield), INTENT(INOUT) :: this
119 CLASS(mesh_base), INTENT(IN) :: Mesh
120 CLASS(physics_base), INTENT(IN) :: Physics
121 REAL, INTENT(IN) :: time
122 CLASS(marray_compound), INTENT(INOUT) :: pvar
123 !------------------------------------------------------------------------!
124 INTEGER :: i,j,k
125 !------------------------------------------------------------------------!
126 SELECT CASE(this%direction%GetType())
127 CASE(west)
128 ! this must be done only once, but after the general boundary initialization
129 IF (this%first_call) THEN
130 ! compute Riemann invariants for the data (given in primitive variables)
131 ! provided by the user in the data array
132 DO i=1,mesh%GINUM
133 ! temporaryly store boundary data in ghost cells
134 pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
135 = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
136 ! compute Riemann invariants
137 CALL physics%CalculatePrim2RiemannX(mesh,mesh%IMIN-i,&
138 pvar,this%lambda,this%Rinv)
139 ! store Riemann invariants in data array
140 this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
141 = this%Rinv(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
142 END DO
143 ! skip the above computation for subsequent calls
144 this%first_call = .false.
145 END IF
146
147 DO i=1,mesh%GINUM
148 ! compute Riemann invariants
149 CALL physics%CalculatePrim2RiemannX(mesh,mesh%IMIN-i+1,&
150 pvar,this%lambda,this%Rinv)
151 ! set infinity Riemann invariants for inflow
152 WHERE (this%lambda(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:).GE.0.0)
153 this%Rinv(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
154 = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
155 END WHERE
156 ! transform back to primitive variables in ghost cells
157 CALL physics%CalculateRiemann2PrimX(mesh,mesh%IMIN-i,this%Rinv,pvar)
158 END DO
159 CASE(east)
160 ! this must be done only once, but after the general boundary initialization
161 IF (this%first_call) THEN
162 ! compute Riemann invariants for the data (given in primitive variables)
163 ! provided by the user in the data array
164 DO i=1,mesh%GINUM
165 ! temporaryly store boundary data in ghost cells
166 pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
167 = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
168 ! compute Riemann invariants
169 CALL physics%CalculatePrim2RiemannX(mesh,mesh%IMAX+i,&
170 pvar,this%lambda,this%Rinv)
171 ! store Riemann invariants in data array
172 this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
173 = this%Rinv(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
174 END DO
175 ! skip the above computation for subsequent calls
176 this%first_call = .false.
177 END IF
178
179 DO i=1,mesh%GINUM
180 ! compute Riemann invariants
181 CALL physics%CalculatePrim2RiemannX(mesh,mesh%IMAX+i-1,&
182 pvar,this%lambda,this%Rinv)
183 ! set infinity Riemanns for inflow
184 WHERE (this%lambda(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:).LE.0.0)
185 this%Rinv(mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) &
186 = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
187 END WHERE
188 ! transform back to primitive variables at the boundary
189 CALL physics%CalculateRiemann2PrimX(mesh,mesh%IMAX+i,this%Rinv,pvar)
190 END DO
191 CASE(south)
192 ! this must be done only once, but after the general boundary initialization
193 IF (this%first_call) THEN
194 ! compute Riemann invariants for the data (given in primitive variables)
195 ! provided by the user in the data array
196 DO j=1,mesh%GJNUM
197 ! temporaryly store boundary data in ghost cells
198 pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,:) &
199 = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:)
200 ! compute Riemann invariants
201 CALL physics%CalculatePrim2RiemannY(mesh,mesh%JMIN-j,&
202 pvar,this%lambda,this%Rinv)
203 ! store Riemann invariants in data array
204 this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:) &
205 = this%Rinv(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:)
206 END DO
207 ! skip the above computation for subsequent calls
208 this%first_call = .false.
209 END IF
210
211 DO j=1,mesh%GJNUM
212 ! compute Riemann invariants
213 CALL physics%CalculatePrim2RiemannY(mesh,mesh%JMIN-j+1,&
214 pvar,this%lambda,this%Rinv)
215 ! set infinity Riemanns for inflow
216 WHERE (this%lambda(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:).GE.0.0)
217 this%Rinv(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:) &
218 = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:)
219 END WHERE
220 ! transform back to primitive variables at the boundary
221 CALL physics%CalculateRiemann2PrimY(mesh,mesh%JMIN-j,this%Rinv,pvar)
222 END DO
223 CASE(north)
224 ! this must be done only once, but after the general boundary initialization
225 IF (this%first_call) THEN
226 ! compute Riemann invariants for the data (given in primitive variables)
227 ! provided by the user in the data array
228 DO j=1,mesh%GJNUM
229 ! temporaryly store boundary data in ghost cells
230 pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,:) &
231 = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:)
232 ! compute Riemann invariants
233 CALL physics%CalculatePrim2RiemannY(mesh,mesh%JMAX+j,&
234 pvar,this%lambda,this%Rinv)
235 ! store Riemann invariants in data array
236 this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:) &
237 = this%Rinv(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:)
238 END DO
239 ! skip the above computation for subsequent calls
240 this%first_call = .false.
241 END IF
242
243 DO j=1,mesh%GJNUM
244 ! compute Riemann invariants
245 CALL physics%CalculatePrim2RiemannY(mesh,mesh%JMAX+j-1,&
246 pvar,this%lambda,this%Rinv)
247 ! set infinity Riemanns for inflow
248 WHERE (this%lambda(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:).LE.0.0)
249 this%Rinv(mesh%IMIN:mesh%IMAX,mesh%KMIN:mesh%KMAX,:) &
250 = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,:)
251 END WHERE
252 ! transform back to primitive variables at the boundary
253 CALL physics%CalculateRiemann2PrimY(mesh,mesh%JMAX+j,this%Rinv,pvar)
254 END DO
255 CASE(bottom)
256 ! this must be done only once, but after the general boundary initialization
257 IF (this%first_call) THEN
258 ! compute Riemann invariants for the data (given in primitive variables)
259 ! provided by the user in the data array
260 DO k=1,mesh%GKNUM
261 ! temporaryly store boundary data in ghost cells
262 pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,:) &
263 = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:)
264
265 ! compute Riemann invariants
266 CALL physics%CalculatePrim2RiemannZ(mesh,mesh%KMIN-k,&
267 pvar,this%lambda,this%Rinv)
268
269 ! store Riemann invariants in data array
270 this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:) &
271 = this%Rinv(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:)
272 END DO
273 ! skip the above computation for subsequent calls
274 this%first_call = .false.
275 END IF
276
277 DO k=1,mesh%GKNUM
278 ! compute Riemann invariants
279 CALL physics%CalculatePrim2RiemannZ(mesh,mesh%KMIN-k+1,&
280 pvar,this%lambda,this%Rinv)
281 ! set infinity Riemanns for inflow
282 WHERE (this%lambda(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:).GE.0.0)
283 this%Rinv(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:) &
284 = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:)
285 END WHERE
286 ! transform back to primitive variables at the boundary
287 CALL physics%CalculateRiemann2PrimZ(mesh,mesh%KMIN-k,this%Rinv,pvar)
288 END DO
289 CASE(top)
290 ! this must be done only once, but after the general boundary initialization
291 IF (this%first_call) THEN
292 ! compute Riemann invariants for the data (given in primitive variables)
293 ! provided by the user in the data array
294 DO k=1,mesh%GKNUM
295 ! temporaryly store boundary data in ghost cells
296 pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,:) &
297 = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:)
298 ! compute Riemann invariants
299 CALL physics%CalculatePrim2RiemannZ(mesh,mesh%KMAX+k,&
300 pvar,this%lambda,this%Rinv)
301 ! store Riemann invariants in data array
302 this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:) &
303 = this%Rinv(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:)
304 END DO
305 ! skip the above computation for subsequent calls
306 this%first_call = .false.
307 END IF
308
309 DO k=1,mesh%GKNUM
310 ! compute Riemann invariants
311 CALL physics%CalculatePrim2RiemannZ(mesh,mesh%KMAX+k-1,&
312 pvar,this%lambda,this%Rinv)
313 ! set infinity Riemanns for inflow
314 WHERE (this%lambda(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:).LE.0.0)
315 this%Rinv(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,:) &
316 = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,:)
317 END WHERE
318 ! transform back to primitive variables at the boundary
319 CALL physics%CalculateRiemann2PrimZ(mesh,mesh%KMAX+k,this%Rinv,pvar)
320 END DO
321 END SELECT
322 END SUBROUTINE setboundarydata
323
325 SUBROUTINE finalize(this)
326 IMPLICIT NONE
327 !------------------------------------------------------------------------!
328 CLASS(boundary_farfield), INTENT(INOUT) :: this
329 !------------------------------------------------------------------------!
330 DEALLOCATE(this%Rinv,this%lambda,this%data)
331 CALL this%Finalize_base()
332 END SUBROUTINE finalize
333
334END MODULE boundary_farfield_mod
integer, parameter farfield
uses far-field data and Riemann invariants
Boundary module for far field conditions.
subroutine finalize(this)
Destructor for farfield boundary conditions.
subroutine setboundarydata(this, Mesh, Physics, time, pvar)
Applies the farfield boundary condition.
character(len=32), parameter boundcond_name
subroutine initboundary_farfield(this, Mesh, Physics, dir, config)
Constructor for farfield boundary conditions.
Dictionary for generic data types.
Definition: common_dict.f90:61
derived class for compound of mesh arrays
basic mesh module
Definition: mesh_base.f90:72
integer, parameter east
named constant for eastern boundary
Definition: mesh_base.f90:101
integer, parameter bottom
named constant for bottom boundary
Definition: mesh_base.f90:101
integer, parameter south
named constant for southern boundary
Definition: mesh_base.f90:101
integer, parameter top
named constant for top boundary
Definition: mesh_base.f90:101
integer, parameter north
named constant for northern boundary
Definition: mesh_base.f90:101
integer, parameter west
named constant for western boundary
Definition: mesh_base.f90:101
Basic physics module.
mesh data structure
Definition: mesh_base.f90:122