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-2018 #
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 !----------------------------------------------------------------------------!
31 !----------------------------------------------------------------------------!
39 !----------------------------------------------------------------------------!
44  USE fluxes_base_mod
45  USE mesh_base_mod
46  USE marray_base_mod
48  USE common_dict
49  !--------------------------------------------------------------------------!
50  PRIVATE
51  CHARACTER(LEN=32), PARAMETER :: source_name = "inertial forces"
53  TYPE(marray_base) :: cent
54  TYPE(marray_base) :: centproj
55  TYPE(marray_base) :: cos1
56  CONTAINS
57  PROCEDURE :: initsources_rotframe
58  PROCEDURE :: infosources
60  PROCEDURE :: convert2rotatingframe
61  PROCEDURE :: finalize
62  END TYPE
63 
64  PUBLIC :: &
65  ! classes
67  !--------------------------------------------------------------------------!
68 
69 CONTAINS
70 
72  SUBROUTINE initsources_rotframe(this,Mesh,Physics,Fluxes,config,IO)
75  IMPLICIT NONE
76  !------------------------------------------------------------------------!
77  CLASS(sources_rotframe) :: 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  INTEGER :: stype
84  !------------------------------------------------------------------------!
85  CALL getattr(config, "stype", stype)
86  CALL this%InitLogging(stype,source_name)
87  CALL this%InitSources(mesh,fluxes,physics,config,io)
88 
89  SELECT TYPE(physics)
90  TYPE IS(physics_euler)
91  ! do nothing
92  TYPE IS(physics_eulerisotherm)
93  ! do nothing
94  CLASS DEFAULT
95  CALL this%Error("sources_rotframe::InitSources","physics not supported")
96  END SELECT
97 
98  IF (mesh%FARGO.GT.0) &
99  CALL this%Error("sources_rotframe::InitSources", &
100  "rotating frame with FARGO seems broken, don't use it together")
101 
102  IF (physics%VDIM.NE.2) &
103  CALL this%Error("sources_rotframe::InitSources", &
104  "Only 2D simulations working with rotating frame at the moment." )
105 
106  this%accel = marray_base(physics%VDIM)
107  this%accel%data1d(:) = 0.
108  this%cent = marray_base(3)
109  this%cent%data1d(:) = 0.
110  this%centproj = marray_base(3)
111  this%centproj%data1d(:) = 0.
112  this%cos1 = marray_base(3)
113  this%cos1%data1d(:) = 0.
114 
115  CALL getattr(config, "gparam", this%gparam, 1.0)
116 
117  ! define position vectors
118  ! for bianglespherical no shift of axis possible
119  ! (for a planet reasonable)
120 ! IF ((Mesh%Geometry%GetType()).EQ.BIANGLESPHERICAL) THEN
121 !
122 ! this%centproj%data4d(:,:,:,1) = this%gparam*SIN(Mesh%bcenter(:,:,:,1))*&
123 ! COS(Mesh%bcenter(:,:,:,1))
124 ! ! for better performance
125 ! this%cos1%data4d(:,:,:,1) = COS(Mesh%bcenter(:,:,:,1))
126 ! this%cos1%data4d(:,:,:,2) = COS(Mesh%bcenter(:,:,:,2))
127 ! ELSE
128  IF (abs(mesh%rotcent(1)).LE.tiny(mesh%rotcent(1)) &
129  .AND.abs(mesh%rotcent(2)).LE.tiny(mesh%rotcent(2))) THEN
130  ! no shift of point mass: set position vector to Mesh defaults
131  this%cent%data4d(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
132  ELSE
133  ! shifted center of rotation:
134  ! compute curvilinear components of shift vector
135  this%cent%data4d(:,:,:,1) = mesh%rotcent(1)
136  this%cent%data4d(:,:,:,2) = mesh%rotcent(2)
137  this%cent%data4d(:,:,:,3) = mesh%rotcent(3)
138  CALL mesh%Geometry%Convert2Curvilinear(mesh%bcenter,this%cent%data4d,this%cent%data4d)
139  ! subtract the result from the position vector:
140  ! this gives you the curvilinear components of all vectors pointing
141  ! from the center of rotation to the bary center of any cell on the mesh
142  this%cent%data4d(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - this%cent%data4d(:,:,:,:)
143  END IF
144 ! END IF
145  END SUBROUTINE initsources_rotframe
146 
147 
148  SUBROUTINE infosources(this,Mesh)
149  IMPLICIT NONE
150  !------------------------------------------------------------------------!
151  CLASS(sources_rotframe), INTENT(IN) :: this
152  CLASS(mesh_base), INTENT(IN) :: Mesh
153  !------------------------------------------------------------------------!
154  CHARACTER(LEN=32) :: omega_str
155  !------------------------------------------------------------------------!
156  WRITE (omega_str,'(ES8.2)') mesh%OMEGA
157  CALL this%Info(" angular velocity: " // trim(omega_str))
158  END SUBROUTINE infosources
159 
160 
161  SUBROUTINE externalsources_single(this,Mesh,Physics,Fluxes,Sources,time,dt,pvar,cvar,sterm)
162  IMPLICIT NONE
163  !------------------------------------------------------------------------!
164  CLASS(sources_rotframe), INTENT(INOUT) :: this
165  CLASS(mesh_base), INTENT(IN) :: Mesh
166  CLASS(physics_base), INTENT(INOUT) :: Physics
167  CLASS(fluxes_base), INTENT(IN) :: Fluxes
168  CLASS(sources_base), INTENT(INOUT) :: Sources
169  REAL, INTENT(IN) :: time, dt
170  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar,sterm
171  !------------------------------------------------------------------------!
172  INTEGER :: i,j,k
173  !------------------------------------------------------------------------!
174  ! Two cases due to different angles between angular velocity to mesh
175  ! 1. only a projected part plays role for bianglespherical geometry
176 ! IF ((Mesh%Geometry%GetType()).EQ.BIANGLESPHERICAL) THEN
177 !!NEC$ outerloop_unroll(8)
178 ! DO k=Mesh%KMIN,Mesh%KMAX
179 ! DO j=Mesh%JMIN,Mesh%JMAX
180 !!NEC$ ivdep
181 ! DO i=Mesh%IMIN,Mesh%IMAX
182 ! this%accel%data4d(i,j,k,1) = Mesh%OMEGA*(Mesh%OMEGA*&
183 ! this%centproj%data4d(i,j,k,1) + 2.0*this%cos1%data4d(i,j,k,1)*&
184 ! pvar%data4d(i,j,k,Physics%YVELOCITY))
185 ! this%accel%data4d(i,j,k,2) = -Mesh%OMEGA*2.0*this%cos1%data4d(i,j,k,1)*&
186 ! pvar%data4d(i,j,k,Physics%XVELOCITY)
187 ! END DO
188 ! END DO
189 ! END DO
190 ! ! 2. OMEGA is always perpendicular to other curvilinear coordinates
191 ! ELSE
192 !NEC$ outerloop_unroll(8)
193  DO k=mesh%KMIN,mesh%KMAX
194  DO j=mesh%JMIN,mesh%JMAX
195  !NEC$ ivdep
196  DO i=mesh%IMIN,mesh%IMAX
197  ! components of centrifugal and coriolis acceleration
198  this%accel%data4d(i,j,k,1) = mesh%OMEGA*(mesh%OMEGA*this%cent%data4d(i,j,k,1) &
199  + 2.0*pvar%data4d(i,j,k,physics%YVELOCITY))
200  this%accel%data4d(i,j,k,2) = mesh%OMEGA*(mesh%OMEGA*this%cent%data4d(i,j,k,2) &
201  - 2.0*pvar%data4d(i,j,k,physics%XVELOCITY))
202  END DO
203  END DO
204  END DO
205 ! END IF
206 
207  ! inertial forces source terms
208  CALL physics%ExternalSources(this%accel,pvar,cvar,sterm)
209  END SUBROUTINE externalsources_single
210 
211  SUBROUTINE convert2rotatingframe(this,Mesh,Physics,pvar)
212  IMPLICIT NONE
213  !------------------------------------------------------------------------!
214  CLASS(sources_rotframe), INTENT(IN) :: this
215  CLASS(mesh_base), INTENT(IN) :: Mesh
216  CLASS(physics_base), INTENT(IN) :: Physics
217  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,Physics%VNUM), &
218  INTENT(INOUT) :: pvar
219  !------------------------------------------------------------------------!
220  ! Convert velocities to the rotating frame
221 ! IF ((Mesh%Geometry%GetType()).EQ.BIANGLESPHERICAL) THEN
222 ! pvar(:,:,:,Physics%XVELOCITY) = pvar(:,:,:,Physics%XVELOCITY)
223 ! pvar(:,:,:,Physics%YVELOCITY) = pvar(:,:,:,Physics%YVELOCITY) - &
224 ! Mesh%OMEGA*SIN(Mesh%bcenter(:,:,:,1))*this%gparam
225 ! ELSE
226  pvar(:,:,:,physics%XVELOCITY) = pvar(:,:,:,physics%XVELOCITY) + &
227  mesh%OMEGA * this%cent%data4d(:,:,:,2)
228  pvar(:,:,:,physics%YVELOCITY) = pvar(:,:,:,physics%YVELOCITY) - &
229  mesh%OMEGA * this%cent%data4d(:,:,:,1)
230 ! END IF
231  END SUBROUTINE convert2rotatingframe
232 
233  SUBROUTINE finalize(this)
234  IMPLICIT NONE
235  !------------------------------------------------------------------------!
236  CLASS(sources_rotframe), INTENT(INOUT) :: this
237  !------------------------------------------------------------------------!
238  CALL this%accel%Destroy()
239  CALL this%cent%Destroy()
240  CALL this%centproj%Destroy()
241  CALL this%cos1%Destroy()
242 
243  CALL this%sources_c_accel%Finalize()
244  END SUBROUTINE finalize
245 
246 END MODULE sources_rotframe_mod
subroutine infosources(this, Mesh)
subroutine initsources_rotframe(this, Mesh, Physics, Fluxes, config, IO)
Constructor of the rotating reference frame module.
generic source terms module providing functionaly common to all source terms
source terms module for constant acceleration
derived class for compound of mesh arrays
base class for mesh arrays
Definition: marray_base.f90:36
character(len=32) source_name
basic mesh array class
Definition: marray_base.f90:64
physics module for 1D,2D and 3D isothermal Euler equations
subroutine finalize(this)
subroutine convert2rotatingframe(this, Mesh, Physics, pvar)
source terms module for inertial forces caused by a rotating grid
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
physics module for 1D,2D and 3D non-isothermal Euler equations
base module for numerical flux functions
Definition: fluxes_base.f90:39
subroutine externalsources_single(this, Mesh, Physics, Fluxes, Sources, time, dt, pvar, cvar, sterm)