50 CHARACTER(LEN=32),
PARAMETER ::
source_name =
"inertial forces"
56 LOGICAL :: disable_centaccel
81 TYPE(
dict_typ),
POINTER :: config, IO
83 TYPE(
marray_base),
POINTER :: caccel3D => null(), vphi3d => null(), omez => null()
84 INTEGER :: stype,disable_centaccel
86 CALL getattr(config,
"stype", stype)
89 CALL getattr(config,
"disable_centaccel",disable_centaccel,0)
90 IF (disable_centaccel.GT.0)
THEN
91 this%disable_centaccel = .true.
93 this%disable_centaccel = .false.
100 CALL this%Error(
"sources_rotframe::InitSources",
"physics not supported")
104 ALLOCATE(this%accel,caccel3d,vphi3d,omez)
106 this%accel%data1d(:) = 0.
115 caccel3d%data2d(:,1) = mesh%rotcent(1)
116 caccel3d%data2d(:,2) = mesh%rotcent(2)
117 caccel3d%data2d(:,3) = mesh%rotcent(3)
119 CALL mesh%Geometry%Convert2Curvilinear(mesh%bcenter,caccel3d%data4d,caccel3d%data4d)
124 caccel3d%data4d(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - caccel3d%data4d(:,:,:,:)
126 omez%data2d(:,1:2) = 0.0
127 WHERE (mesh%without_ghost_zones%mask1d(:))
128 omez%data2d(:,3) = mesh%Omega
130 omez%data2d(:,3) = 0.0
133 CALL mesh%Geometry%Convert2Curvilinear(mesh%bcenter,omez%data4d,omez%data4d)
136 vphi3d = omez.x.caccel3d
137 caccel3d = vphi3d.x.omez
140 IF (physics%VDIM.LT.3)
THEN
141 ALLOCATE(this%caccel,this%vphi)
144 IF(physics%VDIM.EQ.2)
THEN
145 ALLOCATE(this%twoOmega)
149 SELECT CASE(mesh%VECTOR_COMPONENTS)
152 this%caccel%data2d(:,1) = caccel3d%data2d(:,1)
153 this%vphi%data2d(:,1) = vphi3d%data2d(:,1)
156 this%caccel%data2d(:,1) = caccel3d%data2d(:,2)
157 this%vphi%data2d(:,1) = vphi3d%data2d(:,2)
160 this%caccel%data2d(:,1) = caccel3d%data2d(:,3)
161 this%vphi%data2d(:,1) = vphi3d%data2d(:,3)
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)
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)
177 this%twoOmega%data1d(:) = -2*omez%data2d(:,2)
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)
185 this%caccel => caccel3d
187 this%twoOmega => omez
188 this%twoOmega%data1d(:) = 2.0*this%twoOmega%data1d(:)
190 IF(physics%VDIM.LT.3)
DEALLOCATE(caccel3d,vphi3d,omez)
191 IF(this%disable_centaccel)
DEALLOCATE(this%caccel)
192 CALL this%InfoSources(mesh)
202 CHARACTER(LEN=32) :: omega_str
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")
221 REAL,
INTENT(IN) :: time, dt
226 SELECT TYPE(p => pvar)
228 SELECT CASE(physics%VDIM)
232 IF (.NOT.this%disable_centaccel)
THEN
233 this%accel = this%caccel
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)
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)
245 IF (this%disable_centaccel)
THEN
246 this%accel = p%velocity.x.this%twoOmega
248 this%accel = this%caccel + (p%velocity.x.this%twoOmega)
258 CALL physics%ExternalSources(this%accel,pvar,cvar,sterm)
271 SELECT TYPE (p => pvar)
273 p%velocity%data1d = p%velocity%data1d - this%vphi%data1d
275 CALL this%Error(
"sources_rotframe::Convert2RotatingFrame",
"physics currently not supported")
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)
Dictionary for generic data types.
base module for numerical flux functions
base class for mesh arrays
subroutine finalize(this)
derived class for compound of mesh arrays
integer, parameter vector_y
integer, parameter vector_z
integer, parameter vector_x
flags to check which vector components are enabled
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)