ResPart_set_GetHydroForces Subroutine

private impure subroutine ResPart_set_GetHydroForces(this, P, U, V, W, ibVF, visc)

Computes hydrodynamic force on particle.

Type Bound

ResPart_set

Arguments

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

Collection of Resolved Particles

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

Fluid pressure field

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), intent(in) :: ibVF

Solid volume fraction

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

Fluid viscosity


Calls

proc~~respart_set_gethydroforces~~CallsGraph proc~respart_set_gethydroforces ResPart_set%ResPart_set_GetHydroForces markers markers proc~respart_set_gethydroforces->markers particles particles proc~respart_set_gethydroforces->particles proc~cross_product~2 cross_product proc~respart_set_gethydroforces->proc~cross_product~2 proc~respart_set_getsurfacestresses ResPart_set%ResPart_set_GetSurfaceStresses proc~respart_set_gethydroforces->proc~respart_set_getsurfacestresses proc~respart_set_regroup ResPart_set%ResPart_set_Regroup proc~respart_set_gethydroforces->proc~respart_set_regroup proc~respart_set_updatelookup ResPart_set%ResPart_set_UpdateLookup proc~respart_set_gethydroforces->proc~respart_set_updatelookup proc~respart_set_getsurfacestresses->markers p p proc~respart_set_getsurfacestresses->p proc~op_obj_strainrate op_obj%op_obj_StrainRate proc~respart_set_getsurfacestresses->proc~op_obj_strainrate proc~respart_set_regroup->markers proc~block_obj_locate block_obj%block_obj_Locate proc~respart_set_regroup->proc~block_obj_locate proc~lagrangian_set_communicate lagrangian_set%lagrangian_set_Communicate proc~respart_set_regroup->proc~lagrangian_set_communicate proc~lagrangian_set_updatecount lagrangian_set%lagrangian_set_UpdateCount proc~respart_set_regroup->proc~lagrangian_set_updatecount proc~respart_set_updatelookup->particles mpi_cart_rank mpi_cart_rank proc~block_obj_locate->mpi_cart_rank mpi_gather mpi_gather proc~lagrangian_set_communicate->mpi_gather mpi_recv mpi_recv proc~lagrangian_set_communicate->mpi_recv mpi_send mpi_send proc~lagrangian_set_communicate->mpi_send proc~lagrangian_set_recycle lagrangian_set%lagrangian_set_Recycle proc~lagrangian_set_communicate->proc~lagrangian_set_recycle proc~lagrangian_set_resize lagrangian_set%lagrangian_set_Resize proc~lagrangian_set_communicate->proc~lagrangian_set_resize mpi_allgather mpi_allgather proc~lagrangian_set_updatecount->mpi_allgather 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 proc~lagrangian_set_recycle->proc~lagrangian_set_resize 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~~respart_set_gethydroforces~~CalledByGraph proc~respart_set_gethydroforces ResPart_set%ResPart_set_GetHydroForces 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 subroutine ResPart_set_GetHydroForces(this,P,U,V,W,ibVF,visc)
      !> Computes hydrodynamic force on particle.
      implicit none
      class(ResPart_set),   intent(inout) :: this                              !! Collection of Resolved Particles
      type(Eulerian_obj_r), intent(in)    :: P                                 !! Fluid pressure field
      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), intent(in)    :: ibVF                              !! Solid volume fraction
      real(wp),             intent(in)    :: visc                              !! Fluid viscosity
      ! work variable
      integer(leapI8):: id
      integer  :: n,m
      integer  :: dir
      real(wp) :: disp(3)

      call this%GetSurfaceStresses(P,U,V,W,ibVF,visc)

      ! Bring markers that may be in other blocks
      ! to the one containing the centroid
      call this%Regroup()
      call this%UpdateLookup()

      ! Zero foces and torques
      select type (particles =>this%p)
      type is (ResPart_obj)
        do n=1,this%count_
          particles(n)%Fh=0.0_wp
          particles(n)%Th=0.0_wp
        end do
      end select

      ! Compute hydrodynamic forces exerted on particles
      select type (particles =>this%p)
      type is (ResPart_obj)
        select type(markers=>this%ib%p)
        type is (marker_obj)
          do m=1,this%ib%count_
            ! Get ID of parent centroid
            id=markers(m)%s
            ! Get local index of the centroid
            n = this%lookup(id)
            ! Update force applied on the resolved particle
            particles(n)%Fh = particles(n)%Fh + markers(m)%SA*markers(m)%f

            ! Compute displacement for torque
            disp = markers(m)%p-particles(n)%p

            ! Treatment for periodicity
            do dir=1,3
              if (this%block%periods(dir)) then
                if ( disp(dir).gt.0 .and. abs(disp(dir)).gt.0.5_wp*particles(n)%d) then
                   disp(dir) = disp(dir) - (this%block%pmax(dir)-this%block%pmin(dir))
                end if

                if ( disp(dir).lt.0 .and. abs(disp(dir)).gt.0.5_wp*particles(n)%d) then
                   disp(dir) = disp(dir) + (this%block%pmax(dir)-this%block%pmin(dir))
               end if
              end if
            end do

            ! Update torque applied on the resolved particle
            particles(n)%Th = particles(n)%Th + markers(m)%SA*cross_product(disp,markers(m)%f)
          end do
        end select
      end select

      return
    end subroutine ResPart_set_GetHydroForces