38 use,
INTRINSIC :: iso_fortran_env, only : stdin=>input_unit, &
39 stdout=>output_unit, &
48 REAL,
PARAMETER ::
pi = 3.1415926535897932384626433832795028842
51 LOGICAL :: initialized = .false.
60 REAL :: alpha = 0.8511
64 REAL,
ALLOCATABLE,
DIMENSION(:) :: plist
84 FUNCTION createsedov(ndim,gamma,omega,rho0,E0,p0)
RESULT(this)
88 INTEGER,
OPTIONAL,
INTENT(IN) :: ndim
89 REAL,
OPTIONAL,
INTENT(IN) :: gamma,
omega,rho0,e0,p0
92 IF (
PRESENT(ndim))
THEN
93 IF (ndim.LT.1.AND.ndim.GT.3) &
94 CALL this%Abort(
"CreateSedov: ndim must be one of {1,2,3}")
97 IF (
PRESENT(gamma))
THEN
98 IF (gamma.LE.1.0.OR.gamma.GT.5./3.) &
99 CALL this%Abort(
"CreateSedov: gamma not in ( 1 , 5/3 )")
102 IF (
PRESENT(
omega))
THEN
104 CALL this%Abort(
"CreateSedov: omega not in [ 0 , ndim )")
107 IF (this%omega.GT.0.0) this%eps = 1.0e-10
109 IF (
PRESENT(rho0))
THEN
110 IF (rho0.LE.tiny(rho0).OR.rho0.GT.huge(rho0)) &
111 CALL this%Abort(
"CreateSedov: rho0 not in ( 0 , huge )")
114 IF (
PRESENT(e0))
THEN
115 IF (e0.LE.tiny(e0).OR.e0.GT.huge(e0)) &
116 CALL this%Abort(
"CreateSedov: E0 not in ( 0 , huge )")
119 IF (
PRESENT(p0))
THEN
120 IF (p0.LE.tiny(p0).OR.p0.GT.huge(p0)) &
121 CALL this%Abort(
"CreateSedov: p0 not in ( 0 , huge )")
124 CALL this%InitParams()
125 this%initialized = .true.
137 REAL :: gam,gam_p1,gam_m1,j,w,w2,w3,J1,J2
140 REAL :: V,dV,x1,x2,x3,x4,f,g,h,lambda,dlambda
145 gam_p1 = gam + 1.0d+00
146 gam_m1 = gam - 1.0d+00
149 w2 = (2*gam_m1 + j)/gam
151 this%Vmin = 2./(j+2-w)/gam
152 this%Vmax = 4./(j+2-w)/gam_p1
154 IF (
ALLOCATED(this%plist))
DEALLOCATE(this%plist)
155 ALLOCATE(this%plist(19),stat=err)
156 IF (err.NE.0)
CALL this%Abort(
"InitParams: memory allocation failed")
159 this%plist(2) = 2.0/(j+2.0-w)
160 this%plist(4) = gam_m1/(gam*(w-w2))
161 this%plist(3) = (j+2.0-w)*gam/(2.0+j*gam_m1) &
162 *(2*(j*(2.0-gam)-w)/(gam*(j+2.0-w)**2)-this%plist(4))
163 this%plist(5) = (j-w)/(gam*(w2-w))
164 this%plist(6) = (j+2-w)*(j-w)/(w3-w)*this%plist(3)
165 this%plist(7) = (w*gam_p1-2*j)/(w3-w)
166 this%plist(8) = 0.25*(j+2-w)*gam_p1
167 this%plist(9) = gam_p1/gam_m1
168 this%plist(10) = 0.5*gam*(j+2.0-w)
169 this%plist(12) = 0.5*(2+j*gam_m1)
170 this%plist(11) = 1.0 &
171 /(1.0-this%plist(12)/this%plist(8))
172 this%plist(13) = this%plist(9)*this%plist(10)
173 this%plist(14) = -this%plist(11)*this%plist(12)
174 this%plist(15) = -this%plist(9)*this%plist(10) &
182 this%Vmin = this%Vmin + 2*epsilon(this%Vmin)
184 CALL this%ComputeEnergyIntegral(j1,j2)
186 print
'(A)',
"# " // repeat(
"=",77)
187 print
'(A)',
"# Parameter:"
188 print
'(A)',
"# gamma omega dim alpha J1 J2"
189 print
'(A,6(F11.4))',
"# ",this%gamma,this%omega,real(this%ndim),this%alpha,j1,j2
190 print
'(A)',
"# " // repeat(
"-",77)
191 print
'(A,10(F10.4))',
"# p1-p7 ",this%plist(1:7)
192 print
'(A,10(F10.4))',
"# p8-p13 ",this%plist(8:13)
193 print
'(A,10(F10.4))',
"# p14-p19",this%plist(14:19)
194 print
'(A)',
"# " // repeat(
"=",77)
196 dv = (this%Vmax-this%Vmin)/inum
197 print
'(A)',
"# lambda V f g h dJ1/dlam dJ2/dlam"
201 x4 = this%plist(9)*(1.0-this%plist(10)*v/this%plist(1))
203 g =
func_g(x1,x2,x3,x4,this%plist)
204 h =
func_h(x1,x2,x3,x4,this%plist)
205 print
'(A,7(F11.4))',
'# ',lambda,v,f,g,h,
func_j1(v,this%plist),
func_j2(v,this%plist)
217 REAL,
OPTIONAL,
INTENT(OUT) :: J1,J2
222 IF (this%ndim.EQ.1)
THEN
224 this%alpha = 0.5*(j1+1./(this%gamma-1.0)*j2)
226 this%alpha = (this%ndim-1)*
pi*(j1+2./(this%gamma-1.0)*j2)
236 REAL,
INTENT(IN) :: t,r
237 REAL,
INTENT(OUT) :: rho,v,p
240 REAL :: Rshock,Vshock,Vstar,rho2,v2,p2,x1,x2,x3,x4,lambda,dlambda
241 REAL :: lnx,lnlambda,lnx1,lnx2,lnx3,lnx4
244 rshock = this%ShockPosition(t)
245 IF (r.GT.0.0.AND.r.LT.rshock)
THEN
247 lnx = -(log(this%plist(9)) + (log(r/rshock) + this%plist(2) &
248 *log(this%plist(8)/this%plist(10)) + this%plist(3) &
249 *log(this%plist(11)*(1.0-this%plist(12)/this%plist(10))))/this%plist(4))
250 vstar = (1.0+exp(lnx)) / this%plist(10)
251 IF (lnx.LT.log(8*epsilon(lnx)))
THEN
255 vshock = this%plist(2) * rshock / t
256 rho2 = this%plist(9) * this%rho0
257 v2 = 2./(this%gamma+1.0) * vshock
258 p2 = this%rho0 * v2 * vshock
259 lnlambda = log(r/rshock)
260 lnx1 = log(this%plist(8)*this%Vmin)
261 lnx2 = log(this%plist(9)) + lnx
262 lnx3 = log(this%plist(11)*(1.0-this%plist(12)/this%plist(10)))
263 lnx4 = log(this%plist(9)*(1.-this%plist(10)*this%Vmin/this%gamma))
264 rho = rho2 * exp(
func_lng(lnx1,lnx2,lnx3,lnx4,this%plist))
265 v = v2 * exp(lnx1+lnlambda)
266 p = p2 * exp(
func_lnh(lnx1,lnx2,lnx3,lnx4,this%plist))
269 this%plist(18) = rshock
275 CALL funcd_lambda(vstar,this%plist,x1,x2,x3,lambda,dlambda)
276 x4 = this%plist(9)*(1.0-this%plist(10)*vstar/this%gamma)
277 vshock = this%plist(2) * rshock / t
278 rho2 = this%plist(9) * this%rho0
279 v2 = 2./(this%gamma+1.0) * vshock
280 p2 = this%rho0 * v2 * vshock
281 rho = rho2 *
func_g(x1,x2,x3,x4,this%plist)
283 p = p2 *
func_h(x1,x2,x3,x4,this%plist)
287 rho = this%rho0/r**this%omega
297 REAL,
INTENT(IN) :: time
300 IF (.NOT.this%initialized)
CALL this%Abort(
"sedov uninitialzed, aborting ...")
301 rshock = (this%E0/this%rho0*time*time/this%alpha)**(0.5*this%plist(2))
310 WRITE (stdout,
"(A)")
"# ==========================================="
311 WRITE (stdout,
"(A)")
"# << Solution of Sedov explosion problem >> "
312 WRITE (stdout,
"(A)")
"# ==========================================="
313 WRITE (stdout,
"(A,I3)")
"# Geometry / Dimensions ", this%ndim
314 WRITE (stdout,
"(A,F10.6)")
"# Ratio of specific heat cap. ", this%gamma
315 WRITE (stdout,
"(A,ES10.2)")
"# Initial energy input ", this%E0
316 WRITE (stdout,
"(A,ES10.2)")
"# Ambient density ", this%rho0
317 WRITE (stdout,
"(A,ES10.2)")
"# Peak density ", this%rho0*this%plist(9)
318 WRITE (stdout,
"(A,F10.6)")
"# Density power law exponent ", this%omega
319 WRITE (stdout,
"(A,F10.6)")
"# Shock position parameter ", this%alpha
327 CHARACTER(LEN=*) :: msg
329 WRITE (stderr,
'(A)')
"ERROR in " // trim(msg)
338 DEALLOCATE(this%plist)
339 this%initialized = .false.
342 PURE SUBROUTINE funcd(y,fy,dfy,plist)
345 REAL,
INTENT(IN) :: y
346 REAL,
INTENT(OUT) :: fy,dfy
347 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
349 REAL :: x1,x2,x3,lambda,dlambda
352 fy = plist(18)*lambda - plist(19)
353 dfy = plist(18)*dlambda
356 PURE SUBROUTINE func(y,fy,plist)
359 REAL,
INTENT(IN) :: y
360 REAL,
INTENT(OUT) :: fy
361 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
363 REAL :: x1,x2,x3,lambda,dlambda
366 fy = plist(18)*lambda - plist(19)
372 REAL,
INTENT(IN) :: x
373 REAL,
INTENT(INOUT),
DIMENSION(:),
OPTIONAL :: plist
376 REAL :: x1,x2,x3,x4,lambda,dlambda,g
379 x4 = plist(9)*(1.0-plist(10)*x/plist(1))
380 g =
func_g(x1,x2,x3,x4,plist)
381 fx = plist(9) * lambda**(plist(16)+1.0) * g * x**2 * dlambda
387 REAL,
INTENT(IN) :: x
388 REAL,
INTENT(INOUT),
DIMENSION(:),
OPTIONAL :: plist
391 REAL :: x1,x2,x3,x4,lambda,dlambda,h
394 x4 = plist(9)*(1.0-plist(10)*x/plist(1))
395 h =
func_h(x1,x2,x3,x4,plist)
398 fx = 0.5*(plist(1)+1.0)/plist(8)**2 * lambda**(plist(16)-1.0) * h * dlambda
404 REAL,
INTENT(IN) :: v
405 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
406 REAL,
INTENT(OUT) :: x1,x2,x3,lambda,dlambda
409 x2 = plist(9)*max(0.0,plist(10)*v-1.0)
410 x3 = plist(11)*(1.0-plist(12)*v)
411 lambda = x1**(-plist(2)) * x2**(-plist(4)) * x3**(-plist(3))
413 dlambda = -plist(2)*plist(8) * x1**(-plist(2)-1.0) * x2**(-plist(4)) * x3**(-plist(3)) &
414 -plist(4)*plist(13) * x1**(-plist(2)) * x2**(-plist(4)-1.0) * x3**(-plist(3)) &
415 -plist(3)*plist(14) * x1**(-plist(2)) * x2**(-plist(4)) * x3**(-plist(3)-1.0)
418 PURE FUNCTION func_g(x1,x2,x3,x4,plist)
RESULT(g)
421 REAL,
INTENT(IN) :: x1,x2,x3,x4
422 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
425 g = x1**(plist(2)*plist(17)) * x2**(plist(5)+plist(4)*plist(17)) &
426 *x3**(plist(6)+plist(3)*plist(17)) * x4**plist(7)
429 PURE FUNCTION func_lng(lnx1,lnx2,lnx3,lnx4,plist)
RESULT(lng)
432 REAL,
INTENT(IN) :: lnx1,lnx2,lnx3,lnx4
433 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
436 lng = (plist(2)*plist(17))*lnx1 + (plist(5)+plist(4)*plist(17))*lnx2 &
437 + (plist(6)+plist(3)*plist(17))*lnx3 + plist(7)*lnx4
440 PURE FUNCTION func_h(x1,x2,x3,x4,plist)
RESULT(h)
443 REAL,
INTENT(IN) :: x1,x2,x3,x4
444 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
447 h = x1**(plist(2)*plist(16)) * x3**(plist(6)+plist(3)*(plist(17)-2.0)) &
451 PURE FUNCTION func_lnh(lnx1,lnx2,lnx3,lnx4,plist)
RESULT(lnh)
454 REAL,
INTENT(IN) :: lnx1,lnx2,lnx3,lnx4
455 REAL,
INTENT(IN),
DIMENSION(:),
OPTIONAL :: plist
458 lnh = (plist(2)*plist(16))*lnx1 + (plist(6)+plist(3)*(plist(17)-2.0))*lnx3 &
459 + (1.0+plist(7))*lnx4
pure subroutine funcd(y, fy, dfy, plist)
real function, public integrate(fkt, xl, xr, eps, plist, method)
Numerical integration function.
subroutine, public getroot_newton(funcd, x1, x2, root, error, plist, xm, iterations)
module providing sedov class with basic init and solve subroutines
subroutine initparams(this)
sets constants according to Kamm & Timmes "On Efficient Generation of Numerically Robust Sedov Soluti...
pure real function func_h(x1, x2, x3, x4, plist)
pure real function func_lng(lnx1, lnx2, lnx3, lnx4, plist)
subroutine abort(this, msg)
real function shockposition(this, time)
real function func_j1(x, plist)
pure real function func_lnh(lnx1, lnx2, lnx3, lnx4, plist)
subroutine printconfiguration(this)
prints configuration on the screen (stdout)
pure real function func_g(x1, x2, x3, x4, plist)
subroutine computesolution(this, t, r, rho, v, p)
compute the energy integral and set parameter alpha
type(sedov_typ) function createsedov(ndim, gamma, omega, rho0, E0, p0)
constructor for sedov class
subroutine computeenergyintegral(this, J1, J2)
compute the energy integral and set parameter alpha
pure subroutine funcd_lambda(V, plist, x1, x2, x3, lambda, dlambda)
real function func_j2(x, plist)
pure subroutine func(x, fx, plist)
pure real function, dimension(size(ephir%data2d, dim=1)) omega(ephir, velocity)