USER_PROBLEM: Remove unused stuff.

Signed-off-by: Grzegorz Kowal <grzegorz@amuncode.org>
This commit is contained in:
Grzegorz Kowal 2021-11-26 17:15:02 -03:00
parent 3081ac0d5f
commit 82dfcf3c29

View File

@ -31,17 +31,8 @@ module user_problem
implicit none
! default problem parameters
!
real(kind=8), save :: dens = 1.0d+00
real(kind=8), save :: beta = 1.0d+00
real(kind=8), save :: pres = 1.0d+00
real(kind=8), save :: bmag = sqrt(2.0d+00)
private
public :: initialize_user_problem, finalize_user_problem
public :: setup_user_problem
public :: user_boundary_x, user_boundary_y, user_boundary_z
public :: user_statistics
!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
@ -67,11 +58,6 @@ module user_problem
!
subroutine initialize_user_problem(problem, rcount, verbose, status)
use equations , only : eos, csnd, csnd2, adiabatic_index
use helpers , only : print_section, print_parameter
use mesh , only : setup_problem
use parameters, only : get_parameter
implicit none
character(len=64), intent(in) :: problem
@ -83,28 +69,6 @@ module user_problem
!
status = 0
! get parameters
!
call get_parameter("density", dens)
call get_parameter("beta" , beta)
if (eos == "iso") then
pres = csnd2 * dens
else
pres = csnd2 * dens / adiabatic_index
end if
bmag = sqrt(2.0d+00 * pres / beta)
! print information about the user problem setup
!
call print_section(verbose, "Parameters (* - set, otherwise calculated)")
call print_parameter(verbose, '(*) beta (plasma-beta)', beta)
call print_parameter(verbose, '(*) dens' , dens)
call print_parameter(verbose, '( ) pres' , pres)
call print_parameter(verbose, '( ) bmag' , bmag)
call print_parameter(verbose, '(*) csnd' , csnd)
call print_parameter(verbose, '( ) valf' , bmag / sqrt(dens))
!-------------------------------------------------------------------------------
!
end subroutine initialize_user_problem
@ -153,58 +117,13 @@ module user_problem
subroutine setup_user_problem(pdata)
use blocks , only : block_data
use coordinates, only : nn => bcells
use equations , only : prim2cons
use equations , only : nv
use equations , only : idn, ivx, ivy, ivz, ipr, ibx, iby, ibz, ibp
implicit none
type(block_data), pointer, intent(inout) :: pdata
integer :: j, k = 1
real(kind=8), dimension(nv,nn) :: q, u
!-------------------------------------------------------------------------------
!
! set the variables
!
q(idn,:) = dens
if (ipr > 0) q(ipr,:) = pres
q(ivx,:) = 0.0d+00
q(ivy,:) = 0.0d+00
q(ivz,:) = 0.0d+00
if (ibx > 0) then
q(ibx,:) = bmag
q(iby,:) = 0.0d+00
q(ibz,:) = 0.0d+00
q(ibp,:) = 0.0d+00
end if
! convert the primitive variables to conservative ones
!
call prim2cons(q(:,:), u(:,:))
! iterate over all positions in the YZ plane
!
#if NDIMS == 3
do k = 1, nn
#endif /* NDIMS == 3 */
do j = 1, nn
! copy the primitive variables to the current block
!
pdata%q(:,:,j,k) = q(:,:)
! copy the conserved variables to the current block
!
pdata%u(:,:,j,k) = u(:,:)
end do ! j = 1, nn
#if NDIMS == 3
end do ! k = 1, nn
#endif /* NDIMS == 3 */
!-------------------------------------------------------------------------------
!
@ -284,7 +203,7 @@ module user_problem
!
! Arguments:
!
! ic - the block side along the X direction for the ghost zone update;
! is - the block side along the X direction for the ghost zone update;
! jl, ju - the cell index limits for the Y direction;
! kl, ku - the cell index limits for the Z direction;
! t, dt - time and time increment;
@ -293,17 +212,13 @@ module user_problem
!
!===============================================================================
!
subroutine user_boundary_x(ic, jl, ju, kl, ku, t, dt, x, y, z, qn)
subroutine user_boundary_x(is, jl, ju, kl, ku, t, dt, x, y, z, qn)
implicit none
integer , intent(in) :: ic
integer , intent(in) :: jl, ju
integer , intent(in) :: kl, ku
integer , intent(in) :: is, jl, ju, kl, ku
real(kind=8) , intent(in) :: t, dt
real(kind=8), dimension(:) , intent(in) :: x
real(kind=8), dimension(:) , intent(in) :: y
real(kind=8), dimension(:) , intent(in) :: z
real(kind=8), dimension(:) , intent(in) :: x, y, z
real(kind=8), dimension(:,:,:,:), intent(inout) :: qn
!-------------------------------------------------------------------------------
@ -323,7 +238,7 @@ module user_problem
!
! Arguments:
!
! jc - the block side along the Y direction for the ghost zone update;
! js - the block side along the Y direction for the ghost zone update;
! il, iu - the cell index limits for the X direction;
! kl, ku - the cell index limits for the Z direction;
! t, dt - time and time increment;
@ -332,17 +247,13 @@ module user_problem
!
!===============================================================================
!
subroutine user_boundary_y(jc, il, iu, kl, ku, t, dt, x, y, z, qn)
subroutine user_boundary_y(js, il, iu, kl, ku, t, dt, x, y, z, qn)
implicit none
integer , intent(in) :: jc
integer , intent(in) :: il, iu
integer , intent(in) :: kl, ku
integer , intent(in) :: js, il, iu, kl, ku
real(kind=8) , intent(in) :: t, dt
real(kind=8), dimension(:) , intent(in) :: x
real(kind=8), dimension(:) , intent(in) :: y
real(kind=8), dimension(:) , intent(in) :: z
real(kind=8), dimension(:) , intent(in) :: x, y, z
real(kind=8), dimension(:,:,:,:), intent(inout) :: qn
!-------------------------------------------------------------------------------
@ -362,7 +273,7 @@ module user_problem
!
! Arguments:
!
! kc - the block side along the Z direction for the ghost zone update;
! ks - the block side along the Z direction for the ghost zone update;
! il, iu - the cell index limits for the X direction;
! jl, ju - the cell index limits for the Y direction;
! t, dt - time and time increment;
@ -371,17 +282,13 @@ module user_problem
!
!===============================================================================
!
subroutine user_boundary_z(kc, il, iu, jl, ju, t, dt, x, y, z, qn)
subroutine user_boundary_z(ks, il, iu, jl, ju, t, dt, x, y, z, qn)
implicit none
integer , intent(in) :: kc
integer , intent(in) :: il, iu
integer , intent(in) :: jl, ju
integer , intent(in) :: ks, il, iu,jl, ju
real(kind=8) , intent(in) :: t, dt
real(kind=8), dimension(:) , intent(in) :: x
real(kind=8), dimension(:) , intent(in) :: y
real(kind=8), dimension(:) , intent(in) :: z
real(kind=8), dimension(:) , intent(in) :: x, y, z
real(kind=8), dimension(:,:,:,:), intent(inout) :: qn
!-------------------------------------------------------------------------------