38 REAL,
PARAMETER :: tsim = 30.0
39 REAL,
PARAMETER :: re = 4.375
40 REAL,
PARAMETER :: pin = 24.0
41 REAL,
PARAMETER :: pout = 23.0
42 REAL,
PARAMETER :: rho0 = 1.0
44 INTEGER,
PARAMETER :: mgeo = cylindrical
46 INTEGER,
PARAMETER :: xres = 10
47 INTEGER,
PARAMETER :: yres = 10
48 INTEGER,
PARAMETER :: zres = 10
49 REAL,
PARAMETER :: ltube = 10.0
50 REAL,
PARAMETER :: rtube = 1.0
53 INTEGER,
PARAMETER :: onum = 10
54 CHARACTER(LEN=256),
PARAMETER &
56 CHARACTER(LEN=256),
PARAMETER &
57 :: ofname =
'poiseuille' 59 CLASS(
fosite),
ALLOCATABLE :: sim
71 CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
83 TYPE(Dict_TYP),
POINTER :: config
87 TYPE(Dict_TYP),
POINTER :: mesh, physics, boundary, datafile, sources, &
89 REAL :: x1,x2,y1,y2,z1,z2
125 mesh => dict(
"meshtype" / midpoint, &
138 boundary => dict(
"western" / bc(west), &
139 "eastern" / bc(east), &
140 "southern" / bc(south), &
141 "northern" / bc(north), &
142 "bottomer" / bc(bottom), &
146 physics => dict(
"problem" / euler, &
150 fluxes => dict(
"order" / linear, &
152 "variables" / primitive, &
153 "limiter" / monocent, &
158 dvis = sqrt(0.25 * (pin-pout) * rtube**3 * rho0 / ltube / re)
161 vis => dict(
"stype" / viscosity, &
162 "vismodel" / molecular, &
166 sources => dict(
"vis" / vis)
169 timedisc => dict(
"method" / modified_euler, &
173 "dtlimit" / 1.0e-8, &
178 "fileformat" / xdmf, &
179 "filename" / (trim(odir) // trim(ofname)), &
182 config => dict(
"mesh" / mesh, &
183 "physics" / physics, &
184 "boundary" / boundary, &
186 "sources" / sources, &
187 "timedisc" / timedisc, &
188 "datafile" / datafile)
191 SUBROUTINE initdata(Mesh,Physics,Timedisc)
194 CLASS(Physics_base) :: Physics
195 CLASS(Mesh_base) :: Mesh
196 CLASS(Timedisc_base):: Timedisc
198 INTENT(IN) :: mesh,physics
199 INTENT(INOUT) :: timedisc
202 timedisc%pvar%data4d(:,:,:,physics%DENSITY) = rho0
203 timedisc%pvar%data4d(:,:,:,physics%XVELOCITY) = 0.
204 timedisc%pvar%data4d(:,:,:,physics%YVELOCITY) = 0.
205 timedisc%pvar%data4d(:,:,:,physics%ZVELOCITY) = 0.
206 timedisc%pvar%data4d(:,:,:,physics%PRESSURE) = pin + (pout-pin)/ltube &
207 * mesh%bccart(:,:,:,3)
211 SELECT TYPE(bbottom => timedisc%Boundary%boundary(bottom)%p)
212 CLASS IS (boundary_fixed)
213 bbottom%data(:,:,:,physics%DENSITY) = rho0
214 bbottom%data(:,:,:,physics%XVELOCITY) = 0.0
215 bbottom%data(:,:,:,physics%YVELOCITY) = 0.0
216 bbottom%data(:,:,:,physics%ZVELOCITY) = 0.0
217 bbottom%data(:,:,:,physics%PRESSURE) = pin
220 bbottom%fixed(:,:,physics%DENSITY) = .true.
221 bbottom%fixed(:,:,physics%XVELOCITY) = .true.
222 bbottom%fixed(:,:,physics%YVELOCITY) = .true.
223 bbottom%fixed(:,:,physics%ZVELOCITY) = .false.
224 bbottom%fixed(:,:,physics%PRESSURE) = .true.
227 SELECT TYPE(btop => timedisc%Boundary%boundary(top)%p)
228 CLASS IS (boundary_fixed)
229 btop%data(:,:,:,physics%DENSITY) = rho0
230 btop%data(:,:,:,physics%XVELOCITY) = 0.0
231 btop%data(:,:,:,physics%YVELOCITY) = 0.0
232 btop%data(:,:,:,physics%ZVELOCITY) = 0.0
233 btop%data(:,:,:,physics%PRESSURE) = pout
236 btop%fixed(:,:,physics%DENSITY) = .false.
237 btop%fixed(:,:,physics%XVELOCITY) = .false.
238 btop%fixed(:,:,physics%YVELOCITY) = .false.
239 btop%fixed(:,:,physics%ZVELOCITY) = .false.
240 btop%fixed(:,:,physics%PRESSURE) = .true.
243 CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
244 CALL mesh%Info(
" DATA-----> initial condition: " // &
245 "tube with pressure gradient")
program poiseuille
Program and data initialization for testing the law of Hagen-Poiseuille.
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
subroutine makeconfig(Sim, config)