ObserverSumIntegrals Subroutine

public subroutine ObserverSumIntegrals(self, nDiscard, N, startIndex, no_of_lines)

Type Bound

ObserverClass

Arguments

Type IntentOptional Attributes Name
class(ObserverClass) :: self
integer, intent(in), dimension(self % numberOfFaces) :: nDiscard
integer, intent(in) :: N
integer, intent(in) :: startIndex
integer, intent(in) :: no_of_lines

Source Code

   Subroutine ObserverSumIntegrals(self, nDiscard, N, startIndex, no_of_lines)

      implicit none  

      class(observerclass)                                 :: self
      integer, intent(in)                                  :: no_of_lines, startIndex, N
      integer, dimension(self % numberOfFaces), intent(in) :: nDiscard

      ! local variables
      real(kind=RP), dimension(:,:), allocatable           :: localPacc, Pacc   ! temporal variable to store the sum of the pressure
      real(kind=RP), dimension(:), allocatable             :: valx, valy, valz
      integer                                              :: i, ierr

!     Initialization
!     --------------            
      ! 1:N must be equal to startIndex:no_of_lines
      allocate(Pacc(N,3), localPacc(N,3), valx(N), valy(N), valz(N))
      Pacc = 0.0_RP
      valx = 0.0_RP
      valy = 0.0_RP
      valz = 0.0_RP

!$omp parallel private(localPacc) shared(Pacc,nDiscard,N,self,valx,valy,valz)
!$omp do private(localPacc) reduction(+:valx,valy,valz) schedule(runtime)
      do i = 1, self % numberOfFaces
!        Get the array of interpolated values of each pair
         localPacc(1:N,:) = self % sourcePair(i) % Pacc(nDiscard(i)+1:nDiscard(i)+N,:)

         ! sum interpolated
         valx = valx + localPacc(:,1)
         valy = valy + localPacc(:,2)
         valz = valz + localPacc(:,3)

      end do  
!$omp end do
!$omp end parallel

      Pacc(:,1) = valx(:)
      Pacc(:,2) = valy(:)
      Pacc(:,3) = valz(:)

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

      self % Pac(startIndex:no_of_lines,:) = Pacc(1:N,:)

   End Subroutine ObserverSumIntegrals