|
qinit.f90.html |
|
|
Source file: qinit.f90
|
|
Directory: /Users/rjl/clawpack_src/clawpack_master/geoclaw/examples/tsunami/bowl-slosh
|
|
Converted: Fri Aug 23 2024 at 11:39:34
using clawcode2html
|
|
This documentation file will
not reflect any later changes in the source file.
|
! qinit routine for parabolic bowl problem, only single layer
subroutine qinit(meqn,mbc,mx,my,xlower,ylower,dx,dy,q,maux,aux)
use geoclaw_module, only: grav
implicit none
! Subroutine arguments
integer, intent(in) :: meqn,mbc,mx,my,maux
real(kind=8), intent(in) :: xlower,ylower,dx,dy
real(kind=8), intent(inout) :: q(meqn,1-mbc:mx+mbc,1-mbc:my+mbc)
real(kind=8), intent(inout) :: aux(maux,1-mbc:mx+mbc,1-mbc:my+mbc)
! Parameters for problem
real(kind=8), parameter :: a = 1.d0
real(kind=8), parameter :: sigma = 0.5d0
real(kind=8), parameter :: h0 = 0.1d0
! Other storage
integer :: i,j
real(kind=8) :: omega,x,y,eta
omega = sqrt(2.d0 * grav * h0) / a
do i=1-mbc,mx+mbc
x = xlower + (i - 0.5d0)*dx
do j=1-mbc,my+mbc
y = ylower + (j - 0.5d0) * dy
eta = sigma * h0 / a**2 * (2.d0 * x - sigma)
q(1,i,j) = max(0.d0,eta - aux(1,i,j))
q(2,i,j) = 0.d0
q(3,i,j) = sigma * omega * q(1,i,j)
enddo
enddo
end subroutine qinit