38 REAL,
PARAMETER :: tsim = 0.5
39 REAL,
PARAMETER :: gamma = 1.4
40 REAL,
PARAMETER :: csiso = &
45 REAL,
PARAMETER :: rho0 = 1.0
46 REAL,
PARAMETER :: rho1 = 1.0
47 REAL,
PARAMETER :: rwidth = 0.06
48 REAL,
PARAMETER :: p0 = 1.0
49 REAL,
PARAMETER :: p1 = 100.0
50 REAL,
PARAMETER :: pwidth = 0.06
51 REAL,
PARAMETER :: omega0 = 0.0
52 REAL,
PARAMETER :: eta = 0.0
54 REAL,
PARAMETER :: x0 = 0.0
55 REAL,
PARAMETER :: y0 = 0.0
56 REAL,
PARAMETER :: z0 = 0.0
58 INTEGER,
PARAMETER :: mgeo = cartesian
61 INTEGER,
PARAMETER :: res = 30
62 REAL,
PARAMETER :: rmax = 0.5
63 REAL,
PARAMETER :: gpar = 0.8
65 INTEGER,
PARAMETER :: onum = 10
66 CHARACTER(LEN=256),
PARAMETER &
68 CHARACTER(LEN=256),
PARAMETER &
71 CLASS(
fosite),
ALLOCATABLE :: sim
81 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
88 tap_check(ok,
"stoptime reached")
98 TYPE(Dict_TYP),
POINTER :: config
101 INTEGER :: bc(6),xres,yres,zres
102 TYPE(Dict_TYP),
POINTER :: mesh, physics, boundary, datafile, sources, &
104 REAL :: x1,x2,y1,y2,z1,z2
128 bc(south) = absorbing
129 bc(north) = absorbing
130 bc(bottom) = absorbing
146 bc(bottom) = absorbing
165 CALL error(sim%Physics,
"InitProgram",
"geometry not supported for this test")
170 "meshtype" / midpoint, &
182 "output/radius" / 1, &
187 "western" / bc(west), &
188 "eastern" / bc(east), &
189 "southern" / bc(south), &
190 "northern" / bc(north), &
191 "bottomer" / bc(bottom), &
195 IF (csiso.GT.tiny(csiso))
THEN 196 physics => dict(
"problem" / euler_isotherm, &
199 physics => dict(
"problem" / euler, &
207 "variables" / primitive, &
208 "limiter" / vanleer, &
215 "method" / modified_euler, &
220 "dtlimit" / 1.0e-8, &
221 "maxiter" / 10000000)
224 "fileformat" / vtk, &
225 "filename" / (trim(odir) // trim(ofname)), &
230 "physics" / physics, &
231 "boundary" / boundary, &
233 "datafile" / datafile, &
234 "timedisc" / timedisc)
236 IF (
ASSOCIATED(sources)) &
237 CALL setattr(config,
"sources", sources)
242 SUBROUTINE initdata(Mesh,Physics,Timedisc)
246 CLASS(physics_base) :: Physics
247 CLASS(mesh_base) :: Mesh
248 CLASS(timedisc_base) :: Timedisc
249 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX) &
251 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,3) &
254 INTENT(IN) :: mesh,physics
255 INTENT(INOUT) :: timedisc
257 IF (any((/abs(x0),abs(y0),abs(z0)/).GT.tiny(z0)))
THEN 263 CALL mesh%geometry%Convert2Curvilinear(mesh%bcenter,posvec,posvec)
267 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - posvec(:,:,:,:)
269 radius(:,:,:) = sqrt(posvec(:,:,:,1)**2+posvec(:,:,:,2)**2+posvec(:,:,:,3)**2)
272 radius(:,:,:) = mesh%radius%bcenter(:,:,:)
273 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
277 SELECT TYPE(pvar => timedisc%pvar)
278 TYPE IS(statevector_eulerisotherm)
280 pvar%density%data3d(:,:,:) = rho0 + rho1*exp(-log(2.0) &
281 * (radius(:,:,:)/rwidth)**2)
283 pvar%velocity%data1d(:) = 0.0
284 TYPE IS(statevector_euler)
286 pvar%density%data1d(:) = rho0
288 pvar%pressure%data3d(:,:,:) = p0 + p1*exp(-log(2.0) &
289 * (radius(:,:,:)/rwidth)**2)
291 pvar%velocity%data1d(:) = 0.0
293 CALL physics%Error(
"gauss3d::InitData",
"unsupported physics")
296 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
298 CALL mesh%Info(
" DATA-----> initial condition: 3D Gaussian pulse")
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
program gauss3d
3D Gaussian pressure or density pulse with and without rotation
elemental real function, public asinh(x)
inverse hyperbolic sine function
base class for geometrical properties
subroutine makeconfig(Sim, config)
elemental real function, public acosh(x)
inverse hyperbolic cosine function