op_obj_StrainRate Function

private impure function op_obj_StrainRate(this, U, V, W) result(S)

Computes the strain rate tensor from the velocity field. Result is on mid points (staggering=0). Tensor is stored as follows: S = 0.5*( grad(u) + grad(u)^T ) ( S(1) S(4) S(6) ) = ( S(4) S(2) S(5) ) ( S(6) S(5) S(3) )

Type Bound

op_obj

Arguments

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

Differential operators utility

type(eulerian_obj_r), intent(in) :: U

Fluid velocity field in 1-dir

type(eulerian_obj_r), intent(in) :: V

Fluid velocity field in 2-dir

type(eulerian_obj_r), intent(in) :: W

Fluid velocity field in 3-dir

Return Value type(eulerian_obj_r), (6)

Result


Calls

proc~~op_obj_strainrate~~CallsGraph proc~op_obj_strainrate op_obj%op_obj_StrainRate proc~eulerian_obj_init eulerian_obj_base%eulerian_obj_Init proc~op_obj_strainrate->proc~eulerian_obj_init proc~eulerian_obj_updateghostcells eulerian_obj_base%eulerian_obj_UpdateGhostCells proc~op_obj_strainrate->proc~eulerian_obj_updateghostcells proc~eulerian_obj_updateghostcells_x eulerian_obj_base%eulerian_obj_UpdateGhostCells_x proc~eulerian_obj_updateghostcells->proc~eulerian_obj_updateghostcells_x proc~eulerian_obj_updateghostcells_y eulerian_obj_base%eulerian_obj_UpdateGhostCells_y proc~eulerian_obj_updateghostcells->proc~eulerian_obj_updateghostcells_y proc~eulerian_obj_updateghostcells_z eulerian_obj_base%eulerian_obj_UpdateGhostCells_z proc~eulerian_obj_updateghostcells->proc~eulerian_obj_updateghostcells_z cell cell proc~eulerian_obj_updateghostcells_x->cell mpi_irecv mpi_irecv proc~eulerian_obj_updateghostcells_x->mpi_irecv mpi_isend mpi_isend proc~eulerian_obj_updateghostcells_x->mpi_isend mpi_waitall mpi_waitall proc~eulerian_obj_updateghostcells_x->mpi_waitall proc~eulerian_obj_updateghostcells_y->cell proc~eulerian_obj_updateghostcells_y->mpi_irecv proc~eulerian_obj_updateghostcells_y->mpi_isend proc~eulerian_obj_updateghostcells_y->mpi_waitall proc~eulerian_obj_updateghostcells_z->cell proc~eulerian_obj_updateghostcells_z->mpi_irecv proc~eulerian_obj_updateghostcells_z->mpi_isend proc~eulerian_obj_updateghostcells_z->mpi_waitall

Called by

proc~~op_obj_strainrate~~CalledByGraph proc~op_obj_strainrate op_obj%op_obj_StrainRate proc~respart_set_getsurfacestresses ResPart_set%ResPart_set_GetSurfaceStresses proc~respart_set_getsurfacestresses->proc~op_obj_strainrate proc~respart_set_gethydroforces ResPart_set%ResPart_set_GetHydroForces proc~respart_set_gethydroforces->proc~respart_set_getsurfacestresses proc~cdifs_obj_advancesolutionrp cdifs_obj_AdvanceSolutionRP proc~cdifs_obj_advancesolutionrp->proc~respart_set_gethydroforces proc~cdifs_obj_advancesolution cdifs_obj_AdvanceSolution proc~cdifs_obj_advancesolution->proc~cdifs_obj_advancesolutionrp interface~cdifs_obj_advancesolution cdifs_obj%cdifs_obj_AdvanceSolution interface~cdifs_obj_advancesolution->proc~cdifs_obj_advancesolution

Source Code

    impure function op_obj_StrainRate(this,U,V,W) result(S)
      !> Computes the strain rate tensor from the velocity field.
      ! Result is on mid points (staggering=0).
      ! Tensor is stored as follows:
      ! S = 0.5*( grad(u) + grad(u)^T )
      !     ( S(1) S(4) S(6) )
      !   = ( S(4) S(2) S(5) )
      !     ( S(6) S(5) S(3) )
      class(op_obj),        intent(in) :: this                                 !! Differential operators utility
      type(Eulerian_obj_r), intent(in) :: U                                    !! Fluid velocity field in 1-dir
      type(Eulerian_obj_r), intent(in) :: V                                    !! Fluid velocity field in 2-dir
      type(Eulerian_obj_r), intent(in) :: W                                    !! Fluid velocity field in 3-dir
      type(eulerian_obj_r)             :: S(6)                                 !! Result
      ! Work variables
      character(str8) :: name
      integer :: i,j,k,n,m,l

      do n=1,6
        call S(n)%Initialize(name,this%block,this%parallel,0)
        S(n) = 0.0_wp
      end do

      associate (lo => this%block%lo,  hi => this%block%hi)
        ! Diagonal elements
        !------------------------------
        do k=lo(3),hi(3)
          do j=lo(2),hi(2)
            do i=lo(1),hi(1)
              S(1)%cell(i,j,k) = dot_product(this%c_d1dx1(:,i),U%cell(i-this%st+1:i+this%st,j,k))
              S(2)%cell(i,j,k) = dot_product(this%c_d1dx2(:,j),V%cell(i,j-this%st+1:j+this%st,k))
              S(3)%cell(i,j,k) = dot_product(this%c_d1dx3(:,k),W%cell(i,j,k-this%st+1:k+this%st))
            end do
          end do
        end do

        ! Off-diagonal elements
        !------------------------------
        do k=lo(3),hi(3)
          do j=lo(2),hi(2)
            do i=lo(1),hi(1)

             ! Interpolate and differentiate
             ! 0.5*(du/dy+dv/dx)
              do l = -this%st+1,this%st
                do n = -this%st, this%st-1
                  do m = -this%st+1,this%st
                    S(4)%cell(i,j,k) = S(4)%cell(i,j,k)                                                       &
                      + 0.5_wp*this%c_d1dx1(l,i)*this%c_intrp1m(n,i+l)*this%c_intrp2(m,j)*V%cell(i+l+n,j+m,k) &
                      + 0.5_wp*this%c_d1dx2(l,j)*this%c_intrp2m(n,j+l)*this%c_intrp1(m,i)*U%cell(i+m,j+l+n,k)
                  end do
                end do
              end do

              ! 0.5*(dw/dy+dv/dz)
              do l = -this%st+1,this%st
                do n = -this%st, this%st-1
                  do m = -this%st+1,this%st
                    S(5)%cell(i,j,k) = S(5)%cell(i,j,k)                                                       &
                      + 0.5_wp*this%c_d1dx2(l,j)*this%c_intrp2m(n,j+l)*this%c_intrp3(m,k)*W%cell(i,j+l+n,k+m) &
                      + 0.5_wp*this%c_d1dx3(l,k)*this%c_intrp3m(n,k+l)*this%c_intrp2(m,j)*V%cell(i,j+m,k+l+n)
                  end do
                end do
              end do

              ! 0.5*(du/dz+dw/dx)
              do l = -this%st+1,this%st
                do n = -this%st, this%st-1
                  do m = -this%st+1,this%st
                    S(6)%cell(i,j,k) = S(6)%cell(i,j,k)                                                       &
                      + 0.5_wp*this%c_d1dx3(l,k)*this%c_intrp3m(n,k+l)*this%c_intrp1(m,i)*U%cell(i+m,j,k+l+n) &
                      + 0.5_wp*this%c_d1dx1(l,i)*this%c_intrp1m(n,i+l)*this%c_intrp3(m,k)*W%cell(i+l+n,j,k+m)
                  end do
                end do
              end do

            end do
          end do
        end do
      end associate

      do n=1,6
        call S(n)%UpdateGhostCells
      end do

      return
    end function op_obj_StrainRate