55 REAL,
PARAMETER :: tsim = 10.0
58 REAL,
PARAMETER :: dynvis = 1.0e-4
59 REAL,
PARAMETER :: bulkvis = -6.67e-5
61 REAL,
PARAMETER :: rho0 = 2.0
62 REAL,
PARAMETER :: rho1 = 1.0
63 REAL,
PARAMETER :: yacc = 0.2
64 REAL,
PARAMETER :: p0 = 1.2
65 REAL,
PARAMETER :: a0 = 0.02
67 INTEGER,
PARAMETER :: xres = 50
68 INTEGER,
PARAMETER :: yres = 100
69 INTEGER,
PARAMETER :: zres = 1
70 REAL,
PARAMETER :: width = 1.0
71 REAL,
PARAMETER :: height = 2.0
73 INTEGER,
PARAMETER :: onum = 10
74 CHARACTER(LEN=256),
PARAMETER &
76 CHARACTER(LEN=256),
PARAMETER &
79 CLASS(
fosite),
ALLOCATABLE :: sim
89 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc%pvar, sim%Timedisc%cvar)
94 tap_check(.true.,
"Simulation finished")
104 TYPE(dict_typ),
POINTER :: config
106 TYPE(dict_typ),
POINTER :: mesh, physics, boundary, datafile, &
107 sources, timedisc, fluxes, caccel, vis
119 "meshtype" / midpoint, &
120 "geometry" / cartesian, &
124 "xmin" / (-0.5*width), &
125 "xmax" / (0.5*width), &
140 "variables" / conservative, &
141 "limiter" / monocent, &
146 "western" / reflecting, &
147 "eastern" / reflecting, &
148 "southern" / reflecting, &
149 "northern" / reflecting, &
150 "bottomer" / reflecting, &
151 "topper" / reflecting)
159 sources => dict(
"caccel" / caccel)
163 IF (dynvis.GT.tiny(dynvis).OR.bulkvis.GT.tiny(bulkvis))
THEN
165 "stype" / viscosity, &
166 "vismodel" / molecular, &
167 "dynconst" / dynvis, &
168 "bulkconst" / bulkvis)
170 CALL setattr(sources,
"vis", vis)
175 "method" / modified_euler, &
179 "dtlimit" / 1.0e-4, &
184 "fileformat" / vtk, &
185 "filename" / (trim(odir) // trim(ofname)), &
191 "physics" / physics, &
192 "boundary" / boundary, &
194 "sources" / sources, &
195 "timedisc" / timedisc, &
196 "datafile" / datafile)
204 CLASS(mesh_base),
INTENT(IN) :: Mesh
205 CLASS(physics_base),
INTENT(IN) :: Physics
206 CLASS(marray_compound),
POINTER,
INTENT(INOUT) :: pvar,cvar
209 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX) &
214 y0(:,:,:) = 0.5*mesh%ymax - a0*exp(-0.5/(0.4*width)**2 &
215 * (mesh%bcenter(:,:,:,1)**2+mesh%bcenter(:,:,:,3)**2))
218 SELECT TYPE(p => pvar)
219 TYPE IS(statevector_euler)
220 WHERE (mesh%bcenter(:,:,:,2).GT.y0(:,:,:))
222 p%density%data3d(:,:,:) = rho0
223 p%pressure%data3d(:,:,:) = p0 + yacc * rho0 * (mesh%ymax-mesh%bcenter(:,:,:,2))
226 p%density%data3d(:,:,:) = rho1
227 p%pressure%data3d(:,:,:) = p0 + yacc * (rho1 * (y0(:,:,:)-mesh%bcenter(:,:,:,2)) &
228 + rho0 * (mesh%ymax-y0(:,:,:)))
231 p%velocity%data1d(:) = 0.
233 CALL physics%Error(
"RTI::InitData",
"only non-isothermal HD supported")
236 CALL physics%Convert2Conservative(pvar,cvar)
237 CALL mesh%Info(
" DATA-----> initial condition: " // &
238 –
"RayleighTaylor instability")
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
subroutine makeconfig(Sim, config)