gauss2d.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: gauss2d.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 !----------------------------------------------------------------------------!
32 !----------------------------------------------------------------------------!
33 PROGRAM gauss2d
34  USE fosite_mod
35 #include "tap.h"
36  IMPLICIT NONE
37  !--------------------------------------------------------------------------!
38  ! simulation parameter
39  REAL, PARAMETER :: tsim = 0.3 ! simulation time
40  REAL, PARAMETER :: gamma = 1.4 ! ratio of specific heats
41  REAL, PARAMETER :: csiso = &
42  0.0 ! non-isothermal simulation
43 ! 1.127 ! isothermal simulation
44  ! with CSISO as sound speed
45  ! initial condition (dimensionless units)
46  REAL, PARAMETER :: rho0 = 1.0 ! ambient density
47  REAL, PARAMETER :: rho1 = 100.0 ! peak density above RHO0
48  REAL, PARAMETER :: rwidth = 0.06 ! half width of the Gaussian
49  REAL, PARAMETER :: p0 = 1.0 ! ambient pressure
50  REAL, PARAMETER :: p1 = 100.0 ! peak pressure above P0
51  REAL, PARAMETER :: pwidth = 0.06 ! half width of the Gaussian
52  REAL, PARAMETER :: omega0 = 0.0 ! angular velocity
53  REAL, PARAMETER :: eta = 0.0 ! dynamic viscosity (0.0 disables)
54  ! location of the pulse in cylindrical coordinates
55  REAL, PARAMETER :: r0 = 0.0 ! radial position
56  REAL, PARAMETER :: z0 = 0.0 ! vertical position
57  ! mesh settings
58  INTEGER, PARAMETER :: mgeo = cartesian! geometry
59  INTEGER, PARAMETER :: xres = 100 ! x-resolution
60  INTEGER, PARAMETER :: yres = 100 ! y-resolution
61  INTEGER, PARAMETER :: zres = 1 ! z-resolution
62  REAL, PARAMETER :: rmax = 1.0 ! width of square that fits into
63  ! computational domain
64  REAL, PARAMETER :: gpar = 0.8 ! geometry scaling parameter
65  ! output parameters
66  INTEGER, PARAMETER :: onum = 10 ! number of output data sets
67  CHARACTER(LEN=256), PARAMETER & ! output data dir
68  :: odir = './'
69  CHARACTER(LEN=256), PARAMETER & ! output data file name
70  :: ofname = 'gauss2D'
71  !--------------------------------------------------------------------------!
72  CLASS(fosite), ALLOCATABLE :: sim
73  LOGICAL :: ok
74  !--------------------------------------------------------------------------!
75 
76  tap_plan(1)
77 
78  ALLOCATE(sim)
79  CALL sim%InitFosite()
80  CALL makeconfig(sim, sim%config)
81  CALL sim%Setup()
82  CALL initdata(sim%Mesh, sim%Physics, sim%Timedisc)
83 
84  CALL sim%Run()
85  ok = .NOT.sim%aborted
86  CALL sim%Finalize()
87  DEALLOCATE(sim)
88 
89  tap_check(ok,"stoptime reached")
90  tap_done
91 
92 CONTAINS
93 
94  SUBROUTINE makeconfig(Sim, config)
95  USE functions, ONLY : asinh, acosh
96  IMPLICIT NONE
97  !------------------------------------------------------------------------!
98  CLASS(fosite) :: Sim
99  TYPE(Dict_TYP),POINTER :: config
100  !------------------------------------------------------------------------!
101  ! Local variable declaration
102  INTEGER :: bc(6)
103  TYPE(Dict_TYP), POINTER :: mesh, physics, boundary, datafile, sources, &
104  timedisc, fluxes
105  REAL :: x1,x2,y1,y2,z1,z2
106  !------------------------------------------------------------------------!
107  INTENT(INOUT) :: sim
108  !------------------------------------------------------------------------!
109  ! mesh settings and boundary conditions
110  SELECT CASE(mgeo)
111  CASE(cartesian)
112  x1 = -0.5
113  x2 = 0.5
114  y1 = -0.5
115  y2 = 0.5
116  z1 = -0.0
117  z2 = 0.0
118  bc(west) = absorbing
119  bc(east) = absorbing
120  bc(south) = absorbing
121  bc(north) = absorbing
122 ! bc(WEST) = NO_GRADIENTS
123 ! bc(EAST) = NO_GRADIENTS
124 ! bc(SOUTH) = NO_GRADIENTS
125 ! bc(NORTH) = NO_GRADIENTS
126  bc(bottom) = no_gradients
127  bc(top) = no_gradients
128  CASE DEFAULT
129  CALL error(sim%Physics,"InitProgram","geometry not supported for this test")
130  END SELECT
131 
132  !mesh settings
133  mesh => dict( &
134  "meshtype" / midpoint, &
135  "geometry" / mgeo, &
136  "inum" / xres, &
137  "jnum" / yres, &
138  "knum" / zres, &
139  "xmin" / x1, &
140  "xmax" / x2, &
141  "ymin" / y1, &
142  "ymax" / y2, &
143  "zmin" / z1, &
144  "zmax" / z2, &
145  ! "decomposition"/ (/ 1, 2/), &
146  "gparam" / gpar)
147 
148  ! boundary conditions
149  boundary => dict( &
150  "western" / bc(west), &
151  "eastern" / bc(east), &
152  "southern" / bc(south), &
153  "northern" / bc(north), &
154  "bottomer" / bc(bottom), &
155  "topper" / bc(top))
156 
157  ! physics settings
158  IF (csiso.GT.tiny(csiso)) THEN
159  physics => dict("problem" / euler_isotherm, &
160  "cs" / csiso) ! isothermal speed of sound
161  ELSE
162  physics => dict("problem" / euler, &
163  "gamma" / gamma) ! ratio of specific heats
164  END IF
165 
166  ! flux calculation and reconstruction method
167  fluxes => dict( &
168  "order" / linear, &
169  "fluxtype" / kt, &
170 ! "variables" / PRIMITIVE, &
171  "variables" / conservative, &
172  "limiter" / vanleer, &
173  "output/slopes" / 0)
174 
175  NULLIFY(sources)
176 
177  ! time discretization settings
178  timedisc => dict( &
179  "method" / modified_euler, &
180  "order" / 3, &
181  "tol_rel" / 0.01, &
182  "cfl" / 0.4, &
183  "stoptime" / tsim, &
184  "dtlimit" / 1.0e-8, &
185  "maxiter" / 10000000)
186 
187  datafile => dict( &
188  "fileformat" / vtk, &
189  "filename" / (trim(odir) // trim(ofname)), &
190  "count" / onum)
191 
192  config => dict( &
193  "mesh" / mesh, &
194  "physics" / physics, &
195  "boundary" / boundary, &
196  "fluxes" / fluxes, &
197  "datafile" / datafile, &
198  "timedisc" / timedisc)
199 
200  IF (ASSOCIATED(sources)) &
201  CALL setattr(config, "sources", sources)
202 
203  END SUBROUTINE makeconfig
204 
205 
206  SUBROUTINE initdata(Mesh,Physics,Timedisc)
209  IMPLICIT NONE
210  !------------------------------------------------------------------------!
211  CLASS(physics_base) :: Physics
212  CLASS(mesh_base) :: Mesh
213  CLASS(timedisc_base) :: Timedisc
214  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX) &
215  :: radius
216  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,3) &
217  :: posvec
218  !------------------------------------------------------------------------!
219  INTENT(IN) :: mesh,physics
220  INTENT(INOUT) :: timedisc
221  !------------------------------------------------------------------------!
222  IF (abs(r0).LE.tiny(r0).AND.abs(z0).LE.tiny(z0)) THEN
223  ! no shift of point mass set radius and posvec to Mesh defaults
224  radius(:,:,:) = mesh%radius%bcenter(:,:,:)
225  posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:)
226  ELSE
227  ! shifted point mass position:
228  ! compute curvilinear components of shift vector
229  posvec(:,:,:,1) = r0
230  posvec(:,:,:,2) = z0
231  CALL convert2curvilinear(mesh%geometry,mesh%bcenter,posvec,posvec)
232  ! subtract the result from the position vector:
233  ! this gives you the curvilinear components of all vectors pointing
234  ! from the point mass to the bary center of any cell on the mesh
235  posvec(:,:,:,:) = mesh%posvec%bcenter(:,:,:,:) - posvec(:,:,:,:)
236  ! compute its absolute value
237  radius(:,:,:) = sqrt(posvec(:,:,:,1)**2+posvec(:,:,:,2)**2)
238  END IF
239 
240  ! initial condition
241  SELECT TYPE(pvar => timedisc%pvar)
242  TYPE IS(statevector_eulerisotherm) ! isothermal HD
243  ! Gaussian density pulse
244  pvar%density%data3d(:,:,:) = rho0 + rho1*exp(-log(2.0) &
245  * (radius(:,:,:)/rwidth)**2)
246  ! vanishing velocities
247  pvar%velocity%data1d(:) = 0.0
248  TYPE IS(statevector_euler) ! non-isothermal HD
249  ! constant density
250  pvar%density%data1d(:) = rho0
251  ! Gaussian pressure pulse
252  pvar%pressure%data3d(:,:,:) = p0 + p1*exp(-log(2.0) &
253  * (radius(:,:,:)/rwidth)**2)
254  ! vanishing velocities
255  pvar%velocity%data1d(:) = 0.0
256  END SELECT
257 
258  CALL physics%Convert2Conservative(timedisc%pvar,timedisc%cvar)
259 
260  CALL mesh%Info(" DATA-----> initial condition: 2D Gaussian pulse")
261 
262  END SUBROUTINE initdata
263 
264 END PROGRAM gauss2d
Mathematical functions.
Definition: functions.f90:48
subroutine initdata(Mesh, Physics, Fluxes, Timedisc)
Definition: bondi2d.f90:274
main fosite class
Definition: fosite.f90:71
elemental real function, public asinh(x)
inverse hyperbolic sine function
Definition: functions.f90:100
program gauss2d
2D Gaussian pressure or density pulse with and without rotation
Definition: gauss2d.f90:33
subroutine makeconfig(Sim, config)
Definition: bondi2d.f90:165
physics module for 1D,2D and 3D isothermal Euler equations
physics module for 1D,2D and 3D non-isothermal Euler equations
elemental real function, public acosh(x)
inverse hyperbolic cosine function
Definition: functions.f90:110