|
Packit Service |
c5cf8c |
! This file created from f77/rma/baseattrwinf.f with f77tof90
|
|
Packit Service |
c5cf8c |
! -*- Mode: Fortran; -*-
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! (C) 2003 by Argonne National Laboratory.
|
|
Packit Service |
c5cf8c |
! See COPYRIGHT in top-level directory.
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
program main
|
|
Packit Service |
c5cf8c |
use mpi
|
|
Packit Service |
c5cf8c |
integer (kind=MPI_ADDRESS_KIND) extrastate, valin, valout, val
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
logical flag
|
|
Packit Service |
c5cf8c |
integer ierr, errs
|
|
Packit Service |
c5cf8c |
integer base(1024)
|
|
Packit Service |
c5cf8c |
integer disp
|
|
Packit Service |
c5cf8c |
integer win
|
|
Packit Service |
c5cf8c |
integer commsize
|
|
Packit Service |
c5cf8c |
! Include addsize defines asize as an address-sized integer
|
|
Packit Service |
c5cf8c |
integer (kind=MPI_ADDRESS_KIND) asize
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
errs = 0
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_init( ierr )
|
|
Packit Service |
c5cf8c |
call mpi_comm_size( MPI_COMM_WORLD, commsize, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
! Create a window; then extract the values
|
|
Packit Service |
c5cf8c |
asize = 1024
|
|
Packit Service |
c5cf8c |
disp = 4
|
|
Packit Service |
c5cf8c |
call MPI_Win_create( base, asize, disp, MPI_INFO_NULL, &
|
|
Packit Service |
c5cf8c |
& MPI_COMM_WORLD, win, ierr )
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! In order to check the base, we need an address-of function.
|
|
Packit Service |
c5cf8c |
! We use MPI_Get_address, even though that isn't strictly correct
|
|
Packit Service |
c5cf8c |
call MPI_Win_get_attr( win, MPI_WIN_BASE, valout, flag, ierr )
|
|
Packit Service |
c5cf8c |
if (.not. flag) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Could not get WIN_BASE"
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
! There is no easy way to get the actual value of base to compare
|
|
Packit Service |
c5cf8c |
! against. MPI_Address gives a value relative to MPI_BOTTOM, which
|
|
Packit Service |
c5cf8c |
! is different from 0 in Fortran (unless you can define MPI_BOTTOM
|
|
Packit Service |
c5cf8c |
! as something like %pointer(0)).
|
|
Packit Service |
c5cf8c |
! else
|
|
Packit Service |
c5cf8c |
!
|
|
Packit Service |
c5cf8c |
!C For this Fortran 77 version, we use the older MPI_Address function
|
|
Packit Service |
c5cf8c |
! call MPI_Address( base, baseadd, ierr )
|
|
Packit Service |
c5cf8c |
! if (valout .ne. baseadd) then
|
|
Packit Service |
c5cf8c |
! errs = errs + 1
|
|
Packit Service |
c5cf8c |
! print *, "Got incorrect value for WIN_BASE (", valout,
|
|
Packit Service |
c5cf8c |
! & ", should be ", baseadd, ")"
|
|
Packit Service |
c5cf8c |
! endif
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call MPI_Win_get_attr( win, MPI_WIN_SIZE, valout, flag, ierr )
|
|
Packit Service |
c5cf8c |
if (.not. flag) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Could not get WIN_SIZE"
|
|
Packit Service |
c5cf8c |
else
|
|
Packit Service |
c5cf8c |
if (valout .ne. asize) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Got incorrect value for WIN_SIZE (", valout, &
|
|
Packit Service |
c5cf8c |
& ", should be ", asize, ")"
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call MPI_Win_get_attr( win, MPI_WIN_DISP_UNIT, valout, flag, ierr)
|
|
Packit Service |
c5cf8c |
if (.not. flag) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Could not get WIN_DISP_UNIT"
|
|
Packit Service |
c5cf8c |
else
|
|
Packit Service |
c5cf8c |
if (valout .ne. disp) then
|
|
Packit Service |
c5cf8c |
errs = errs + 1
|
|
Packit Service |
c5cf8c |
print *, "Got wrong value for WIN_DISP_UNIT (", valout, &
|
|
Packit Service |
c5cf8c |
& ", should be ", disp, ")"
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
endif
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call MPI_Win_free( win, ierr )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
call mtest_finalize( errs )
|
|
Packit Service |
c5cf8c |
|
|
Packit Service |
c5cf8c |
end
|