ode.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: sedov2d.f90 #
5 !# #
6 !# Copyright (C) 2006-2012, 2013 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# Björn Sperling <sperling@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 !#############################################################################
26 
27 !----------------------------------------------------------------------------!
31 
32 !! References:
33 !! \cite sedov1945 Sedov, L. I.: Unsteady motions of compressible fluids,
34 !! J. Appl. Math. Mech. 9 (1945)
35 !! \cite sedov1959 Sedov, L. I.: Similarity and Dimensional Methods in Mechanics
36 !! Academic Press Ltd., New York (1959)
37 !----------------------------------------------------------------------------!
38 PROGRAM ode_test
39  USE fosite_mod
40 #include "tap.h"
41  IMPLICIT NONE
42  !--------------------------------------------------------------------------!
43  ! simulation parameters
44  REAL, PARAMETER :: tsim = 0.05 ! simulation stop time
45  REAL, PARAMETER :: gamma = 1.4 ! ratio of specific heats
46  ! initial condition (dimensionless units)
47  REAL, PARAMETER :: rho0 = 1.0 ! ambient density
48  REAL, PARAMETER :: p0 = 1.0e-05 ! ambient pressure
49  REAL, PARAMETER :: e1 = 1.0 ! initial energy input
50  ! Spatial with of the initial pulse should be at least 5 cells;
51  ! if you wish to compare the results on different grids
52  ! R0 should be of the same order
53  REAL, PARAMETER :: r0 = 3.0e-2
54  ! mesh settings
55  INTEGER, PARAMETER :: mgeo = cartesian ! geometry
56 ! INTEGER, PARAMETER :: MGEO = CYLINDRICAL ! geometry
57 !!$ INTEGER, PARAMETER :: MGEO = POLAR
58 !!$ INTEGER, PARAMETER :: MGEO = LOGPOLAR
59 !!$ INTEGER, PARAMETER :: MGEO = TANPOLAR
60 !!$ INTEGER, PARAMETER :: MGEO = SINHPOLAR
61  INTEGER, PARAMETER :: xres = 100 ! x-resolution
62  INTEGER, PARAMETER :: yres = 100 ! y-resolution
63  INTEGER, PARAMETER :: zres = 1 ! z-resolution
64  REAL, PARAMETER :: rmin = 1.0e-3 ! inner radius for polar grids
65  REAL, PARAMETER :: rmax = 0.3 ! outer radius
66  REAL, PARAMETER :: gpar = 0.2 ! geometry scaling parameter !
67  ! output parameters
68  INTEGER, PARAMETER :: onum = 5 ! number of output data sets
69  CHARACTER(LEN=256), PARAMETER & ! output data dir
70  :: odir = './'
71  CHARACTER(LEN=256), PARAMETER & ! output data file name
72  :: ofname = 'ode'
73  !--------------------------------------------------------------------------!
74  CLASS(fosite),ALLOCATABLE :: sim
75  !--------------------------------------------------------------------------!
76  INTEGER, PARAMETER :: num = 5 ! last ODE-solver
77  INTEGER :: ode, i
78  CHARACTER(LEN=256),DIMENSION(NUM) :: odename
79  REAL,DIMENSION(NUM) :: time
80  CHARACTER(LEN=256) :: prefix, buffer
81  !--------------------------------------------------------------------------!
82 
83  tap_plan(num)
84 DO ode=1,num
85  ALLOCATE(sim)
86  CALL sim%InitFosite()
87 
88  write(prefix,'((A),(I2.2),(A),(I2.2))') "_ode-",ode,"_geo-",mgeo
89  CALL makeconfig(sim, sim%config,ode)
90 
91 ! CALL PrintDict(Sim%config)
92  CALL sim%Setup()
93  ! set initial condition
94  CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
95 
96  CALL sim%Run()
97 
98  CALL sim%ComputeRunTime()
99  time(ode) = sim%run_time
100  odename(ode) = sim%Timedisc%GetName()
101 
102  tap_check(.true.,"Simulation finished")
103  IF(ode.NE.num) THEN
104  CALL sim%Finalize()
105  Deallocate(sim)
106  END IF
107 END DO
108  CALL sim%Info(repeat("*",64))
109  DO i=1,num
110  WRITE(buffer,'((a),(I2),(A),(F5.2))') "#", i, ". RUN, ODE solver: " //trim(odename(i)) //", runtime: ", time(i)
111  CALL sim%Info(buffer)
112  END DO
113  CALL sim%Info(repeat("*",64))
114 
115  CALL sim%Finalize()
116  Deallocate(sim)
117 
118  tap_done
119 
120 CONTAINS
121 
122  SUBROUTINE makeconfig(Sim, config, i)
123  IMPLICIT NONE
124  !------------------------------------------------------------------------!
125  CLASS(Fosite) :: Sim
126  TYPE(Dict_TYP),POINTER :: config
127  INTEGER :: i
128  !------------------------------------------------------------------------!
129  ! Local variable declaration
130  INTEGER :: bc(6)
131  TYPE(Dict_TYP), POINTER :: mesh, physics, boundary, datafile, &
132  timedisc, fluxes
133  REAL :: x1,x2,y1,y2,z1,z2
134  !------------------------------------------------------------------------!
135  INTENT(IN) :: i
136  INTENT(INOUT) :: sim
137  !------------------------------------------------------------------------!
138  ! mesh settings and boundary conditions
139  SELECT CASE(mgeo)
140  CASE(cartesian)
141  x1 =-rmax
142  x2 = rmax
143  y1 =-rmax
144  y2 = rmax
145  z1 = 0.0
146  z2 = 0.0
147 ! CASE(POLAR)
148 ! x1 = RMIN
149 ! x2 = RMAX
150 ! y1 = 0.0
151 ! y2 = 2*PI
152  CASE(cylindrical)
153  x1 = rmin
154  x2 = rmax
155  y1 = 0.0
156  y2 = 2*pi
157  z1 = 0.0
158  z2 = 0.0
159 ! CASE(LOGPOLAR)
160 ! x1 = LOG(RMIN/GPAR)
161 ! x2 = LOG(RMAX/GPAR)
162 ! y1 = 0.0
163 ! y2 = 2*PI
164 ! CASE(TANPOLAR)
165 ! x1 = ATAN(RMIN/GPAR)
166 ! x2 = ATAN(RMAX/GPAR)
167 ! y1 = 0.0
168 ! y2 = 2*PI
169 ! CASE(SINHPOLAR)
170 ! x1 = RMIN/GPAR
171 ! x1 = LOG(x1+SQRT(1.0+x1*x1)) ! = ASINH(RMIN/GPAR))
172 ! x2 = RMAX/GPAR
173 ! x2 = LOG(x2+SQRT(1.0+x2*x2)) ! = ASINH(RMAX/GPAR))
174 ! y1 = 0.0
175 ! y2 = 2*PI
176  CASE DEFAULT
177  CALL sim%Error("InitProgram","mesh geometry not supported for 2D Sedov explosion")
178  END SELECT
179  ! mesh settings
180  mesh => dict("meshtype" / midpoint, &
181  "geometry" / mgeo, &
182  "inum" / xres, &
183  "jnum" / yres, &
184  "knum" / zres, &
185  "xmin" / x1, &
186  "xmax" / x2, &
187  "ymin" / y1, &
188  "ymax" / y2, &
189  "zmin" / z1, &
190  "zmax" / z2, &
191  "gparam" / gpar)
192 
193  ! mesh settings and boundary conditions
194  SELECT CASE(mgeo)
195  CASE(cartesian)
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
202  CASE(cylindrical)
203  bc(west) = no_gradients
204  bc(east) = no_gradients
205  bc(south) = periodic
206  bc(north) = periodic
207  bc(bottom)= no_gradients
208  bc(top) = no_gradients
209 ! CASE(POLAR)
210 ! bc(WEST) = NO_GRADIENTS
211 ! bc(EAST) = NO_GRADIENTS
212 ! bc(SOUTH) = PERIODIC
213 ! bc(NORTH) = PERIODIC
214 ! CASE(LOGPOLAR)
215 ! bc(WEST) = NO_GRADIENTS
216 ! bc(EAST) = NO_GRADIENTS
217 ! bc(SOUTH) = PERIODIC
218 ! bc(NORTH) = PERIODIC
219 ! CASE(TANPOLAR)
220 ! bc(WEST) = NO_GRADIENTS
221 ! bc(EAST) = NO_GRADIENTS
222 ! bc(SOUTH) = PERIODIC
223 ! bc(NORTH) = PERIODIC
224 ! CASE(SINHPOLAR)
225 ! bc(WEST) = NO_GRADIENTS
226 ! bc(EAST) = NO_GRADIENTS
227 ! bc(SOUTH) = PERIODIC
228 ! bc(NORTH) = PERIODIC
229  CASE DEFAULT
230  CALL sim%Error("InitProgram","mesh geometry not supported for 2D Sedov explosion")
231  END SELECT
232 
233  ! boundary conditions
234  boundary => dict("western" / bc(west), &
235  "eastern" / bc(east), &
236  "southern" / bc(south), &
237  "northern" / bc(north), &
238  "bottomer" / bc(bottom), &
239  "topper" / bc(top))
240 
241  ! physics settings
242  physics => dict("problem" / euler, &
243  "gamma" / gamma) ! ratio of specific heats !
244 
245  ! flux calculation and reconstruction method
246  fluxes => dict("order" / linear, &
247  "fluxtype" / kt, &
248  "variables" / conservative, & ! vars. to use for reconstruction!
249  "limiter" / monocent, & ! one of: minmod, monocent,... !
250  "theta" / 1.2) ! optional parameter for limiter !
251 
252  ! time discretization settings
253  timedisc => dict( &
254  "method" / i, &
255  "cfl" / 0.3, &
256  "ShowButcherTableau" / 1, &
257  "stoptime" / tsim, &
258  "dtlimit" / 1.0e-15, &
259  "tol_rel" / 0.01, &
260  "tol_abs" / (/0.0,1e-3,1e-3,0.0/), &
261  "output/error" / 1, &
262  "maxiter" / 1000000)
263 
264  ! initialize data input/output
265  datafile => dict("fileformat" / vtk, &
266 ! datafile => Dict("fileformat" / GNUPLOT, "filecycles" / 0, &
267  "filename" / (trim(odir) // trim(ofname) //trim(prefix)), &
268  "count" / onum)
269 
270  config => dict("mesh" / mesh, &
271  "physics" / physics, &
272  "boundary" / boundary, &
273  "fluxes" / fluxes, &
274  "timedisc" / timedisc, &
275  "datafile" / datafile)
276  END SUBROUTINE makeconfig
277 
278 
279  SUBROUTINE initdata(Mesh,Physics,Timedisc)
281  IMPLICIT NONE
282  !------------------------------------------------------------------------!
283  CLASS(Physics_base) :: Physics
284  CLASS(Mesh_base) :: Mesh
285  CLASS(Timedisc_base):: Timedisc
286  !------------------------------------------------------------------------!
287  ! Local variable declaration
288  INTEGER :: n
289  REAL :: P1
290  !------------------------------------------------------------------------!
291  INTENT(IN) :: mesh,physics
292  INTENT(INOUT) :: timedisc
293  !------------------------------------------------------------------------!
294  ! isothermal modules are excluded
295  SELECT TYPE (phys => physics)
296  CLASS IS(physics_euler)
297  ! peak pressure
298  n = 2 ! 3 for 3D
299  p1 = 3.*(phys%gamma - 1.0)*e1 / ((n + 1)*pi*r0**n)
300  CLASS DEFAULT
301  ! abort
302  CALL phys%Error("InitData","physics not supported")
303  END SELECT
304 
305  ! uniform density
306  timedisc%pvar%data4d(:,:,:,physics%DENSITY) = rho0
307  ! vanishing initial velocities
308  timedisc%pvar%data4d(:,:,:,physics%XVELOCITY) = 0.
309  timedisc%pvar%data4d(:,:,:,physics%YVELOCITY) = 0.
310  ! pressure
311  WHERE ((mesh%bccart(:,:,:,1)**2 + mesh%bccart(:,:,:,2)**2 + mesh%bccart(:,:,:,3)**2).LE.r0**2)
312  ! behind the shock front
313  timedisc%pvar%data4d(:,:,:,physics%PRESSURE) = p1
314  ELSEWHERE
315  ! in front of the shock front (ambient medium)
316  timedisc%pvar%data4d(:,:,:,physics%PRESSURE) = p0
317  END WHERE
318 
319  CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
320  CALL mesh%Info(" DATA-----> initial condition: 2D Sedov explosion")
321 
322  END SUBROUTINE initdata
323 
324 
325 END PROGRAM ode_test
program ode_test
Definition: ode.f90:38
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
physics module for 1D,2D and 3D non-isothermal Euler equations