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 = 1.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)
93 tap_check(ok,
"stoptime reached")
103 TYPE(dict_typ),
POINTER :: config
106 INTEGER :: bc(6),xres,yres,zres
107 TYPE(dict_typ),
POINTER :: mesh, physics, boundary, datafile, sources, &
109 REAL :: x1,x2,y1,y2,z1,z2
133 bc(south) = absorbing
134 bc(north) = absorbing
135 bc(bottom) = absorbing
151 bc(bottom) = absorbing
170 CALL sim%Error(
"InitProgram",
"geometry not supported for this test")
175 "meshtype" / midpoint, &
187 "output/radius" / 1, &
192 "western" / bc(west), &
193 "eastern" / bc(east), &
194 "southern" / bc(south), &
195 "northern" / bc(north), &
196 "bottomer" / bc(bottom), &
200 IF (csiso.GT.tiny(csiso))
THEN
201 physics => dict(
"problem" / euler_isotherm, &
204 physics => dict(
"problem" / euler, &
212 "variables" / primitive, &
213 "limiter" / vanleer, &
220 "method" / modified_euler, &
225 "dtlimit" / 1.0e-8, &
226 "maxiter" / 10000000)
229 "fileformat" / xdmf, &
230 "filename" / (trim(odir) // trim(ofname)), &
235 "physics" / physics, &
236 "boundary" / boundary, &
238 "datafile" / datafile, &
239 "timedisc" / timedisc)
241 IF (
ASSOCIATED(sources)) &
242 CALL setattr(config,
"sources", sources)
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) &
256 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,3) &
259 INTENT(IN) :: mesh,physics
260 INTENT(INOUT) :: timedisc
262 IF (any((/abs(x0),abs(y0),abs(z0)/).GT.tiny(z0)))
THEN
268 CALL mesh%geometry%Convert2Curvilinear(mesh%bcenter,posvec,posvec)
272 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - posvec(:,:,:,:)
274 radius(:,:,:) = sqrt(posvec(:,:,:,1)**2+posvec(:,:,:,2)**2+posvec(:,:,:,3)**2)
277 radius(:,:,:) = mesh%radius%bcenter(:,:,:)
278 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
282 SELECT TYPE(pvar => timedisc%pvar)
283 TYPE IS(statevector_eulerisotherm)
285 pvar%density%data3d(:,:,:) = rho0 + rho1*exp(-log(2.0) &
286 * (radius(:,:,:)/rwidth)**2)
288 pvar%velocity%data1d(:) = 0.0
289 TYPE IS(statevector_euler)
291 pvar%density%data1d(:) = rho0
293 pvar%pressure%data3d(:,:,:) = p0 + p1*exp(-log(2.0) &
294 * (radius(:,:,:)/rwidth)**2)
296 pvar%velocity%data1d(:) = 0.0
298 CALL physics%Error(
"gauss3d::InitData",
"unsupported physics")
301 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
303 CALL mesh%Info(
" DATA-----> initial condition: 3D Gaussian pulse")
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
subroutine makeconfig(Sim, config)
program gauss3d
3D Gaussian pressure or density pulse with and without rotation
elemental real function, public acosh(x)
inverse hyperbolic cosine function
elemental real function, public gamma(x)
Compute the Gamma function for arguments != 0,-1,-2,..
elemental real function, public asinh(x)
inverse hyperbolic sine function
base class for geometrical properties