You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
CACmb/src/box.f90

48 lines
1.4 KiB

module box
!This module contains information on the properties of the current box.
use parameters
implicit none
real(kind=dp) :: box_bd(6) !Global box boundaries
!The subbox variables contain values for each subbox, being the boxes read in through some
!command. Currently only mode_merge will require sub_boxes, for mode_create it will always
!allocate to only 1 sub_box
integer :: sub_box_num = 0
real(kind=dp), allocatable :: sub_box_ori(:,:,:)
real(kind=dp), allocatable :: sub_box_bd(:,:)
public
contains
subroutine box_init
!Initialize some box functions
box_bd(:) = 0.0_dp
end subroutine box_init
subroutine alloc_sub_box(n)
!Allocate the sub_box variables
integer, intent(in) :: n
sub_box_num = n
allocate(sub_box_ori(3,3,n), sub_box_bd(6,n))
end subroutine alloc_sub_box
subroutine grow_box(temp_box_bd)
!This function takes in a temporary box boundary and adjusts the overall box boundaries
!to include it
real(kind=dp), dimension(6), intent(in) :: temp_box_bd
integer :: i
do i = 1, 3
if(temp_box_bd(2*i-1) < box_bd(2*i-1)) box_bd(2*i-1) = temp_box_bd(2*i-1)
if(temp_box_bd(2*i) > box_bd(2*i)) box_bd(2*i) = temp_box_bd(2*i)
end do
return
end subroutine grow_box
end module box