sources_rotframe.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: sources_rotframe.f90 #
5!# #
6!# Copyright (C) 2010-2021 #
7!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8!# Jannes Klee <jklee@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!----------------------------------------------------------------------------!
30!----------------------------------------------------------------------------!
38!----------------------------------------------------------------------------!
47 USE common_dict
48 !--------------------------------------------------------------------------!
49 PRIVATE
50 CHARACTER(LEN=32), PARAMETER :: source_name = "inertial forces"
51 !--------------------------------------------------------------------------!
53 TYPE(marray_base), POINTER :: caccel => null(), &
54 vphi => null(), &
55 twoomega
56 LOGICAL :: disable_centaccel
57 CONTAINS
58 PROCEDURE :: initsources
59 PROCEDURE :: infosources
60 PROCEDURE :: externalsources
62 final :: finalize
63 END TYPE
64
65 PUBLIC :: &
66 ! classes
68 !--------------------------------------------------------------------------!
69
70CONTAINS
71
73 SUBROUTINE initsources(this,Mesh,Physics,Fluxes,config,IO)
75 IMPLICIT NONE
76 !------------------------------------------------------------------------!
77 CLASS(sources_rotframe), INTENT(INOUT) :: this
78 CLASS(mesh_base), INTENT(IN) :: Mesh
79 CLASS(physics_base), INTENT(IN) :: Physics
80 CLASS(fluxes_base), INTENT(IN) :: Fluxes
81 TYPE(dict_typ), POINTER :: config, IO
82 !------------------------------------------------------------------------!
83 TYPE(marray_base), POINTER :: caccel3D => null(), vphi3d => null(), omez => null()
84 INTEGER :: stype,disable_centaccel
85 !------------------------------------------------------------------------!
86 CALL getattr(config, "stype", stype)
87 CALL this%InitSources_base(stype,source_name)
88
89 CALL getattr(config,"disable_centaccel",disable_centaccel,0)
90 IF (disable_centaccel.GT.0) THEN
91 this%disable_centaccel = .true.
92 ELSE
93 this%disable_centaccel = .false.
94 END IF
95
96 SELECT TYPE(physics)
97 CLASS IS(physics_eulerisotherm)
98 ! do nothing
99 CLASS DEFAULT
100 CALL this%Error("sources_rotframe::InitSources","physics not supported")
101 END SELECT
102
103
104 ALLOCATE(this%accel,caccel3d,vphi3d,omez)
105 this%accel = marray_base(physics%VDIM)
106 this%accel%data1d(:) = 0.
107
108 ! compute centrifugal acceleration for rotation around vertical direction
109 ! with center of rotation in r_0, i.e. -Omega**2 * ez x (ez x (r-r_0))
110 caccel3d = marray_base(3) ! 3D centrifugal acceleration
111 vphi3d = marray_base(3) ! 3D azimuthal velocity caused by rotating frame
112 omez = marray_base(3) ! 3D angular velocity of rotating frame (= Omega*ez)
113 ! set cartesian components of shifted center of rotation, i.e. r_0x, r_0y, r_0z,
114 ! using this%cent as temporary storage
115 caccel3d%data2d(:,1) = mesh%rotcent(1)
116 caccel3d%data2d(:,2) = mesh%rotcent(2)
117 caccel3d%data2d(:,3) = mesh%rotcent(3)
118 ! compute curvilinear components of shift vector
119 CALL mesh%Geometry%Convert2Curvilinear(mesh%bcenter,caccel3d%data4d,caccel3d%data4d)
120 ! subtract the result from the position vector:
121 ! this gives you the curvilinear components of all vectors pointing
122 ! from the center of rotation to the bary center of any cell on the mesh,
123 ! i.e. r-r_0
124 caccel3d%data4d(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - caccel3d%data4d(:,:,:,:)
125 ! set cartesian components of Omega*ez within computational domain
126 omez%data2d(:,1:2) = 0.0 ! no x and y component
127 WHERE (mesh%without_ghost_zones%mask1d(:))
128 omez%data2d(:,3) = mesh%Omega
129 ELSEWHERE
130 omez%data2d(:,3) = 0.0
131 END WHERE
132 ! compute curvinlinear components of Omega*ez with respect to the given geometry of the mesh
133 CALL mesh%Geometry%Convert2Curvilinear(mesh%bcenter,omez%data4d,omez%data4d)
134 ! compute curvilinear components of the local azimuthal velocity caused by the rotating frame
135 ! and the centrifual acceleration
136 vphi3d = omez.x.caccel3d ! = Omega*ez x (r-r0)
137 caccel3d = vphi3d.x.omez ! = -Omega**2 * ez x (ez x (r-r0)) = (Omega*ez x (r-r0)) x Omega*ez
138
139 ! set the projected components of the centrifugal acceleration
140 IF (physics%VDIM.LT.3) THEN
141 ALLOCATE(this%caccel,this%vphi)
142 this%caccel = marray_base(physics%VDIM) ! dimensionality of velocity vector
143 this%vphi = marray_base(physics%VDIM)
144 IF(physics%VDIM.EQ.2) THEN
145 ALLOCATE(this%twoOmega)
146 this%twoOmega = marray_base(1) ! = 2*Omega*(ez*e_perp)) = 2*projection of Omega onto 3rd suppressed dimension
147 END IF
148 END IF
149 SELECT CASE(mesh%VECTOR_COMPONENTS)
150 CASE(vector_x) ! 1D momentum in x-direction (1st curvilinear direction)
151 ! vy = vz = my = mz = 0
152 this%caccel%data2d(:,1) = caccel3d%data2d(:,1)
153 this%vphi%data2d(:,1) = vphi3d%data2d(:,1)
154 CASE(vector_y) ! 1D momentum in y-direction (2nd curvilinear direction)
155 ! vx = vz = mx = mz = 0
156 this%caccel%data2d(:,1) = caccel3d%data2d(:,2)
157 this%vphi%data2d(:,1) = vphi3d%data2d(:,2)
158 CASE(vector_z) ! 1D momentum in z-direction (3rd curvilinear direction)
159 ! vx = vy = mx = my = 0
160 this%caccel%data2d(:,1) = caccel3d%data2d(:,3)
161 this%vphi%data2d(:,1) = vphi3d%data2d(:,3)
162 CASE(ior(vector_x,vector_y)) ! 2D momentum in x-y-plane
163 ! vz = mz = 0
164 this%caccel%data2d(:,1:2) = caccel3d%data2d(:,1:2)
165 this%vphi%data2d(:,1:2) = vphi3d%data2d(:,1:2)
166 this%twoOmega%data1d(:) = 2*omez%data2d(:,3)
167 CASE(ior(vector_x,vector_z)) ! 2D momentum in x-z-plane
168 ! vy = my = 0
169 this%caccel%data2d(:,1) = caccel3d%data2d(:,1)
170 this%vphi%data2d(:,1) = vphi3d%data2d(:,1)
171 this%caccel%data2d(:,2) = caccel3d%data2d(:,3)
172 this%vphi%data2d(:,2) = vphi3d%data2d(:,3)
173 ! the minus is because e1 and e3 become the new 2D
174 ! curvilinear basis vectors and we must flip the direction of e2
175 ! in order to retain a right handed triad and hence
176 ! we must project Omez onto -e2 instead of e2
177 this%twoOmega%data1d(:) = -2*omez%data2d(:,2)
178 CASE(ior(vector_y,vector_z)) ! 2D momentum in y-z-plane
179 ! vx = mx = 0
180 this%caccel%data2d(:,1:2) = caccel3d%data2d(:,2:3)
181 this%vphi%data2d(:,1:2) = vphi3d%data2d(:,2:3)
182 this%twoOmega%data1d(:) = 2*omez%data2d(:,1)
183 CASE DEFAULT
184 ! full 3D case: caccel = caccel3D
185 this%caccel => caccel3d
186 this%vphi => vphi3d
187 this%twoOmega => omez
188 this%twoOmega%data1d(:) = 2.0*this%twoOmega%data1d(:)
189 END SELECT
190 IF(physics%VDIM.LT.3) DEALLOCATE(caccel3d,vphi3d,omez)
191 IF(this%disable_centaccel) DEALLOCATE(this%caccel)
192 CALL this%InfoSources(mesh)
193 END SUBROUTINE initsources
194
195
196 SUBROUTINE infosources(this,Mesh)
197 IMPLICIT NONE
198 !------------------------------------------------------------------------!
199 CLASS(sources_rotframe), INTENT(IN) :: this
200 CLASS(mesh_base), INTENT(IN) :: Mesh
201 !------------------------------------------------------------------------!
202 CHARACTER(LEN=32) :: omega_str
203 !------------------------------------------------------------------------!
204 WRITE (omega_str,'(ES9.2)') mesh%OMEGA
205 CALL this%Info(" angular velocity: " // trim(omega_str))
206 IF (this%disable_centaccel) THEN
207 CALL this%Info(" centrifugal accel: " // "disabled")
208 END IF
209 END SUBROUTINE infosources
210
211
212 SUBROUTINE externalsources(this,Mesh,Physics,Fluxes,Sources,time,dt,pvar,cvar,sterm)
214 IMPLICIT NONE
215 !------------------------------------------------------------------------!
216 CLASS(sources_rotframe), INTENT(INOUT) :: this
217 CLASS(mesh_base), INTENT(IN) :: Mesh
218 CLASS(physics_base), INTENT(INOUT) :: Physics
219 CLASS(fluxes_base), INTENT(IN) :: Fluxes
220 CLASS(sources_base), INTENT(INOUT) :: Sources
221 REAL, INTENT(IN) :: time, dt
222 CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar,sterm
223 !------------------------------------------------------------------------!
224 INTEGER :: i,j,k
225 !------------------------------------------------------------------------!
226 SELECT TYPE(p => pvar)
228 SELECT CASE(physics%VDIM)
229 CASE(1) ! 1D acceleration
230 ! no coriolis acceleration, because it is always perpendicular to the
231 ! velocity vector and hence causes no acceleration along this direction
232 IF (.NOT.this%disable_centaccel) THEN
233 this%accel = this%caccel
234 END IF
235 ! otherwise do nothing, this%accel should be zero (see initialization)
236 CASE(2) ! 2D acceleration
237 IF (this%disable_centaccel) THEN
238 this%accel%data2d(:,1) = this%twoOmega%data1d(:)*p%velocity%data2d(:,2)
239 this%accel%data2d(:,2) = -this%twoOmega%data1d(:)*p%velocity%data2d(:,1)
240 ELSE
241 this%accel%data2d(:,1) = this%caccel%data2d(:,1) + this%twoOmega%data1d(:)*p%velocity%data2d(:,2)
242 this%accel%data2d(:,2) = this%caccel%data2d(:,2) - this%twoOmega%data1d(:)*p%velocity%data2d(:,1)
243 END IF
244 CASE(3) ! 3D acceleration
245 IF (this%disable_centaccel) THEN
246 this%accel = p%velocity.x.this%twoOmega ! = -2*Omega x v
247 ELSE
248 this%accel = this%caccel + (p%velocity.x.this%twoOmega) ! = caccel - 2*Omega x v
249 END IF
250 CASE DEFAULT
251 ! this should not happen
252 END SELECT
253 CLASS DEFAULT
254 ! do nothing
255 END SELECT
256
257 ! inertial forces source terms
258 CALL physics%ExternalSources(this%accel,pvar,cvar,sterm)
259 END SUBROUTINE externalsources
260
261 SUBROUTINE convert2rotatingframe(this,Mesh,Physics,pvar)
263 IMPLICIT NONE
264 !------------------------------------------------------------------------!
265 CLASS(sources_rotframe), INTENT(IN) :: this
266 CLASS(mesh_base), INTENT(IN) :: Mesh
267 CLASS(physics_base), INTENT(IN) :: Physics
268 CLASS(marray_compound), INTENT(INOUT) :: pvar
269 !------------------------------------------------------------------------!
270 ! Convert velocities to the rotating frame
271 SELECT TYPE (p => pvar)
273 p%velocity%data1d = p%velocity%data1d - this%vphi%data1d
274 CLASS DEFAULT
275 CALL this%Error("sources_rotframe::Convert2RotatingFrame","physics currently not supported")
276 END SELECT
277 END SUBROUTINE convert2rotatingframe
278
279 SUBROUTINE finalize(this)
280 IMPLICIT NONE
281 !------------------------------------------------------------------------!
282 TYPE(sources_rotframe), INTENT(INOUT) :: this
283 !------------------------------------------------------------------------!
284 DEALLOCATE(this%vphi)
285 IF (ASSOCIATED(this%caccel)) DEALLOCATE(this%caccel)
286 IF (ASSOCIATED(this%twoOmega)) DEALLOCATE(this%twoOmega)
287 NULLIFY(this%vphi,this%caccel,this%twoOmega)
288 ! deallocation of this%accel is done in inherited destructor
289 ! which is called automatically
290 END SUBROUTINE finalize
291
292END MODULE sources_rotframe_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
base module for numerical flux functions
Definition: fluxes_base.f90:39
base class for mesh arrays
Definition: marray_base.f90:36
subroutine finalize(this)
derived class for compound of mesh arrays
basic mesh module
Definition: mesh_base.f90:72
integer, parameter vector_y
Definition: mesh_base.f90:109
integer, parameter vector_z
Definition: mesh_base.f90:109
integer, parameter vector_x
flags to check which vector components are enabled
Definition: mesh_base.f90:109
Basic physics module.
physics module for 1D,2D and 3D isothermal Euler equations
generic source terms module providing functionaly common to all source terms
source terms module for constant acceleration
character(len=32), parameter source_name
subroutine externalsources(this, Mesh, Physics, Fluxes, Sources, time, dt, pvar, cvar, sterm)
subroutine initsources(this, Mesh, Physics, Fluxes, config, IO)
source terms module for inertial forces caused by a rotating grid
subroutine convert2rotatingframe(this, Mesh, Physics, pvar)
subroutine infosources(this, Mesh)
basic mesh array class
Definition: marray_base.f90:69
mesh data structure
Definition: mesh_base.f90:122