bc_set_UpdateExtents Subroutine

private pure subroutine bc_set_UpdateExtents(this, name)

Finds the intersection between block owned by this MPI rank, and the plane defining the region.

Type Bound

bc_set

Arguments

Type IntentOptional Attributes Name
class(bc_set), intent(inout) :: this

Boundary conditions utility

character(len=*), intent(in) :: name

Region name


Calls

proc~~bc_set_updateextents~~CallsGraph proc~bc_set_updateextents bc_set%bc_set_UpdateExtents proc~bc_set_getregionindex bc_set%bc_set_GetRegionIndex proc~bc_set_updateextents->proc~bc_set_getregionindex none~get~3 hashtbl_obj%Get proc~bc_set_getregionindex->none~get~3 proc~hashtbl_obj_hashstring hashtbl_obj%hashtbl_obj_HashString proc~bc_set_getregionindex->proc~hashtbl_obj_hashstring proc~hashtbl_obj_get_int4 hashtbl_obj%hashtbl_obj_Get_int4 none~get~3->proc~hashtbl_obj_get_int4 proc~hashtbl_obj_get_int8 hashtbl_obj%hashtbl_obj_Get_int8 none~get~3->proc~hashtbl_obj_get_int8 proc~hashtbl_obj_get_real_dp hashtbl_obj%hashtbl_obj_Get_real_dp none~get~3->proc~hashtbl_obj_get_real_dp proc~hashtbl_obj_get_real_sp hashtbl_obj%hashtbl_obj_Get_real_sp none~get~3->proc~hashtbl_obj_get_real_sp none~get~2 sllist_obj%Get proc~hashtbl_obj_get_int4->none~get~2 proc~hashtbl_obj_get_int8->none~get~2 proc~hashtbl_obj_get_real_dp->none~get~2 proc~hashtbl_obj_get_real_sp->none~get~2 proc~sllist_obj_get_int4 sllist_obj%sllist_obj_Get_int4 none~get~2->proc~sllist_obj_get_int4 proc~sllist_obj_get_int8 sllist_obj%sllist_obj_Get_int8 none~get~2->proc~sllist_obj_get_int8 proc~sllist_obj_get_real_dp sllist_obj%sllist_obj_Get_real_dp none~get~2->proc~sllist_obj_get_real_dp proc~sllist_obj_get_real_sp sllist_obj%sllist_obj_Get_real_sp none~get~2->proc~sllist_obj_get_real_sp proc~sllist_obj_get_int4->proc~sllist_obj_get_int4 proc~sllist_obj_get_int8->proc~sllist_obj_get_int8 proc~sllist_obj_get_real_dp->proc~sllist_obj_get_real_dp proc~sllist_obj_get_real_sp->proc~sllist_obj_get_real_sp

Called by

proc~~bc_set_updateextents~~CalledByGraph proc~bc_set_updateextents bc_set%bc_set_UpdateExtents proc~bc_set_add bc_set%bc_set_Add proc~bc_set_add->proc~bc_set_updateextents proc~bc_set_read bc_set%bc_set_Read proc~bc_set_read->proc~bc_set_add

Source Code

    pure subroutine bc_set_UpdateExtents(this,name)
      !> Finds the intersection between block owned by this MPI rank, and the
      ! plane defining the region.
      class(bc_set),    intent(inout) :: this                                  !! Boundary conditions utility
      character(len=*), intent(in)    :: name                                  !! Region name
      ! Work variable
      integer :: ind
      logical :: overlap
      real(wp):: xlo(3),xhi(3)
      integer :: i,j,k
      real(wp):: normal(3)
      real(wp):: ds

      ! Get index of region
      ind = this%GetRegionIndex(name)

      ! Initialize indices
      this%region(ind)%lo =  floor(huge(1)/100.0_wp)
      this%region(ind)%hi = -floor(huge(1)/100.0_wp)

      associate (lo => this%block%lo, hi => this%block%hi,    &
        x => this%block%x, y => this%block%y, z=>this%block%z )

        xlo  = this%region(ind)%xlo
        xhi  = this%region(ind)%xhi

        ds   = 0.5_wp*minval(this%block%dx)

        normal = 0.0_wp
        select case (this%region(ind)%side)
        case (BC_LEFT)
          normal(this%region(ind)%dir) =  1.0_wp
          xhi = xhi + ds*normal
        case (BC_RIGHT)
          normal(this%region(ind)%dir) = -1.0_wp
          xlo = xlo + ds*normal
        end select


        do k=lo(3),hi(3)
          do j=lo(2),hi(2)
            do i=lo(1),hi(1)
              overlap = .true.
              if ( x(i) .ge. xhi(1) .or. xlo(1) .ge. x(i+1) ) overlap=.false.
              if ( y(j) .ge. xhi(2) .or. xlo(2) .ge. y(j+1) ) overlap=.false.
              if ( z(k) .ge. xhi(3) .or. xlo(3) .ge. z(k+1) ) overlap=.false.
              if (overlap) then
                this%region(ind)%lo(1) = min(this%region(ind)%lo(1),i)
                this%region(ind)%hi(1) = max(this%region(ind)%hi(1),i)

                this%region(ind)%lo(2) = min(this%region(ind)%lo(2),j)
                this%region(ind)%hi(2) = max(this%region(ind)%hi(2),j)

                this%region(ind)%lo(3) = min(this%region(ind)%lo(3),k)
                this%region(ind)%hi(3) = max(this%region(ind)%hi(3),k)
              end if
          end do
          end do
        end do
      end associate

      return
    end subroutine bc_set_UpdateExtents