lagrangian_obj_Extrapolate Subroutine

private subroutine lagrangian_obj_Extrapolate(this, l_filter, slo, shi, block, int_g1ex, bump)

Gets a bump function centered on the lagrangian object.

Type Bound

lagrangian_obj

Arguments

Type IntentOptional Attributes Name
class(lagrangian_obj), intent(in) :: this

A Lagrangian object

real(kind=wp), intent(in) :: l_filter

Filter size

integer, intent(in) :: slo(3)

Stencil lower bound

integer, intent(in) :: shi(3)

Stencil higher bound

type(block_obj), intent(in), pointer :: block

A block object

procedure(kernel_1D), intent(in), pointer :: int_g1ex

Integrated filter kernel

real(kind=wp), intent(out), allocatable :: bump(:,:,:)

The bump function


Source Code

    subroutine lagrangian_obj_Extrapolate(this,l_filter,slo,shi,block,int_g1ex,bump)
      !> Gets a bump function centered on the lagrangian object.
      implicit none
      class(lagrangian_obj), intent(in) :: this                                !! A Lagrangian object
      real(wp),              intent(in) :: l_filter                            !! Filter size
      integer,               intent(in) :: slo(3)                              !! Stencil lower bound
      integer,               intent(in) :: shi(3)                              !! Stencil higher bound
      type(block_obj),       intent(in), &
                               pointer  :: block                               !! A block object
      procedure(kernel_1D),  intent(in), &
                               pointer  :: int_g1ex                            !! Integrated filter kernel
      real(wp),              intent(out),&
                            allocatable :: bump(:,:,:)                         !! The bump function
      ! Work variables
      integer  :: i,j,k
      real(wp) :: x_r,x_l
      real(wp) :: y_r,y_l
      real(wp) :: z_r,z_l
      real(wp) :: dVol

      if (allocated(bump)) deallocate(bump)
      allocate( bump(slo(1):shi(1),slo(2):shi(2),slo(3):shi(3)))

      bump=0.0_wp
      do k=slo(3),shi(3)
        do j=slo(2),shi(2)
          do i=slo(1),shi(1)
            ! Cell volume
            dVol = (block%x(i+1)-block%x(i))*(block%y(j+1)-block%y(j))*(block%z(k+1)-block%z(k))

            ! Centered and non-dimensionalized cooridnates
            x_r = (block%x(i+1)-this%p(1))/l_filter
            x_l = (block%x(i  )-this%p(1))/l_filter
            y_r = (block%y(j+1)-this%p(2))/l_filter
            y_l = (block%y(j  )-this%p(2))/l_filter
            z_r = (block%z(k+1)-this%p(3))/l_filter
            z_l = (block%z(k  )-this%p(3))/l_filter

            bump(i,j,k) = (int_g1ex(x_r)-int_g1ex(x_l)) &
                         *(int_g1ex(y_r)-int_g1ex(y_l)) &
                         *(int_g1ex(z_r)-int_g1ex(z_l))/dVol
          end do
        end do
      end do

      return
    end subroutine lagrangian_obj_Extrapolate