Page Menu
Home
c4science
Search
Configure Global Search
Log In
Files
F106994128
pi_p2p_ring.f90
No One
Temporary
Actions
Download File
Edit File
Delete File
View Transforms
Subscribe
Mute Notifications
Award Token
Subscribers
None
File Metadata
Details
File Info
Storage
Attached
Created
Thu, Apr 3, 07:34
Size
1 KB
Mime Type
text/x-c
Expires
Sat, Apr 5, 07:34 (1 d, 23 h)
Engine
blob
Format
Raw Data
Handle
25327689
Attached To
rSCINTROPAR Introduction to parallelism
pi_p2p_ring.f90
View Options
! ==========================================================================
! This exercise is taken from the class Parallel Programming Workshop (MPI,
! OpenMP and Advanced Topics) at HLRS given by Rolf Rabenseifner
! ==========================================================================
program pi_p2p_ring
use mpi
implicit none
integer, parameter :: n = 10000000
double precision :: omp_t1, omp_t2
double precision :: dx, x, sm, pif
double precision, external :: f
integer :: i
integer :: ierror, prank, psize
integer :: nlocal, istart, iend
integer :: next, prev
double precision :: send, recv
integer :: request
call MPI_init(ierror)
call MPI_Comm_size(MPI_COMM_WORLD, psize, ierror)
call MPI_Comm_rank(MPI_COMM_WORLD, prank, ierror)
! calculate pi = integral [0..1] 4 / (1 + x**2) dx
omp_t1 = MPI_Wtime()
nlocal = n / psize
istart = 1 + nlocal * prank
iend = nlocal * (prank + 1);
dx = 1. / n
sm = 0.0;
do i = istart, iend
x = (1. * i - 0.5) * dx
sm = sm + f(x)
enddo
next = mod((prank + 1),psize)
prev = mod((prank - 1 + psize), psize)
send = sm
do i = 2, psize
if (mod(prank,2).eq.0) then
call MPI_Send(send, 1, MPI_DOUBLE, next, 13, MPI_COMM_WORLD, request, ierror);
call MPI_Recv(recv, 1, MPI_DOUBLE, prev, 13, MPI_COMM_WORLD, MPI_STATUS_IGNORE, ierror);
else
call MPI_Recv(recv, 1, MPI_DOUBLE, prev, 13, MPI_COMM_WORLD, MPI_STATUS_IGNORE, ierror);
call MPI_Send(send, 1, MPI_DOUBLE, next, 13, MPI_COMM_WORLD, request, ierror);
endif
sm = sm + recv
send = recv
enddo
pif = dx * sm
omp_t2 = MPI_Wtime()
if (prank.eq.0) then
print *, 'computed pi =',pif
print *, 'Running time = ', (omp_t2-omp_t1)
endif
call MPI_Finalize(ierror)
end program pi_p2p_ring
double precision function f(a)
implicit none
double precision, intent(in) :: a
f = 4. / (1. + (a**2))
end function f
Event Timeline
Log In to Comment