|
Packit |
0848f5 |
! This file created from test/mpi/f77/io/fileerrf.f with f77tof90
|
|
Packit |
0848f5 |
! -*- Mode: Fortran; -*-
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! (C) 2003 by Argonne National Laboratory.
|
|
Packit |
0848f5 |
! See COPYRIGHT in top-level directory.
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
program main
|
|
Packit |
0848f5 |
use mpi
|
|
Packit |
0848f5 |
integer errs, ierr, code(2), newerrclass, eclass
|
|
Packit |
0848f5 |
character*(MPI_MAX_ERROR_STRING) errstring
|
|
Packit |
0848f5 |
integer comm, rlen
|
|
Packit |
0848f5 |
integer buf(10)
|
|
Packit |
0848f5 |
integer file
|
|
Packit |
0848f5 |
! external myerrhanfunc
|
|
Packit |
0848f5 |
INTERFACE
|
|
Packit |
0848f5 |
SUBROUTINE myerrhanfunc(vv0,vv1)
|
|
Packit |
0848f5 |
INTEGER vv0,vv1
|
|
Packit |
0848f5 |
END SUBROUTINE
|
|
Packit |
0848f5 |
END INTERFACE
|
|
Packit |
0848f5 |
integer myerrhan, qerr
|
|
Packit |
0848f5 |
integer callcount, codesSeen(3)
|
|
Packit |
0848f5 |
common /myerrhan/ callcount, codesSeen
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
errs = 0
|
|
Packit |
0848f5 |
callcount = 0
|
|
Packit |
0848f5 |
call mtest_init( ierr )
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! Setup some new codes and classes
|
|
Packit |
0848f5 |
call mpi_add_error_class( newerrclass, ierr )
|
|
Packit |
0848f5 |
call mpi_add_error_code( newerrclass, code(1), ierr )
|
|
Packit |
0848f5 |
call mpi_add_error_code( newerrclass, code(2), ierr )
|
|
Packit |
0848f5 |
call mpi_add_error_string( newerrclass, "New Class", ierr )
|
|
Packit |
0848f5 |
call mpi_add_error_string( code(1), "First new code", ierr )
|
|
Packit |
0848f5 |
call mpi_add_error_string( code(2), "Second new code", ierr )
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
call mpi_file_create_errhandler( myerrhanfunc, myerrhan, ierr )
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! Create a new communicator so that we can leave the default errors-abort
|
|
Packit |
0848f5 |
! on MPI_COMM_WORLD. Use this comm for file_open, just to leave a little
|
|
Packit |
0848f5 |
! more separation from comm_world
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
|
|
Packit |
0848f5 |
call mpi_file_open( comm, "testfile.txt", MPI_MODE_RDWR + &
|
|
Packit |
0848f5 |
& MPI_MODE_CREATE, MPI_INFO_NULL, file, ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
call mpi_file_set_errhandler( file, myerrhan, ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call mpi_file_get_errhandler( file, qerr, ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
if (qerr .ne. myerrhan) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Did not get expected error handler'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_errhandler_free( qerr, ierr )
|
|
Packit |
0848f5 |
! We can free our error handler now
|
|
Packit |
0848f5 |
call mpi_errhandler_free( myerrhan, ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call mpi_file_call_errhandler( file, newerrclass, ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_file_call_errhandler( file, code(1), ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_file_call_errhandler( file, code(2), ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
call MTestPrintError( ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
if (callcount .ne. 3) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Expected 3 calls to error handler, found ', &
|
|
Packit |
0848f5 |
& callcount
|
|
Packit |
0848f5 |
else
|
|
Packit |
0848f5 |
if (codesSeen(1) .ne. newerrclass) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, 'Expected class ', newerrclass, ' got ', &
|
|
Packit |
0848f5 |
& codesSeen(1)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
if (codesSeen(2) .ne. code(1)) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, 'Expected code ', code(1), ' got ', &
|
|
Packit |
0848f5 |
& codesSeen(2)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
if (codesSeen(3) .ne. code(2)) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, 'Expected code ', code(2), ' got ', &
|
|
Packit |
0848f5 |
& codesSeen(3)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call mpi_file_close( file, ierr )
|
|
Packit |
0848f5 |
call mpi_comm_free( comm, ierr )
|
|
Packit |
0848f5 |
call mpi_file_delete( "testfile.txt", MPI_INFO_NULL, ierr )
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
! Check error strings while here here...
|
|
Packit |
0848f5 |
call mpi_error_string( newerrclass, errstring, rlen, ierr )
|
|
Packit |
0848f5 |
if (errstring(1:rlen) .ne. "New Class") then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Wrong string for error class: ', errstring(1:rlen)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_error_class( code(1), eclass, ierr )
|
|
Packit |
0848f5 |
if (eclass .ne. newerrclass) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Class for new code is not correct'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_error_string( code(1), errstring, rlen, ierr )
|
|
Packit |
0848f5 |
if (errstring(1:rlen) .ne. "First new code") then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Wrong string for error code: ', errstring(1:rlen)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_error_class( code(2), eclass, ierr )
|
|
Packit |
0848f5 |
if (eclass .ne. newerrclass) then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Class for new code is not correct'
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_error_string( code(2), errstring, rlen, ierr )
|
|
Packit |
0848f5 |
if (errstring(1:rlen) .ne. "Second new code") then
|
|
Packit |
0848f5 |
errs = errs + 1
|
|
Packit |
0848f5 |
print *, ' Wrong string for error code: ', errstring(1:rlen)
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
call mtest_finalize( errs )
|
|
Packit |
0848f5 |
call mpi_finalize( ierr )
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
end
|
|
Packit |
0848f5 |
!
|
|
Packit |
0848f5 |
subroutine myerrhanfunc( file, errcode )
|
|
Packit |
0848f5 |
use mpi
|
|
Packit |
0848f5 |
integer file, errcode
|
|
Packit |
0848f5 |
integer rlen, ierr
|
|
Packit |
0848f5 |
integer callcount, codesSeen(3)
|
|
Packit |
0848f5 |
character*(MPI_MAX_ERROR_STRING) errstring
|
|
Packit |
0848f5 |
common /myerrhan/ callcount, codesSeen
|
|
Packit |
0848f5 |
|
|
Packit |
0848f5 |
callcount = callcount + 1
|
|
Packit |
0848f5 |
! Remember the code we've seen
|
|
Packit |
0848f5 |
if (callcount .le. 3) then
|
|
Packit |
0848f5 |
codesSeen(callcount) = errcode
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
call mpi_error_string( errcode, errstring, rlen, ierr )
|
|
Packit |
0848f5 |
if (ierr .ne. MPI_SUCCESS) then
|
|
Packit |
0848f5 |
print *, ' Panic! could not get error string'
|
|
Packit |
0848f5 |
call mpi_abort( MPI_COMM_WORLD, 1, ierr )
|
|
Packit |
0848f5 |
endif
|
|
Packit |
0848f5 |
end
|