riemann3d.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: riemann3d.f90 #
5 !# #
6 !# Copyright (C) 2006-2018 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# #
9 !# This program is free software; you can redistribute it and/or modify #
10 !# it under the terms of the GNU General Public License as published by #
11 !# the Free Software Foundation; either version 2 of the License, or (at #
12 !# your option) any later version. #
13 !# #
14 !# This program is distributed in the hope that it will be useful, but #
15 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
16 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
17 !# NON INFRINGEMENT. See the GNU General Public License for more #
18 !# details. #
19 !# #
20 !# You should have received a copy of the GNU General Public License #
21 !# along with this program; if not, write to the Free Software #
22 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
23 !# #
24 !#############################################################################
25 
26 !----------------------------------------------------------------------------!
34 !----------------------------------------------------------------------------!
35 PROGRAM riemann3d
36  USE fosite_mod
37 #include "tap.h"
38  IMPLICIT NONE
39  !--------------------------------------------------------------------------!
40  ! simulation parameters
41  REAL, PARAMETER :: tsim = 0.7 ! simulation time
42  REAL, PARAMETER :: gamma = 1.4 ! ratio of specific heats
43  ! mesh settings
44  INTEGER, PARAMETER :: mgeo = cylindrical ! geometry
45  INTEGER, PARAMETER :: xres = 150 ! x-resolution
46  INTEGER, PARAMETER :: yres = 1 ! y-resolution
47  INTEGER, PARAMETER :: zres = 100 ! y-resolution
48  ! output parameters
49  INTEGER, PARAMETER :: onum = 7 ! number of output data sets
50  CHARACTER(LEN=256), PARAMETER & ! output data dir
51  :: odir = './'
52  CHARACTER(LEN=256), PARAMETER & ! output data file name
53  :: ofname = 'riemann3d'
54  !--------------------------------------------------------------------------!
55  CLASS(fosite), ALLOCATABLE :: sim
56  LOGICAL :: ok
57  !--------------------------------------------------------------------------!
58 
59  tap_plan(1)
60 
61  ALLOCATE(sim)
62  CALL sim%InitFosite()
63  CALL makeconfig(sim, sim%config)
64  CALL sim%Setup()
65  CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
66 
67  CALL sim%Run()
68  ok = .NOT.sim%aborted
69  CALL sim%Finalize()
70  DEALLOCATE(sim)
71 
72  tap_check(ok,"stoptime reached")
73  tap_done
74 
75 CONTAINS
76 
77  SUBROUTINE makeconfig(Sim, config)
78  IMPLICIT NONE
79  !------------------------------------------------------------------------!
80  CLASS(fosite) :: Sim
81  TYPE(Dict_TYP),POINTER :: config
82  !------------------------------------------------------------------------!
83  ! Local variable declaration
84  REAL :: z0,z1,r0,r1
85  TYPE(Dict_TYP), POINTER :: mesh, physics, boundary, datafile, logfile, &
86  timedisc, fluxes
87  REAL :: x1,x2,y1,y2
88  !------------------------------------------------------------------------!
89  INTENT(INOUT) :: sim
90  !------------------------------------------------------------------------!
91 
92  ! mesh settings
93  mesh => dict("meshtype" / midpoint, &
94  "geometry" / cylindrical, &
95  "inum" / xres, &
96  "jnum" / yres, &
97  "knum" / zres, &
98  "xmin" / 0.0, &
99  "xmax" / 1.5, &
100  "ymin" / (-pi), &
101  "ymax" / pi, &
102  "zmin" / 0.0, &
103  "zmax" / 1.0, &
104  "gparam" / 1.0)
105 
106  ! physics settings
107  physics => dict("problem" / euler, &
108  "gamma" / 1.4, & ! ratio of specific heats !
109  "mu" / 0.029) ! mean molecular weight !
110 
111  ! flux calculation and reconstruction method
112  fluxes => dict("order" / linear, &
113  "fluxtype" / kt, &
114  "variables" / conservative, & ! vars. to use for reconstruction!
115  "limiter" / monocent, & ! one of: minmod, monocent,... !
116  "theta" / 1.2) ! optional parameter for limiter !
117 
118  ! boundary conditions
119  boundary => dict(&
120  "western" / axis, &
121  "eastern" / reflecting, &
122  "southern" / periodic, &
123  "northern" / periodic, &
124  "bottomer" / reflecting, &
125  "topper" / reflecting)
126 
127  ! time discretization settings
128  timedisc => dict("method" / modified_euler, &
129  "order" / 3, &
130  "cfl" / 0.4, &
131  "stoptime" / tsim, &
132  "dtlimit" / 1.0e-9, &
133  "maxiter" / 1000000)
134 
135  ! initialize data input/output
136  datafile => dict( &
137  "fileformat" / vtk, &
138  "filename" / (trim(odir) // trim(ofname)), &
139  "count" / onum)
140 
141 
142  config => dict("mesh" / mesh, &
143  "physics" / physics, &
144  "boundary" / boundary, &
145  "fluxes" / fluxes, &
146  "timedisc" / timedisc, &
147 ! "logfile" / logfile, &
148  "datafile" / datafile)
149  END SUBROUTINE makeconfig
150 
151 
152  SUBROUTINE initdata(Mesh,Physics,Timedisc)
154  IMPLICIT NONE
155  !------------------------------------------------------------------------!
156  CLASS(physics_base) :: Physics
157  CLASS(mesh_base) :: Mesh
158  CLASS(timedisc_base) :: Timedisc
159  !------------------------------------------------------------------------!
160  ! Local variable declaration
161  REAL :: rmax,x0,y0,z0
162  REAL :: P_in, P_out
163  !------------------------------------------------------------------------!
164  INTENT(IN) :: mesh,physics
165  INTENT(INOUT) :: timedisc
166  !------------------------------------------------------------------------!
167  ! radius and cartesian position of the bubble
168  rmax = 0.2
169  x0 = 0.0
170  y0 = 0.0
171  z0 = 0.4
172 
173  ! inside and ambient pressure
174  p_in = 5.0
175  p_out = 1.0
176 
177  ! initial condition
178  SELECT TYPE(pvar => timedisc%pvar)
179  TYPE IS(statevector_euler) ! non-isothermal HD
180  ! constant density
181  pvar%density%data1d(:) = 1.0
182  ! vanishing velocities
183  pvar%velocity%data1d(:) = 0.0
184  ! pressure pulse
185  WHERE (((mesh%bccart(:,:,:,1)-x0)**2+(mesh%bccart(:,:,:,2)-y0)**2 &
186  +(mesh%bccart(:,:,:,3)-z0)**2).LT.rmax**2)
187  pvar%pressure%data3d(:,:,:) = p_in
188  ELSEWHERE
189  pvar%pressure%data3d(:,:,:) = p_out
190  END WHERE
191  CLASS DEFAULT
192  CALL physics%Error("riemann3d::InitData","physics not supported")
193  END SELECT
194 
195  CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
196 
197  CALL physics%Info(" DATA-----> initial condition: Spherical pressure discontinuity between walls")
198  END SUBROUTINE initdata
199 
200 END PROGRAM riemann3d
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
Definition: bondi2d.f90:274
main fosite class
Definition: fosite.f90:71
base class for geometrical properties
subroutine makeconfig(Sim, config)
Definition: bondi2d.f90:165
program riemann3d
Definition: riemann3d.f90:35