boundary_noslip.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: boundary_noslip.f90 #
5 !# #
6 !# Copyright (C) 2010-2018 #
7 !# Bjoern Sperling <sperling@astrophysik.uni-kiel.de> #
8 !# Tobias Illenseer <tillense@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 !----------------------------------------------------------------------------!
36 !----------------------------------------------------------------------------!
39  USE mesh_base_mod
43  USE common_dict
44  IMPLICIT NONE
45  !--------------------------------------------------------------------------!
46  PRIVATE
47  TYPE, EXTENDS(boundary_fixed) :: boundary_noslip
48  CONTAINS
49  PROCEDURE :: initboundary_noslip
50  PROCEDURE :: setboundarydata
51  PROCEDURE :: finalize
52  END TYPE boundary_noslip
53  CHARACTER(LEN=32), PARAMETER :: boundcond_name = "noslip"
54  !--------------------------------------------------------------------------!
55  PUBLIC :: &
57  west, east, south, north, bottom, top
58  !--------------------------------------------------------------------------!
59 
60 CONTAINS
61 
63  SUBROUTINE initboundary_noslip(this,Mesh,Physics,dir,config)
64  IMPLICIT NONE
65  !------------------------------------------------------------------------!
66  CLASS(Boundary_noslip),INTENT(INOUT) :: this
67  CLASS(Mesh_base) ,INTENT(IN) :: Mesh
68  CLASS(Physics_base) ,INTENT(IN) :: Physics
69  TYPE(Dict_TYP),POINTER,INTENT(IN) :: config
70  INTEGER ,INTENT(IN) :: dir
71  !------------------------------------------------------------------------!
72  INTEGER :: err = 0
73  !------------------------------------------------------------------------!
74  CALL this%InitBoundary(mesh,physics,noslip,boundcond_name,dir,config)
75 
76  ! allocate memory for boundary data
77  SELECT CASE(dir)
78  CASE(west,east)
79  ALLOCATE(this%data(mesh%GINUM,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%VNUM), &
80  stat=err)
81  this%data(:,:,:,:)=0.0
82  CASE(south,north)
83  ALLOCATE(this%data(mesh%IMIN:mesh%IMAX,mesh%GJNUM,mesh%KMIN:mesh%KMAX,physics%VNUM), &
84  stat=err)
85  this%data(:,:,:,:)=0.0
86  CASE(bottom,top)
87  ALLOCATE(this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%GKNUM, physics%VNUM), &
88  stat=err)
89  this%data(:,:,:,:)=0.0
90  END SELECT
91 
92  IF (err.NE.0) THEN
93  CALL this%Error("InitBoundary_noslip", "Unable to allocate memory.")
94  END IF
95  END SUBROUTINE initboundary_noslip
96 
98  PURE SUBROUTINE setboundarydata(this,Mesh,Physics,time,pvar)
99  IMPLICIT NONE
100  !------------------------------------------------------------------------!
101  CLASS(boundary_noslip),INTENT(INOUT) :: this
102  CLASS(mesh_base) ,INTENT(IN) :: mesh
103  CLASS(physics_base) ,INTENT(IN) :: physics
104  REAL ,INTENT(IN) :: time
105  CLASS(marray_compound),INTENT(INOUT) :: pvar
106  !------------------------------------------------------------------------!
107  INTEGER :: i,j,k
108  !------------------------------------------------------------------------!
109  SELECT CASE(this%direction%GetType())
110  CASE(west)
111  ! UNROLL=Mesh%GNUM would be sufficient, but the compiler does
112  ! not know the value of Mesh%GNUM, hence we set UNROLL=4 and
113  ! hope that nobody sets Mesh%GNUM to a value greater than 4
114 !NEC$ UNROLL(4)
115  DO i=1,mesh%GINUM
116  ! vanishing density gradient at the boundary
117  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%DENSITY) &
118  = pvar%data4d(mesh%IMIN+i-1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%DENSITY)
119  ! normal velocity
120  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%XVELOCITY) &
121  = -pvar%data4d(mesh%IMIN+i-1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%XVELOCITY)
122  ! tangential velocities
123  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%YVELOCITY) &
124  = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%YVELOCITY)
125  IF (physics%ZVELOCITY.GT.0) THEN
126  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY) &
127  = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY)
128  END IF
129  ! vanishing pressure gradient at the boundary
130  IF (physics%PRESSURE.GT.0) THEN
131  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%PRESSURE) &
132  = pvar%data4d(mesh%IMIN+i-1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%PRESSURE)
133  END IF
134  END DO
135  CASE(east)
136 !NEC$ UNROLL(4)
137  DO i=1,mesh%GNUM
138  ! vanishing density gradient at the boundary
139  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%DENSITY) &
140  = pvar%data4d(mesh%IMAX-i+1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%DENSITY)
141  ! normal velocity
142  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%XVELOCITY) &
143  = -pvar%data4d(mesh%IMAX-i+1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%XVELOCITY)
144  ! tangential velocities
145  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%YVELOCITY) &
146  = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%YVELOCITY)
147  IF (physics%ZVELOCITY.GT.0) THEN
148  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY) &
149  = this%data(i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY)
150  END IF
151  ! vanishing pressure gradient at the boundary
152  IF (physics%PRESSURE.GT.0) THEN
153  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%PRESSURE) &
154  = pvar%data4d(mesh%IMAX-i+1,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,physics%PRESSURE)
155  END IF
156  END DO
157  CASE(south)
158 !NEC$ UNROLL(4)
159  DO j=1,mesh%GJNUM
160  ! vanishing density gradient at the boundary
161  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,physics%DENSITY) &
162  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN+j-1,mesh%KMIN:mesh%KMAX,physics%DENSITY)
163  ! normal velocity
164  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,physics%YVELOCITY) &
165  = -pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN+j-1,mesh%KMIN:mesh%KMAX,physics%YVELOCITY)
166  ! tangential velocities
167  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,physics%XVELOCITY) &
168  = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,physics%XVELOCITY)
169  IF (physics%ZVELOCITY.GT.0) THEN
170  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY) &
171  = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY)
172  END IF
173  ! vanishing pressure gradient at the boundary
174  IF (physics%PRESSURE.GT.0) THEN
175  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,physics%PRESSURE) &
176  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN+j-1,mesh%KMIN:mesh%KMAX,physics%PRESSURE)
177  END IF
178  END DO
179  CASE(north)
180 !NEC$ UNROLL(4)
181  DO j=1,mesh%GNUM
182  ! vanishing density gradient at the boundary
183  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,physics%DENSITY) &
184  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX-j+1,mesh%KMIN:mesh%KMAX,physics%DENSITY)
185  ! normal velocity
186  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,physics%YVELOCITY) &
187  = -pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX-j+1,mesh%KMIN:mesh%KMAX,physics%YVELOCITY)
188  ! tangential velocities
189  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,physics%XVELOCITY) &
190  = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,physics%XVELOCITY)
191  IF (physics%ZVELOCITY.GT.0) THEN
192  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY) &
193  = this%data(mesh%IMIN:mesh%IMAX,j,mesh%KMIN:mesh%KMAX,physics%ZVELOCITY)
194  END IF
195  ! vanishing pressure gradient at the boundary
196  IF (physics%PRESSURE.GT.0) THEN
197  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,physics%PRESSURE) &
198  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX-j+1,mesh%KMIN:mesh%KMAX,physics%PRESSURE)
199  END IF
200  END DO
201  CASE(bottom)
202 !NEC$ UNROLL(4)
203  DO k=1,mesh%GKNUM
204  ! vanishing density gradient at the boundary
205  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,physics%DENSITY) &
206  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%kMIN+k-1,physics%DENSITY)
207  ! normal velocity
208  IF (physics%ZVELOCITY.GT.0) THEN
209  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,physics%ZVELOCITY) &
210  = -pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN+k-1,physics%ZVELOCITY)
211  END IF
212  ! tangential velocities
213  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,physics%XVELOCITY) &
214  = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,physics%XVELOCITY)
215  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,physics%YVELOCITY) &
216  = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,physics%YVELOCITY)
217  ! vanishing pressure gradient at the boundary
218  IF (physics%PRESSURE.GT.0) THEN
219  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,physics%PRESSURE) &
220  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN+k-1,physics%PRESSURE)
221  END IF
222  END DO
223  CASE(top)
224 !NEC$ UNROLL(4)
225  DO k=1,mesh%GKNUM
226  ! vanishing density gradient at the boundary
227  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,physics%DENSITY) &
228  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX-k+1,physics%DENSITY)
229  ! normal velocity
230  IF (physics%ZVELOCITY.GT.0) THEN
231  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,physics%ZVELOCITY) &
232  = -pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX-k+1,physics%ZVELOCITY)
233  END IF
234  ! tangential velocities
235  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,physics%XVELOCITY) &
236  = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,physics%XVELOCITY)
237  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,physics%YVELOCITY) &
238  = this%data(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,k,physics%YVELOCITY)
239  ! vanishing pressure gradient at the boundary
240  IF (physics%PRESSURE.GT.0) THEN
241  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,physics%PRESSURE) &
242  = pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX-k+1,physics%PRESSURE)
243  END IF
244  END DO
245 
246  END SELECT
247  END SUBROUTINE setboundarydata
248 
250  SUBROUTINE finalize(this)
251  IMPLICIT NONE
252  !------------------------------------------------------------------------!
253  CLASS(Boundary_noslip), INTENT(INOUT) :: this
254  !------------------------------------------------------------------------!
255  DEALLOCATE(this%data)
256  CALL this%Finalize_base()
257  END SUBROUTINE finalize
258 
259 END MODULE boundary_noslip_mod
subroutine finalize(this)
Destructor for fixed boundary conditions.
type(logging_base), save this
derived class for compound of mesh arrays
Boundary module for noslip conditions (see wikipedia )
character(len=32), parameter boundcond_name
subroutine initboundary_noslip(this, Mesh, Physics, dir, config)
Constructor for noslip boundary conditions.
named integer constants for flavour of state vectors
pure subroutine setboundarydata(this, Mesh, Physics, time, pvar)
Applies the fixed boundary condition.
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
Boundary module for fixed in/outflow conditions.