39 REAL,
PARAMETER :: tsim = 0.3
40 REAL,
PARAMETER :: gamma = 1.4
41 REAL,
PARAMETER :: csiso = &
46 REAL,
PARAMETER :: rho0 = 1.0
47 REAL,
PARAMETER :: rho1 = 100.0
48 REAL,
PARAMETER :: rwidth = 0.06
49 REAL,
PARAMETER :: p0 = 1.0
50 REAL,
PARAMETER :: p1 = 100.0
51 REAL,
PARAMETER :: pwidth = 0.06
52 REAL,
PARAMETER :: omega0 = 0.0
53 REAL,
PARAMETER :: eta = 0.0
55 REAL,
PARAMETER :: r0 = 0.0
56 REAL,
PARAMETER :: z0 = 0.0
58 INTEGER,
PARAMETER :: mgeo = cartesian
59 INTEGER,
PARAMETER :: xres = 100
60 INTEGER,
PARAMETER :: yres = 100
61 INTEGER,
PARAMETER :: zres = 1
62 REAL,
PARAMETER :: rmax = 1.0
64 REAL,
PARAMETER :: gpar = 0.8
66 INTEGER,
PARAMETER :: onum = 10
67 CHARACTER(LEN=256),
PARAMETER &
69 CHARACTER(LEN=256),
PARAMETER &
72 CLASS(
fosite),
ALLOCATABLE :: sim
82 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
89 tap_check(ok,
"stoptime reached")
99 TYPE(Dict_TYP),
POINTER :: config
103 TYPE(Dict_TYP),
POINTER :: mesh, physics, boundary, datafile, sources, &
105 REAL :: x1,x2,y1,y2,z1,z2
120 bc(south) = absorbing
121 bc(north) = absorbing
126 bc(bottom) = no_gradients
127 bc(top) = no_gradients
129 CALL error(sim%Physics,
"InitProgram",
"geometry not supported for this test")
134 "meshtype" / midpoint, &
150 "western" / bc(west), &
151 "eastern" / bc(east), &
152 "southern" / bc(south), &
153 "northern" / bc(north), &
154 "bottomer" / bc(bottom), &
158 IF (csiso.GT.tiny(csiso))
THEN 159 physics => dict(
"problem" / euler_isotherm, &
162 physics => dict(
"problem" / euler, &
171 "variables" / conservative, &
172 "limiter" / vanleer, &
179 "method" / modified_euler, &
184 "dtlimit" / 1.0e-8, &
185 "maxiter" / 10000000)
188 "fileformat" / vtk, &
189 "filename" / (trim(odir) // trim(ofname)), &
194 "physics" / physics, &
195 "boundary" / boundary, &
197 "datafile" / datafile, &
198 "timedisc" / timedisc)
200 IF (
ASSOCIATED(sources)) &
201 CALL setattr(config,
"sources", sources)
206 SUBROUTINE initdata(Mesh,Physics,Timedisc)
211 CLASS(physics_base) :: Physics
212 CLASS(mesh_base) :: Mesh
213 CLASS(timedisc_base) :: Timedisc
214 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX) &
216 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,3) &
219 INTENT(IN) :: mesh,physics
220 INTENT(INOUT) :: timedisc
222 IF (abs(r0).LE.tiny(r0).AND.abs(z0).LE.tiny(z0))
THEN 224 radius(:,:,:) = mesh%radius%bcenter(:,:,:)
225 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
231 CALL convert2curvilinear(mesh%geometry,mesh%bcenter,posvec,posvec)
235 posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - posvec(:,:,:,:)
237 radius(:,:,:) = sqrt(posvec(:,:,:,1)**2+posvec(:,:,:,2)**2)
241 SELECT TYPE(pvar => timedisc%pvar)
244 pvar%density%data3d(:,:,:) = rho0 + rho1*exp(-log(2.0) &
245 * (radius(:,:,:)/rwidth)**2)
247 pvar%velocity%data1d(:) = 0.0
250 pvar%density%data1d(:) = rho0
252 pvar%pressure%data3d(:,:,:) = p0 + p1*exp(-log(2.0) &
253 * (radius(:,:,:)/rwidth)**2)
255 pvar%velocity%data1d(:) = 0.0
258 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
260 CALL mesh%Info(
" DATA-----> initial condition: 2D Gaussian pulse")
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
elemental real function, public asinh(x)
inverse hyperbolic sine function
program gauss2d
2D Gaussian pressure or density pulse with and without rotation
subroutine makeconfig(Sim, config)
physics module for 1D,2D and 3D isothermal Euler equations
physics module for 1D,2D and 3D non-isothermal Euler equations
elemental real function, public acosh(x)
inverse hyperbolic cosine function