gauss3d.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: gauss3d.f90 #
5!# #
6!# Copyright (C) 2006-2014 #
7!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8!# #
9!# This program is free software; you can redistribute it and/or modify #
10!# it under the terms of the GNU General Public License as published by #
11!# the Free Software Foundation; either version 2 of the License, or (at #
12!# your option) any later version. #
13!# #
14!# This program is distributed in the hope that it will be useful, but #
15!# WITHOUT ANY WARRANTY; without even the implied warranty of #
16!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
17!# NON INFRINGEMENT. See the GNU General Public License for more #
18!# details. #
19!# #
20!# You should have received a copy of the GNU General Public License #
21!# along with this program; if not, write to the Free Software #
22!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
23!# #
24!#############################################################################
25
26!----------------------------------------------------------------------------!
31!----------------------------------------------------------------------------!
32PROGRAM gauss3d
33 USE fosite_mod
34#include "tap.h"
35 IMPLICIT NONE
36 !--------------------------------------------------------------------------!
37 ! simulation parameter
38 REAL, PARAMETER :: tsim = 0.5 ! simulation time
39 REAL, PARAMETER :: gamma = 1.4 ! ratio of specific heats
40 REAL, PARAMETER :: csiso = &
41 0.0 ! non-isothermal simulation
42! 1.127 ! isothermal simulation
43 ! with CSISO as sound speed
44 ! initial condition (dimensionless units)
45 REAL, PARAMETER :: rho0 = 1.0 ! ambient density
46 REAL, PARAMETER :: rho1 = 1.0 ! peak density above RHO0
47 REAL, PARAMETER :: rwidth = 0.06 ! half width of the Gaussian
48 REAL, PARAMETER :: p0 = 1.0 ! ambient pressure
49 REAL, PARAMETER :: p1 = 1.0 ! peak pressure above P0
50 REAL, PARAMETER :: pwidth = 0.06 ! half width of the Gaussian
51 REAL, PARAMETER :: omega0 = 0.0 ! angular velocity
52 REAL, PARAMETER :: eta = 0.0 ! dynamic viscosity (0.0 disables)
53 ! location of the initial pulse (cartesian coordinates)
54 REAL, PARAMETER :: x0 = 0.0 ! x-position
55 REAL, PARAMETER :: y0 = 0.0 ! y-position
56 REAL, PARAMETER :: z0 = 0.0 ! z-position
57 ! mesh settings
58 INTEGER, PARAMETER :: mgeo = cartesian! geometry
59! INTEGER, PARAMETER :: MGEO = CYLINDRICAL
60! INTEGER, PARAMETER :: MGEO = SPHERICAL
61 INTEGER, PARAMETER :: res = 30 ! x-/y-/z-resolution
62 REAL, PARAMETER :: rmax = 0.5 ! maximal radial extent
63 REAL, PARAMETER :: gpar = 0.8 ! geometry scaling parameter
64 ! output parameters
65 INTEGER, PARAMETER :: onum = 10 ! number of output data sets
66 CHARACTER(LEN=256), PARAMETER & ! output data dir
67 :: odir = './'
68 CHARACTER(LEN=256), PARAMETER & ! output data file name
69 :: ofname = 'gauss3D'
70 !--------------------------------------------------------------------------!
71 CLASS(fosite), ALLOCATABLE :: sim
72 LOGICAL :: ok
73 !--------------------------------------------------------------------------!
74
75 tap_plan(1)
76
77 ALLOCATE(sim)
78 CALL sim%InitFosite()
79 CALL makeconfig(sim, sim%config)
80 CALL sim%Setup()
81 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
82! SELECT TYPE(pvar => Sim%Fluxes%prim)
83! TYPE IS(statevector_eulerisotherm) ! isothermal HD
84! PRINT *,pvar%density%data1d(1)
85! CLASS DEFAULT
86! PRINT *, "ERROR: wrong state vector"
87! END SELECT
88 CALL sim%Run()
89 ok = .NOT.sim%aborted
90 CALL sim%Finalize()
91 DEALLOCATE(sim)
92
93 tap_check(ok,"stoptime reached")
94 tap_done
95
96CONTAINS
97
98 SUBROUTINE makeconfig(Sim, config)
99 USE functions, ONLY : asinh, acosh
100 IMPLICIT NONE
101 !------------------------------------------------------------------------!
102 CLASS(fosite) :: Sim
103 TYPE(dict_typ),POINTER :: config
104 !------------------------------------------------------------------------!
105 ! Local variable declaration
106 INTEGER :: bc(6),xres,yres,zres
107 TYPE(dict_typ), POINTER :: mesh, physics, boundary, datafile, sources, &
108 timedisc, fluxes
109 REAL :: x1,x2,y1,y2,z1,z2
110 !------------------------------------------------------------------------!
111 INTENT(INOUT) :: sim
112 !------------------------------------------------------------------------!
113 ! mesh settings and boundary conditions
114 SELECT CASE(mgeo)
115 CASE(cartesian)
116 x1 = -rmax
117 x2 = rmax
118 y1 = -rmax
119 y2 = rmax
120 z1 = -rmax
121 z2 = rmax
122 xres = res
123 yres = res
124 zres = res
125! bc(WEST) = NO_GRADIENTS
126! bc(EAST) = NO_GRADIENTS
127! bc(SOUTH) = NO_GRADIENTS
128! bc(NORTH) = NO_GRADIENTS
129! bc(BOTTOM) = NO_GRADIENTS
130! bc(TOP) = NO_GRADIENTS
131 bc(west) = absorbing
132 bc(east) = absorbing
133 bc(south) = absorbing
134 bc(north) = absorbing
135 bc(bottom) = absorbing
136 bc(top) = absorbing
137 CASE(cylindrical)
138 x1 = 0.01
139 x2 = rmax
140 y1 = 0.0
141 y2 = 2*pi
142 z1 = -rmax
143 z2 = rmax
144 xres = res / 2
145 yres = res / 2
146 zres = res
147 bc(west) = axis
148 bc(east) = absorbing
149 bc(south) = periodic
150 bc(north) = periodic
151 bc(bottom) = absorbing
152 bc(top) = absorbing
153 CASE(spherical)
154 x1 = 0.01
155 x2 = rmax
156 y1 = 0.0
157 y2 = pi
158 z1 = 0.0
159 z2 = 2*pi
160 xres = res / 2
161 yres = res / 4
162 zres = res / 2
163 bc(west) = axis
164 bc(east) = absorbing
165 bc(south) = axis
166 bc(north) = axis
167 bc(bottom)= periodic
168 bc(top) = periodic
169 CASE DEFAULT
170 CALL sim%Error("InitProgram","geometry not supported for this test")
171 END SELECT
172
173 !mesh settings
174 mesh => dict( &
175 "meshtype" / midpoint, &
176 "geometry" / mgeo, &
177 "inum" / xres, &
178 "jnum" / yres, &
179 "knum" / zres, &
180 "xmin" / x1, &
181 "xmax" / x2, &
182 "ymin" / y1, &
183 "ymax" / y2, &
184 "zmin" / z1, &
185 "zmax" / z2, &
186! "decomposition"/ (/ 1, 1, 2/), &
187 "output/radius" / 1, &
188 "gparam" / gpar)
189
190 ! boundary conditions
191 boundary => dict( &
192 "western" / bc(west), &
193 "eastern" / bc(east), &
194 "southern" / bc(south), &
195 "northern" / bc(north), &
196 "bottomer" / bc(bottom), &
197 "topper" / bc(top))
198
199 ! physics settings
200 IF (csiso.GT.tiny(csiso)) THEN
201 physics => dict("problem" / euler_isotherm, &
202 "cs" / csiso) ! isothermal speed of sound
203 ELSE
204 physics => dict("problem" / euler, &
205 "gamma" / gamma) ! ratio of specific heats
206 END IF
207
208 ! flux calculation and reconstruction method
209 fluxes => dict( &
210 "order" / linear, &
211 "fluxtype" / kt, &
212 "variables" / primitive, &
213 "limiter" / vanleer, &
214 "output/slopes" / 0)
215
216 NULLIFY(sources)
217
218 ! time discretization settings
219 timedisc => dict( &
220 "method" / modified_euler, &
221 "order" / 3, &
222 "tol_rel" / 10.0, & ! > 1 disables adaptive step size
223 "cfl" / 0.4, &
224 "stoptime" / tsim, &
225 "dtlimit" / 1.0e-8, &
226 "maxiter" / 10000000)
227
228 datafile => dict( &
229 "fileformat" / xdmf, &
230 "filename" / (trim(odir) // trim(ofname)), &
231 "count" / onum)
232
233 config => dict( &
234 "mesh" / mesh, &
235 "physics" / physics, &
236 "boundary" / boundary, &
237 "fluxes" / fluxes, &
238 "datafile" / datafile, &
239 "timedisc" / timedisc)
240
241 IF (ASSOCIATED(sources)) &
242 CALL setattr(config, "sources", sources)
243
244 END SUBROUTINE makeconfig
245
246
247 SUBROUTINE initdata(Mesh,Physics,Timedisc)
249 IMPLICIT NONE
250 !------------------------------------------------------------------------!
251 CLASS(physics_base) :: Physics
252 CLASS(mesh_base) :: Mesh
253 CLASS(timedisc_base) :: Timedisc
254 REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX) &
255 :: radius
256 REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,3) &
257 :: posvec
258 !------------------------------------------------------------------------!
259 INTENT(IN) :: mesh,physics
260 INTENT(INOUT) :: timedisc
261 !------------------------------------------------------------------------!
262 IF (any((/abs(x0),abs(y0),abs(z0)/).GT.tiny(z0))) THEN
263 ! shifted point mass position:
264 ! compute curvilinear components of shift vector
265 posvec(:,:,:,1) = x0
266 posvec(:,:,:,2) = y0
267 posvec(:,:,:,3) = z0
268 CALL mesh%geometry%Convert2Curvilinear(mesh%bcenter,posvec,posvec)
269 ! subtract the result from the position vector:
270 ! this gives you the curvilinear components of all vectors pointing
271 ! from the point mass to the bary center of any cell on the mesh
272 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - posvec(:,:,:,:)
273 ! compute its absolute value
274 radius(:,:,:) = sqrt(posvec(:,:,:,1)**2+posvec(:,:,:,2)**2+posvec(:,:,:,3)**2)
275 ELSE
276 ! no shift of point mass set radius and posvec to Mesh defaults
277 radius(:,:,:) = mesh%radius%bcenter(:,:,:)
278 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
279 END IF
280
281 ! initial condition
282 SELECT TYPE(pvar => timedisc%pvar)
283 TYPE IS(statevector_eulerisotherm) ! isothermal HD
284 ! Gaussian density pulse
285 pvar%density%data3d(:,:,:) = rho0 + rho1*exp(-log(2.0) &
286 * (radius(:,:,:)/rwidth)**2)
287 ! vanishing velocities
288 pvar%velocity%data1d(:) = 0.0
289 TYPE IS(statevector_euler) ! non-isothermal HD
290 ! constant density
291 pvar%density%data1d(:) = rho0
292 ! Gaussian pressure pulse
293 pvar%pressure%data3d(:,:,:) = p0 + p1*exp(-log(2.0) &
294 * (radius(:,:,:)/rwidth)**2)
295 ! vanishing velocities
296 pvar%velocity%data1d(:) = 0.0
297 CLASS DEFAULT
298 CALL physics%Error("gauss3d::InitData","unsupported physics")
299 END SELECT
300
301 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
302
303 CALL mesh%Info(" DATA-----> initial condition: 3D Gaussian pulse")
304
305 END SUBROUTINE initdata
306
307END PROGRAM gauss3d
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
Definition: bondi2d.f90:274
subroutine makeconfig(Sim, config)
Definition: bondi2d.f90:165
program gauss3d
3D Gaussian pressure or density pulse with and without rotation
Definition: gauss3d.f90:32
Mathematical functions.
Definition: functions.f90:48
elemental real function, public acosh(x)
inverse hyperbolic cosine function
Definition: functions.f90:110
elemental real function, public gamma(x)
Compute the Gamma function for arguments != 0,-1,-2,..
Definition: functions.f90:1133
real, parameter pi
Definition: functions.f90:52
elemental real function, public asinh(x)
inverse hyperbolic sine function
Definition: functions.f90:100
base class for geometrical properties
main fosite class
Definition: fosite.f90:71