ObserverUpdate Subroutine

public subroutine ObserverUpdate(self, mesh, isSolid, bufferPosition, interpolate)

Uses

    • VariableConversion

Type Bound

ObserverClass

Arguments

Type IntentOptional Attributes Name
class(ObserverClass) :: self
class(HexMesh), intent(in) :: mesh
logical, intent(in) :: isSolid
integer, intent(in), optional :: bufferPosition
logical, intent(in) :: interpolate

Source Code

   Subroutine ObserverUpdate(self, mesh, isSolid, BufferPosition, interpolate)

!     *******************************************************************
!        This subroutine updates the observer acoustic pressure computing it from
!        the mesh storage. It is stored in the "bufferPosition" position of the 
!        buffer.
!     *******************************************************************
!
use VariableConversion, only: Pressure, PressureDot
      implicit none
      class (ObserverClass)                                :: self
      class (HexMesh), intent(in)                          :: mesh
      integer,intent(in), optional                         :: bufferPosition
      logical, intent(in)                                  :: isSolid, interpolate

      ! local variables
      real(kind=RP)                                        :: Pt, Pl  ! pressure of each pair
      real(kind=RP), dimension(3)                          :: localPacc, Pacc   ! temporal variable to store the sum of the pressure
      real(kind=RP), dimension(3)                          :: mInterp ! slope of interpolation
      real(kind=RP)                                        :: valx, valy, valz
      integer                                              :: zoneFaceID, meshFaceID,  ierr
      integer                                             :: storePosition

!     Initialization
!     --------------            
      if (present(bufferPosition)) self % Pac(bufferPosition,:) = 0.0_RP
      Pacc = 0.0_RP
      valx = 0.0_RP
      valy = 0.0_RP
      valz = 0.0_RP

!     Loop the pairs (equivalent to loop the zone) and get the values
!     ---------------------------------------
      interp_cond: if (interpolate) then
!        For this case only save the values of the solution of each pair, at the corresponding position
!        ---------------------------------------
!$omp parallel private(meshFaceID,storePosition,localPacc) shared(mesh,isSolid,interpolate,Pacc,NodalStorage,&
!$omp&                                                     self,bufferPosition)
!$omp do private(meshFaceID,storePosition,localPacc) schedule(runtime)
         do zoneFaceID = 1, self % numberOfFaces
!            Compute the integral
!            --------------------
             meshFaceID = self % sourcePair(zoneFaceID) % faceIDinMesh
             localPacc = self % sourcePair(zoneFaceID) % FWHSurfaceIntegral( mesh % faces(meshFaceID), isSolid )

             !save solution at bufferPosition or last position
             if (present(bufferPosition)) then
                 storePosition = bufferPosition
             else
                 storePosition = size(self % sourcePair(zoneFaceID) % Pacc, dim=1)
             end if
             self % sourcePair(zoneFaceID) % Pacc(storePosition,:) = localPacc
         end do  
!$omp end do
!$omp end parallel
     else interp_cond
!        For this case get the whole solution of the observer, adding all the pairs without saving
!        ---------------------------------------
!$omp parallel private(meshFaceID, localPacc) shared(mesh,isSolid,interpolate,Pacc,NodalStorage,&
!$omp&                                        self,valx,valy,valz)
!$omp do private(meshFaceID,localPacc) reduction(+:valx,valy,valz) schedule(runtime)
          do zoneFaceID = 1, self % numberOfFaces
!            Compute the integral
!            --------------------
             meshFaceID = self % sourcePair(zoneFaceID) % faceIDinMesh

             localPacc = self % sourcePair(zoneFaceID) % FWHSurfaceIntegral( mesh % faces(meshFaceID), isSolid )

             ! sum without interpolate: suppose little change of each tDelay
             valx = valx + localPacc(1)
             valy = valy + localPacc(2)
             valz = valz + localPacc(3)
         end do  
!$omp end do
!$omp end parallel

          Pacc = (/valx, valy, valz/)

#ifdef _HAS_MPI_
      localPacc = Pacc
      call mpi_allreduce(localPacc, Pacc, 3, MPI_DOUBLE, MPI_SUM, MPI_COMM_WORLD, ierr)
#endif

          self % Pac(bufferPosition,:) = Pacc
     end if interp_cond

   End Subroutine ObserverUpdate