Skip to content

Commit

Permalink
callback prototypes - untested
Browse files Browse the repository at this point in the history
  • Loading branch information
jeffhammond committed Feb 18, 2024
1 parent be4f668 commit 31c4013
Show file tree
Hide file tree
Showing 2 changed files with 142 additions and 0 deletions.
123 changes: 123 additions & 0 deletions mpi_fortran_callback_prototypes.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,123 @@

ABSTRACT INTERFACE
SUBROUTINE MPI_User_function(invec, inoutvec, len, datatype)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR
TYPE(C_PTR), VALUE :: invec, inoutvec
INTEGER :: len
TYPE(MPI_Datatype) :: datatype

ABSTRACT INTERFACE
SUBROUTINE MPI_User_function_c(invec, inoutvec, len, datatype) !(_c)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR
TYPE(C_PTR), VALUE :: invec, inoutvec
INTEGER(KIND=MPI_COUNT_KIND) :: len
TYPE(MPI_Datatype) :: datatype

ABSTRACT INTERFACE
SUBROUTINE MPI_Comm_copy_attr_function(oldcomm, comm_keyval, extra_state,
attribute_val_in, attribute_val_out, flag, ierror)
TYPE(MPI_Comm) :: oldcomm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in,
attribute_val_out
LOGICAL :: flag

ABSTRACT INTERFACE
SUBROUTINE MPI_Comm_delete_attr_function(comm, comm_keyval, attribute_val, extra_state, ierror)
TYPE(MPI_Comm) :: comm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: attribute_val, extra_state

ABSTRACT INTERFACE
SUBROUTINE MPI_Win_copy_attr_function(oldcomm, comm_keyval, extra_state,
attribute_val_in, attribute_val_out, flag, ierror)
TYPE(MPI_Win) :: oldcomm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in,
attribute_val_out
LOGICAL :: flag

ABSTRACT INTERFACE
SUBROUTINE MPI_Win_delete_attr_function(comm, comm_keyval, attribute_val, extra_state, ierror)
TYPE(MPI_Win) :: comm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: attribute_val, extra_state

ABSTRACT INTERFACE
SUBROUTINE MPI_Type_copy_attr_function(oldcomm, comm_keyval, extra_state,
attribute_val_in, attribute_val_out, flag, ierror)
TYPE(MPI_Type) :: oldcomm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in,
attribute_val_out
LOGICAL :: flag

ABSTRACT INTERFACE
SUBROUTINE MPI_Type_delete_attr_function(comm, comm_keyval, attribute_val, extra_state, ierror)
TYPE(MPI_Type) :: comm
INTEGER :: comm_keyval, ierror
INTEGER(KIND=MPI_ADDRESS_KIND) :: attribute_val, extra_state

ABSTRACT INTERFACE
SUBROUTINE MPI_Comm_errhandler_function(comm, error_code)
TYPE(MPI_Comm) :: comm
INTEGER :: error_code

ABSTRACT INTERFACE
SUBROUTINE MPI_Win_errhandler_function(win, error_code)
TYPE(MPI_Win) :: win
INTEGER :: error_code

ABSTRACT INTERFACE
SUBROUTINE MPI_File_errhandler_function(file, error_code)
TYPE(MPI_File) :: file
INTEGER :: error_code

ABSTRACT INTERFACE
SUBROUTINE MPI_Session_errhandler_function(session, error_code)
TYPE(MPI_Session) :: session
INTEGER :: error_code

ABSTRACT INTERFACE
SUBROUTINE MPI_Grequest_query_function(extra_state, status, ierror)
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state
TYPE(MPI_Status) :: status
INTEGER :: ierror

ABSTRACT INTERFACE
SUBROUTINE MPI_Grequest_free_function(extra_state, ierror)
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state
INTEGER :: ierror

ABSTRACT INTERFACE
SUBROUTINE MPI_Grequest_cancel_function(extra_state, complete, ierror)
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state
LOGICAL :: complete
INTEGER :: ierror

ABSTRACT INTERFACE
SUBROUTINE MPI_Datarep_extent_function(datatype, extent, extra_state, ierror)
TYPE(MPI_Datatype) :: datatype
INTEGER(KIND=MPI_ADDRESS_KIND) :: extent, extra_state
INTEGER :: ierror

ABSTRACT INTERFACE
SUBROUTINE MPI_Datarep_conversion_function(userbuf, datatype, count, filebuf,
position, extra_state, ierror)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR
TYPE(C_PTR), VALUE :: userbuf, filebuf
TYPE(MPI_Datatype) :: datatype
INTEGER :: count, ierror
INTEGER(KIND=MPI_OFFSET_KIND) :: position
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state

ABSTRACT INTERFACE
SUBROUTINE MPI_Datarep_conversion_function_c(userbuf, datatype, count,
filebuf, position, extra_state, ierror) !(_c)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR
TYPE(C_PTR), VALUE :: userbuf, filebuf
TYPE(MPI_Datatype) :: datatype
INTEGER(KIND=MPI_COUNT_KIND) :: count
INTEGER(KIND=MPI_OFFSET_KIND) :: position
INTEGER(KIND=MPI_ADDRESS_KIND) :: extra_state
INTEGER :: ierror
19 changes: 19 additions & 0 deletions mpi_fortran_constants.F90
Original file line number Diff line number Diff line change
Expand Up @@ -361,5 +361,24 @@ module mpi_fortran_constants
integer, parameter :: MPI_WIN_CREATE_FLAVOR = 20004
integer, parameter :: MPI_WIN_MODEL = 20005

#define MPI_NULL_COPY_FN ((MPI_Copy_function*)0x0)
#define MPI_DUP_FN ((MPI_Copy_function*)0x1)
#define MPI_NULL_DELETE_FN ((MPI_Delete_function*)0x0)
#define MPI_COMM_NULL_COPY_FN ((MPI_Comm_copy_attr_function*)0x0)
#define MPI_COMM_DUP_FN ((MPI_Comm_copy_attr_function*)0x1)
#define MPI_COMM_NULL_DELETE_FN ((MPI_Comm_delete_attr_function*)0x0)
#define MPI_TYPE_NULL_COPY_FN ((MPI_Type_copy_attr_function*)0x0)
#define MPI_TYPE_DUP_FN ((MPI_Type_copy_attr_function*)0x1)
#define MPI_TYPE_NULL_DELETE_FN ((MPI_Type_delete_attr_function*)0x0)
#define MPI_WIN_NULL_COPY_FN ((MPI_Win_copy_attr_function*)0x0)
#define MPI_WIN_DUP_FN ((MPI_Win_copy_attr_function*)0x1)
#define MPI_WIN_NULL_DELETE_FN ((MPI_Win_delete_attr_function*)0x0)
#define MPI_CONVERSION_FN_NULL ((MPI_Datarep_conversion_function*)0x0)

#define MPI_T_ENUM_NULL ((MPI_T_enum)0)
#define MPI_T_CVAR_HANDLE_NULL ((MPI_T_cvar_handle)0)
#define MPI_T_PVAR_SESSION_NULL ((MPI_T_pvar_session)0)
#define MPI_T_PVAR_HANDLE_NULL ((MPI_T_pvar_handle)0)
#define MPI_T_PVAR_ALL_HANDLES ((MPI_T_pvar_handle)1)

end module mpi_fortran_constants

0 comments on commit 31c4013

Please sign in to comment.