44 REAL,
PARAMETER :: tsim = 0.05
45 REAL,
PARAMETER :: gamma = 1.4
47 REAL,
PARAMETER :: rho0 = 1.0
48 REAL,
PARAMETER :: p0 = 1.0e-05
49 REAL,
PARAMETER :: e1 = 1.0
53 REAL,
PARAMETER :: r0 = 3.0e-2
55 INTEGER,
PARAMETER :: mgeo = cartesian
61 INTEGER,
PARAMETER :: xres = 100
62 INTEGER,
PARAMETER :: yres = 100
63 INTEGER,
PARAMETER :: zres = 1
64 REAL,
PARAMETER :: rmin = 1.0e-3
65 REAL,
PARAMETER :: rmax = 0.3
66 REAL,
PARAMETER :: gpar = 0.2
68 INTEGER,
PARAMETER :: onum = 5
69 CHARACTER(LEN=256),
PARAMETER &
71 CHARACTER(LEN=256),
PARAMETER &
74 CLASS(
fosite),
ALLOCATABLE :: sim
76 INTEGER,
PARAMETER :: num = 5
78 CHARACTER(LEN=256),
DIMENSION(NUM) :: odename
79 REAL,
DIMENSION(NUM) :: time
80 CHARACTER(LEN=256) :: prefix, buffer
88 write(prefix,
'((A),(I2.2),(A),(I2.2))')
"_ode-",ode,
"_geo-",mgeo
94 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
98 CALL sim%ComputeRunTime()
99 time(ode) = sim%run_time
100 odename(ode) = sim%Timedisc%GetName()
102 tap_check(.true.,
"Simulation finished")
108 CALL sim%Info(repeat(
"*",64))
110 WRITE(buffer,
'((a),(I2),(A),(F5.2))')
"#", i,
". RUN, ODE solver: " //trim(odename(i)) //
", runtime: ", time(i)
111 CALL sim%Info(buffer)
113 CALL sim%Info(repeat(
"*",64))
126 TYPE(Dict_TYP),
POINTER :: config
131 TYPE(Dict_TYP),
POINTER :: mesh, physics, boundary, datafile, &
133 REAL :: x1,x2,y1,y2,z1,z2
177 CALL sim%Error(
"InitProgram",
"mesh geometry not supported for 2D Sedov explosion")
180 mesh => dict(
"meshtype" / midpoint, &
196 bc(west) = no_gradients
197 bc(east) = no_gradients
198 bc(south) = no_gradients
199 bc(north) = no_gradients
200 bc(bottom)= no_gradients
201 bc(top) = no_gradients
203 bc(west) = no_gradients
204 bc(east) = no_gradients
207 bc(bottom)= no_gradients
208 bc(top) = no_gradients
230 CALL sim%Error(
"InitProgram",
"mesh geometry not supported for 2D Sedov explosion")
234 boundary => dict(
"western" / bc(west), &
235 "eastern" / bc(east), &
236 "southern" / bc(south), &
237 "northern" / bc(north), &
238 "bottomer" / bc(bottom), &
242 physics => dict(
"problem" / euler, &
246 fluxes => dict(
"order" / linear, &
248 "variables" / conservative, &
249 "limiter" / monocent, &
256 "ShowButcherTableau" / 1, &
258 "dtlimit" / 1.0e-15, &
260 "tol_abs" / (/0.0,1e-3,1e-3,0.0/), &
261 "output/error" / 1, &
265 datafile => dict(
"fileformat" / vtk, &
267 "filename" / (trim(odir) // trim(ofname) //trim(prefix)), &
270 config => dict(
"mesh" / mesh, &
271 "physics" / physics, &
272 "boundary" / boundary, &
274 "timedisc" / timedisc, &
275 "datafile" / datafile)
279 SUBROUTINE initdata(Mesh,Physics,Timedisc)
283 CLASS(Physics_base) :: Physics
284 CLASS(Mesh_base) :: Mesh
285 CLASS(Timedisc_base):: Timedisc
291 INTENT(IN) :: mesh,physics
292 INTENT(INOUT) :: timedisc
295 SELECT TYPE (phys => physics)
299 p1 = 3.*(phys%gamma - 1.0)*e1 / ((n + 1)*pi*r0**n)
302 CALL phys%Error(
"InitData",
"physics not supported")
306 timedisc%pvar%data4d(:,:,:,physics%DENSITY) = rho0
308 timedisc%pvar%data4d(:,:,:,physics%XVELOCITY) = 0.
309 timedisc%pvar%data4d(:,:,:,physics%YVELOCITY) = 0.
311 WHERE ((mesh%bccart(:,:,:,1)**2 + mesh%bccart(:,:,:,2)**2 + mesh%bccart(:,:,:,3)**2).LE.r0**2)
313 timedisc%pvar%data4d(:,:,:,physics%PRESSURE) = p1
316 timedisc%pvar%data4d(:,:,:,physics%PRESSURE) = p0
319 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
320 CALL mesh%Info(
" DATA-----> initial condition: 2D Sedov explosion")
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
subroutine makeconfig(Sim, config)
physics module for 1D,2D and 3D non-isothermal Euler equations