poiseuille.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: poiseuille.f90 #
5 !# #
6 !# Copyright (C) 2006-2019 #
7 !# Bjoern Sperling <sperling@astrophysik.uni-kiel.de> #
8 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
9 !# #
10 !# This program is free software; you can redistribute it and/or modify #
11 !# it under the terms of the GNU General Public License as published by #
12 !# the Free Software Foundation; either version 2 of the License, or (at #
13 !# your option) any later version. #
14 !# #
15 !# This program is distributed in the hope that it will be useful, but #
16 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
17 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18 !# NON INFRINGEMENT. See the GNU General Public License for more #
19 !# details. #
20 !# #
21 !# You should have received a copy of the GNU General Public License #
22 !# along with this program; if not, write to the Free Software #
23 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24 !# #
25 !#############################################################################
32 !----------------------------------------------------------------------------!
33 PROGRAM poiseuille
34  USE fosite_mod
35  IMPLICIT NONE
36  !--------------------------------------------------------------------------!
37  ! simulation parameters
38  REAL, PARAMETER :: tsim = 30.0 ! simulation time !
39  REAL, PARAMETER :: re = 4.375 ! Reynolds Number !
40  REAL, PARAMETER :: pin = 24.0 ! inflow pressure !
41  REAL, PARAMETER :: pout = 23.0 ! outflow pressure !
42  REAL, PARAMETER :: rho0 = 1.0 ! initial density !
43  ! mesh settings
44  INTEGER, PARAMETER :: mgeo = cylindrical
45 ! INTEGER, PARAMETER :: MGEO = CARTESIAN
46  INTEGER, PARAMETER :: xres = 10 ! radial resolution !
47  INTEGER, PARAMETER :: yres = 10 ! azimuthal resolution !
48  INTEGER, PARAMETER :: zres = 10 ! resolution along the tube !
49  REAL, PARAMETER :: ltube = 10.0 ! length of the tube !
50  REAL, PARAMETER :: rtube = 1.0 ! radius of the tube !
51  !--------------------------------------------------------------------------!
52  ! output file parameter
53  INTEGER, PARAMETER :: onum = 10 ! number of output data sets
54  CHARACTER(LEN=256), PARAMETER & ! output data dir
55  :: odir = './'
56  CHARACTER(LEN=256), PARAMETER & ! output data file name
57  :: ofname = 'poiseuille'
58  !--------------------------------------------------------------------------!
59  CLASS(fosite),ALLOCATABLE :: sim
60  !--------------------------------------------------------------------------!
61  ALLOCATE(sim)
62  CALL sim%InitFosite()
63 
64  CALL makeconfig(sim, sim%config)
65 
66 ! CALL PrintDict(config)
67 
68  CALL sim%Setup()
69 
70  ! set initial condition
71  CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
72 
73  CALL sim%Run()
74  CALL sim%Finalize()
75  DEALLOCATE(sim)
76 
77 CONTAINS
78 
79  SUBROUTINE makeconfig(Sim, config)
80  IMPLICIT NONE
81  !------------------------------------------------------------------------!
82  CLASS(Fosite) :: Sim
83  TYPE(Dict_TYP),POINTER :: config
84  !------------------------------------------------------------------------!
85  ! Local variable declaration
86  INTEGER :: bc(6)
87  TYPE(Dict_TYP), POINTER :: mesh, physics, boundary, datafile, sources, &
88  vis, timedisc, fluxes
89  REAL :: x1,x2,y1,y2,z1,z2
90  REAL :: dvis, bvis
91  !------------------------------------------------------------------------!
92  INTENT(INOUT) :: sim
93  !------------------------------------------------------------------------!
94  ! geometry dependent setttings
95  SELECT CASE(mgeo)
96  CASE(cylindrical)
97  x1 = 0.0
98  x2 = rtube
99  y1 = 0.0
100  y2 = 2*pi
101  z1 = 0.0
102  z2 = ltube
103  bc(west) = axis
104  bc(east) = noslip
105  bc(south) = periodic
106  bc(north) = periodic
107  bc(bottom)= fixed
108  bc(top) = fixed
109  CASE(cartesian)
110  x1 = 0.0
111  x2 = rtube
112  y1 = 0.0
113  y2 = rtube
114  z1 = 0.0
115  z2 = ltube
116  bc(west) = noslip
117  bc(east) = noslip
118  bc(south) = noslip
119  bc(north) = noslip
120  bc(bottom)= fixed
121  bc(top) = fixed
122  END SELECT
123 
124  ! mesh settings
125  mesh => dict("meshtype" / midpoint, &
126  "geometry" / mgeo, &
127  "inum" / xres, &
128  "jnum" / yres, &
129  "knum" / zres, &
130  "xmin" / x1, &
131  "xmax" / x2, &
132  "ymin" / y1, &
133  "ymax" / y2, &
134  "zmin" / z1, &
135  "zmax" / z2)
136 
137  ! boundary conditions
138  boundary => dict("western" / bc(west), &
139  "eastern" / bc(east), &
140  "southern" / bc(south), &
141  "northern" / bc(north), &
142  "bottomer" / bc(bottom), &
143  "topper" / bc(top))
144 
145  ! physics settings
146  physics => dict("problem" / euler, &
147  "gamma" / 1.4) ! ratio of specific heats !
148 
149  ! flux calculation and reconstruction method
150  fluxes => dict("order" / linear, &
151  "fluxtype" / kt, &
152  "variables" / primitive, & ! vars. to use for reconstruction!
153  "limiter" / monocent, & ! one of: minmod, monocent,... !
154  "theta" / 1.2) ! optional parameter for limiter !
155 
156  ! viscosity source term
157  ! dynamic viscosity
158  dvis = sqrt(0.25 * (pin-pout) * rtube**3 * rho0 / ltube / re)
159  ! bulk viscosity
160  bvis = -2./3. * dvis
161  vis => dict("stype" / viscosity, &
162  "vismodel" / molecular, &
163  "dynconst" / dvis, &
164  "bulkconst" / bvis)
165 
166  sources => dict("vis" / vis)
167 
168  ! time discretization settings
169  timedisc => dict("method" / modified_euler, &
170  "order" / 3, &
171  "cfl" / 0.4, &
172  "stoptime" / tsim, &
173  "dtlimit" / 1.0e-8, &
174  "maxiter" / 1000000)
175 
176  ! initialize data input/output
177  datafile => dict( &
178  "fileformat" / xdmf, &
179  "filename" / (trim(odir) // trim(ofname)), &
180  "count" / onum)
181 
182  config => dict("mesh" / mesh, &
183  "physics" / physics, &
184  "boundary" / boundary, &
185  "fluxes" / fluxes, &
186  "sources" / sources, &
187  "timedisc" / timedisc, &
188  "datafile" / datafile)
189  END SUBROUTINE makeconfig
190 
191  SUBROUTINE initdata(Mesh,Physics,Timedisc)
192  IMPLICIT NONE
193  !------------------------------------------------------------------------!
194  CLASS(Physics_base) :: Physics
195  CLASS(Mesh_base) :: Mesh
196  CLASS(Timedisc_base):: Timedisc
197  !------------------------------------------------------------------------!
198  INTENT(IN) :: mesh,physics
199  INTENT(INOUT) :: timedisc
200  !------------------------------------------------------------------------!
201  ! initial condition
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)
208 
209  ! fixed boundary conditions
210  ! inflow
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
218  ! imposed density, pressure and tangential velocities;
219  ! extrapolated normal velocity
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.
225  END SELECT
226  ! outflow
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
234  ! imposed pressure;
235  ! extrapolated density, tangential and normal velocities
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.
241  END SELECT
242 
243  CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
244  CALL mesh%Info(" DATA-----> initial condition: " // &
245  "tube with pressure gradient")
246 
247  END SUBROUTINE initdata
248 
249 END PROGRAM poiseuille
program poiseuille
Program and data initialization for testing the law of Hagen-Poiseuille.
Definition: poiseuille.f90:33
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
Definition: bondi2d.f90:274
main fosite class
Definition: fosite.f90:71
subroutine makeconfig(Sim, config)
Definition: bondi2d.f90:165