1
1

mpi/fortran: use conformant dummy names for Fortran bindings

The MPI spec defines that the "mpi" and "mpi_f08" module Fortran
bindings support passing by parameters by name.  Hence, we need to use
the MPI-spec-defined parameter names ("dummy variables", in Fortran
parlance) for the "mpi" and "mpi_f08" modules.

Specifically, Fortran allows calls to procedures to be written with
keyword arguments, e.g., "call mpi_sizeof(x=x,size=rsize,ierror=ier)"
An "explicit interface" for the procedure must be in scope for this to
be allowed in a Fortran program unit.  Therefore, the explicit
interface blocks we provide in the "mpi" and "mpi_f08" modules must
match the MPI published standard, including the names of the dummy
variables (i.e., parameter names), as that is how Fortran programs may
call them.

Note that we didn't find this issue previously because even though the
MPI spec *allows* for name-based parameter passing, not many people
actually use it.  I suspect that we might have some more incorrect
parameter names -- we should probably do a full "mpi" / "mpi_f08"
module parameter name audit someday.

Thanks to Themos Tsikas for reporting the issue and supplying the
initial fix.

Signed-off-by: themos.tsikas@nag.co.uk
Signed-off-by: Jeff Squyres <jsquyres@cisco.com>
Signed-off-by: Gilles Gouaillardet <gilles@rist.or.jp>
Этот коммит содержится в:
Themos Tsikas 2018-04-27 11:30:01 +01:00 коммит произвёл Gilles Gouaillardet
родитель 72f2c3befe
Коммит 4d126c16fa
21 изменённых файлов: 256 добавлений и 242 удалений

Просмотреть файл

@ -4,7 +4,7 @@
! Copyright (c) 2006-2014 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2006-2014 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2013 Los Alamos National Security, LLC. All rights ! Copyright (c) 2013 Los Alamos National Security, LLC. All rights
! reserved. ! reserved.
! Copyright (c) 2015 Research Organization for Information Science ! Copyright (c) 2015-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -84,35 +84,35 @@ interface
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine MPI_TYPE_DUP_FN( oldtype, type_keyval, extra_state, & subroutine MPI_TYPE_DUP_FN( datatype, type_keyval, extra_state, &
attribute_val_in, attribute_val_out, & attribute_val_in, attribute_val_out, &
flag, ierr ) flag, ierr )
implicit none implicit none
include 'mpif-config.h' include 'mpif-config.h'
integer :: oldtype integer :: datatype
integer :: type_keyval integer :: type_keyval
integer(KIND=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in, attribute_val_out integer(KIND=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in, attribute_val_out
logical :: flag logical :: flag
integer :: ierr integer :: ierr
end subroutine MPI_TYPE_DUP_FN end subroutine MPI_TYPE_DUP_FN
subroutine MPI_TYPE_NULL_COPY_FN( type, type_keyval, extra_state, & subroutine MPI_TYPE_NULL_COPY_FN( datatype, type_keyval, extra_state, &
attribute_val_in, attribute_val_out, & attribute_val_in, attribute_val_out, &
flag, ierr ) flag, ierr )
implicit none implicit none
include 'mpif-config.h' include 'mpif-config.h'
integer :: type integer :: datatype
integer :: type_keyval integer :: type_keyval
integer(kind=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in, attribute_val_out integer(kind=MPI_ADDRESS_KIND) :: extra_state, attribute_val_in, attribute_val_out
integer :: ierr integer :: ierr
logical :: flag logical :: flag
end subroutine MPI_TYPE_NULL_COPY_FN end subroutine MPI_TYPE_NULL_COPY_FN
subroutine MPI_TYPE_NULL_DELETE_FN( type, type_keyval, attribute_val_out, & subroutine MPI_TYPE_NULL_DELETE_FN( datatype, type_keyval, attribute_val_out, &
extra_state, ierr ) extra_state, ierr )
implicit none implicit none
include 'mpif-config.h' include 'mpif-config.h'
integer :: type integer :: datatype
integer :: type_keyval integer :: type_keyval
integer(kind=MPI_ADDRESS_KIND) :: attribute_val_out, extra_state integer(kind=MPI_ADDRESS_KIND) :: attribute_val_out, extra_state
integer :: ierr integer :: ierr

Просмотреть файл

@ -2,7 +2,7 @@
! Copyright (c) 2009-2013 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2013 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2015-2017 Research Organization for Information Science ! Copyright (c) 2015-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
@ -23,13 +23,13 @@ END INTERFACE
!Example of a user defined callback function !Example of a user defined callback function
! !
! subroutine my_user_function( invec, inoutvec, len, type ) bind(c) ! subroutine my_user_function( invec, inoutvec, len, datatype ) bind(c)
! use, intrinsic :: iso_c_binding, only : c_ptr, c_f_pointer ! use, intrinsic :: iso_c_binding, only : c_ptr, c_f_pointer
! type(c_ptr), value :: invec, inoutvec ! type(c_ptr), value :: invec, inoutvec
! integer, intent(in) :: len ! integer, intent(in) :: len
! type(MPI_Datatype) :: type ! type(MPI_Datatype) :: datatype
! real, pointer :: invec_r(:), inoutvec_r(:) ! real, pointer :: invec_r(:), inoutvec_r(:)
! if (type%MPI_VAL == MPI_REAL%MPI_VAL) then ! if (datatype%MPI_VAL == MPI_REAL%MPI_VAL) then
! call c_f_pointer(invec, invec_r, (/ len /) ) ! call c_f_pointer(invec, invec_r, (/ len /) )
! call c_f_pointer(inoutvec, inoutvec_r, (/ len /) ) ! call c_f_pointer(inoutvec, inoutvec_r, (/ len /) )
! inoutvec_r = invec_r + inoutvec_r ! inoutvec_r = invec_r + inoutvec_r

Просмотреть файл

@ -7,7 +7,7 @@
! of Tennessee Research Foundation. All rights ! of Tennessee Research Foundation. All rights
! reserved. ! reserved.
! Copyright (c) 2012 Inria. All rights reserved. ! Copyright (c) 2012 Inria. All rights reserved.
! Copyright (c) 2015-2017 Research Organization for Information Science ! Copyright (c) 2015-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -655,10 +655,10 @@ subroutine ompi_type_create_subarray_f(ndims,array_of_sizes, &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_create_subarray_f end subroutine ompi_type_create_subarray_f
subroutine ompi_type_dup_f(type,newtype,ierror) & subroutine ompi_type_dup_f(oldtype,newtype,ierror) &
BIND(C, name="ompi_type_dup_f") BIND(C, name="ompi_type_dup_f")
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: oldtype
INTEGER, INTENT(OUT) :: newtype INTEGER, INTENT(OUT) :: newtype
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_dup_f end subroutine ompi_type_dup_f
@ -1536,10 +1536,10 @@ subroutine ompi_type_create_keyval_f(type_copy_attr_fn,type_delete_attr_fn, &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_create_keyval_f end subroutine ompi_type_create_keyval_f
subroutine ompi_type_delete_attr_f(type,type_keyval,ierror) & subroutine ompi_type_delete_attr_f(datatype,type_keyval,ierror) &
BIND(C, name="ompi_type_delete_attr_f") BIND(C, name="ompi_type_delete_attr_f")
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_delete_attr_f end subroutine ompi_type_delete_attr_f
@ -1551,32 +1551,32 @@ subroutine ompi_type_free_keyval_f(type_keyval,ierror) &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_free_keyval_f end subroutine ompi_type_free_keyval_f
subroutine ompi_type_get_name_f(type,type_name,resultlen,ierror,type_name_len) & subroutine ompi_type_get_name_f(datatype,type_name,resultlen,ierror,type_name_len) &
BIND(C, name="ompi_type_get_name_f") BIND(C, name="ompi_type_get_name_f")
use, intrinsic :: ISO_C_BINDING, only : C_CHAR use, intrinsic :: ISO_C_BINDING, only : C_CHAR
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: type_name CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: type_name
INTEGER, INTENT(OUT) :: resultlen INTEGER, INTENT(OUT) :: resultlen
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
INTEGER, VALUE, INTENT(IN) :: type_name_len INTEGER, VALUE, INTENT(IN) :: type_name_len
end subroutine ompi_type_get_name_f end subroutine ompi_type_get_name_f
subroutine ompi_type_set_attr_f(type,type_keyval,attribute_val,ierror) & subroutine ompi_type_set_attr_f(datatype,type_keyval,attribute_val,ierror) &
BIND(C, name="ompi_type_set_attr_f") BIND(C, name="ompi_type_set_attr_f")
use :: mpi_f08_types, only : MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_ADDRESS_KIND
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_set_attr_f end subroutine ompi_type_set_attr_f
subroutine ompi_type_set_name_f(type,type_name,ierror,type_name_len) & subroutine ompi_type_set_name_f(datatype,type_name,ierror,type_name_len) &
BIND(C, name="ompi_type_set_name_f") BIND(C, name="ompi_type_set_name_f")
use, intrinsic :: ISO_C_BINDING, only : C_CHAR use, intrinsic :: ISO_C_BINDING, only : C_CHAR
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: type_name CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: type_name
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
INTEGER, VALUE, INTENT(IN) :: type_name_len INTEGER, VALUE, INTENT(IN) :: type_name_len
@ -3246,11 +3246,11 @@ subroutine ompi_type_create_f90_real_f(p,r,newtype,ierror) &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_create_f90_real_f end subroutine ompi_type_create_f90_real_f
subroutine ompi_type_match_size_f(typeclass,size,type,ierror) & subroutine ompi_type_match_size_f(typeclass,size,datatype,ierror) &
BIND(C, name="ompi_type_match_size_f") BIND(C, name="ompi_type_match_size_f")
implicit none implicit none
INTEGER, INTENT(IN) :: typeclass, size INTEGER, INTENT(IN) :: typeclass, size
INTEGER, INTENT(OUT) :: type INTEGER, INTENT(OUT) :: datatype
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine ompi_type_match_size_f end subroutine ompi_type_match_size_f

Просмотреть файл

@ -7,7 +7,7 @@
! of Tennessee Research Foundation. All rights ! of Tennessee Research Foundation. All rights
! reserved. ! reserved.
! Copyright (c) 2012 Inria. All rights reserved. ! Copyright (c) 2012 Inria. All rights reserved.
! Copyright (c) 2015-2017 Research Organization for Information Science ! Copyright (c) 2015-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -560,10 +560,10 @@ subroutine pompi_type_create_subarray_f(ndims,array_of_sizes, &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_create_subarray_f end subroutine pompi_type_create_subarray_f
subroutine pompi_type_dup_f(type,newtype,ierror) & subroutine pompi_type_dup_f(oldtype,newtype,ierror) &
BIND(C, name="pompi_type_dup_f") BIND(C, name="pompi_type_dup_f")
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: oldtype
INTEGER, INTENT(OUT) :: newtype INTEGER, INTENT(OUT) :: newtype
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_dup_f end subroutine pompi_type_dup_f
@ -1370,10 +1370,10 @@ subroutine pompi_type_create_keyval_f(type_copy_attr_fn,type_delete_attr_fn, &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_create_keyval_f end subroutine pompi_type_create_keyval_f
subroutine pompi_type_delete_attr_f(type,type_keyval,ierror) & subroutine pompi_type_delete_attr_f(datatype,type_keyval,ierror) &
BIND(C, name="pompi_type_delete_attr_f") BIND(C, name="pompi_type_delete_attr_f")
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_delete_attr_f end subroutine pompi_type_delete_attr_f
@ -1385,32 +1385,32 @@ subroutine pompi_type_free_keyval_f(type_keyval,ierror) &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_free_keyval_f end subroutine pompi_type_free_keyval_f
subroutine pompi_type_get_name_f(type,type_name,resultlen,ierror,type_name_len) & subroutine pompi_type_get_name_f(datatype,type_name,resultlen,ierror,type_name_len) &
BIND(C, name="pompi_type_get_name_f") BIND(C, name="pompi_type_get_name_f")
use, intrinsic :: ISO_C_BINDING, only : C_CHAR use, intrinsic :: ISO_C_BINDING, only : C_CHAR
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: type_name CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) :: type_name
INTEGER, INTENT(OUT) :: resultlen INTEGER, INTENT(OUT) :: resultlen
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
INTEGER, VALUE, INTENT(IN) :: type_name_len INTEGER, VALUE, INTENT(IN) :: type_name_len
end subroutine pompi_type_get_name_f end subroutine pompi_type_get_name_f
subroutine pompi_type_set_attr_f(type,type_keyval,attribute_val,ierror) & subroutine pompi_type_set_attr_f(datatype,type_keyval,attribute_val,ierror) &
BIND(C, name="pompi_type_set_attr_f") BIND(C, name="pompi_type_set_attr_f")
use :: mpi_f08_types, only : MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_ADDRESS_KIND
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_set_attr_f end subroutine pompi_type_set_attr_f
subroutine pompi_type_set_name_f(type,type_name,ierror,type_name_len) & subroutine pompi_type_set_name_f(datatype,type_name,ierror,type_name_len) &
BIND(C, name="pompi_type_set_name_f") BIND(C, name="pompi_type_set_name_f")
use, intrinsic :: ISO_C_BINDING, only : C_CHAR use, intrinsic :: ISO_C_BINDING, only : C_CHAR
implicit none implicit none
INTEGER, INTENT(IN) :: type INTEGER, INTENT(IN) :: datatype
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: type_name CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: type_name
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
INTEGER, VALUE, INTENT(IN) :: type_name_len INTEGER, VALUE, INTENT(IN) :: type_name_len
@ -3029,11 +3029,11 @@ subroutine pompi_type_create_f90_real_f(p,r,newtype,ierror) &
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_create_f90_real_f end subroutine pompi_type_create_f90_real_f
subroutine pompi_type_match_size_f(typeclass,size,type,ierror) & subroutine pompi_type_match_size_f(typeclass,size,datatype,ierror) &
BIND(C, name="pompi_type_match_size_f") BIND(C, name="pompi_type_match_size_f")
implicit none implicit none
INTEGER, INTENT(IN) :: typeclass, size INTEGER, INTENT(IN) :: typeclass, size
INTEGER, INTENT(OUT) :: type INTEGER, INTENT(OUT) :: datatype
INTEGER, INTENT(OUT) :: ierror INTEGER, INTENT(OUT) :: ierror
end subroutine pompi_type_match_size_f end subroutine pompi_type_match_size_f

Просмотреть файл

@ -3,18 +3,20 @@
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_delete_attr_f08(type,type_keyval,ierror) subroutine PMPI_Type_delete_attr_f08(datatype,type_keyval,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_delete_attr_f use :: mpi_f08, only : ompi_type_delete_attr_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_delete_attr_f(type%MPI_VAL,type_keyval,c_ierror) call ompi_type_delete_attr_f(datatype%MPI_VAL,type_keyval,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_delete_attr_f08 end subroutine PMPI_Type_delete_attr_f08

Просмотреть файл

@ -3,18 +3,20 @@
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_dup_f08(type,newtype,ierror) subroutine PMPI_Type_dup_f08(oldtype,newtype,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_dup_f use :: mpi_f08, only : ompi_type_dup_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: oldtype
TYPE(MPI_Datatype), INTENT(OUT) :: newtype TYPE(MPI_Datatype), INTENT(OUT) :: newtype
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_dup_f(type%MPI_VAL,newtype%MPI_VAL,c_ierror) call ompi_type_dup_f(oldtype%MPI_VAL,newtype%MPI_VAL,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_dup_f08 end subroutine PMPI_Type_dup_f08

Просмотреть файл

@ -3,21 +3,23 @@
! Copyright (c) 2009-2013 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2013 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_get_attr_f08(type,type_keyval,attribute_val,flag,ierror) subroutine PMPI_Type_get_attr_f08(datatype,type_keyval,attribute_val,flag,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND
! See note in mpi-f-interfaces-bind.h for why we "use mpi" here and ! See note in mpi-f-interfaces-bind.h for why we "use mpi" here and
! call a PMPI_* subroutine below. ! call a PMPI_* subroutine below.
use :: mpi, only : PMPI_Type_get_attr use :: mpi, only : PMPI_Type_get_attr
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(OUT) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(OUT) :: attribute_val
LOGICAL, INTENT(OUT) :: flag LOGICAL, INTENT(OUT) :: flag
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call PMPI_Type_get_attr(type%MPI_VAL,type_keyval,attribute_val,flag,c_ierror) call PMPI_Type_get_attr(datatype%MPI_VAL,type_keyval,attribute_val,flag,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_get_attr_f08 end subroutine PMPI_Type_get_attr_f08

Просмотреть файл

@ -3,19 +3,21 @@
! Copyright (c) 2010-2011 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2010-2011 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_get_name_f08(type,type_name,resultlen,ierror) subroutine PMPI_Type_get_name_f08(datatype,type_name,resultlen,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_MAX_OBJECT_NAME use :: mpi_f08_types, only : MPI_Datatype, MPI_MAX_OBJECT_NAME
use :: mpi_f08, only : ompi_type_get_name_f use :: mpi_f08, only : ompi_type_get_name_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
CHARACTER(LEN=*), INTENT(OUT) :: type_name CHARACTER(LEN=*), INTENT(OUT) :: type_name
INTEGER, INTENT(OUT) :: resultlen INTEGER, INTENT(OUT) :: resultlen
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_get_name_f(type%MPI_VAL,type_name,resultlen,c_ierror,len(type_name)) call ompi_type_get_name_f(datatype%MPI_VAL,type_name,resultlen,c_ierror,len(type_name))
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_get_name_f08 end subroutine PMPI_Type_get_name_f08

Просмотреть файл

@ -3,18 +3,20 @@
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All Rights reserved. ! All Rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_match_size_f08(typeclass,size,type,ierror) subroutine PMPI_Type_match_size_f08(typeclass,size,datatype,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_match_size_f use :: mpi_f08, only : ompi_type_match_size_f
implicit none implicit none
INTEGER, INTENT(IN) :: typeclass, size INTEGER, INTENT(IN) :: typeclass, size
TYPE(MPI_Datatype), INTENT(OUT) :: type TYPE(MPI_Datatype), INTENT(OUT) :: datatype
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_match_size_f(typeclass,size,type%MPI_VAL,c_ierror) call ompi_type_match_size_f(typeclass,size,datatype%MPI_VAL,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_match_size_f08 end subroutine PMPI_Type_match_size_f08

Просмотреть файл

@ -3,19 +3,21 @@
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_set_attr_f08(type,type_keyval,attribute_val,ierror) subroutine PMPI_Type_set_attr_f08(datatype,type_keyval,attribute_val,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND
use :: mpi_f08, only : ompi_type_set_attr_f use :: mpi_f08, only : ompi_type_set_attr_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_set_attr_f(type%MPI_VAL,type_keyval,attribute_val,c_ierror) call ompi_type_set_attr_f(datatype%MPI_VAL,type_keyval,attribute_val,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_set_attr_f08 end subroutine PMPI_Type_set_attr_f08

Просмотреть файл

@ -3,18 +3,20 @@
! Copyright (c) 2010-2011 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2010-2011 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine PMPI_Type_set_name_f08(type,type_name,ierror) subroutine PMPI_Type_set_name_f08(datatype,type_name,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_set_name_f use :: mpi_f08, only : ompi_type_set_name_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
CHARACTER(LEN=*), INTENT(IN) :: type_name CHARACTER(LEN=*), INTENT(IN) :: type_name
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_set_name_f(type%MPI_VAL,type_name,c_ierror,len(type_name)) call ompi_type_set_name_f(datatype%MPI_VAL,type_name,c_ierror,len(type_name))
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine PMPI_Type_set_name_f08 end subroutine PMPI_Type_set_name_f08

Просмотреть файл

@ -1,20 +1,20 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_delete_attr_f08(type,type_keyval,ierror) subroutine MPI_Type_delete_attr_f08(datatype,type_keyval,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_delete_attr_f use :: mpi_f08, only : ompi_type_delete_attr_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_delete_attr_f(type%MPI_VAL,type_keyval,c_ierror) call ompi_type_delete_attr_f(datatype%MPI_VAL,type_keyval,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_delete_attr_f08 end subroutine MPI_Type_delete_attr_f08

Просмотреть файл

@ -1,20 +1,20 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_dup_f08(type,newtype,ierror) subroutine MPI_Type_dup_f08(datatype,newtype,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_dup_f use :: mpi_f08, only : ompi_type_dup_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
TYPE(MPI_Datatype), INTENT(OUT) :: newtype TYPE(MPI_Datatype), INTENT(OUT) :: newtype
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_dup_f(type%MPI_VAL,newtype%MPI_VAL,c_ierror) call ompi_type_dup_f(datatype%MPI_VAL,newtype%MPI_VAL,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_dup_f08 end subroutine MPI_Type_dup_f08

Просмотреть файл

@ -1,23 +1,23 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2013 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_get_attr_f08(type,type_keyval,attribute_val,flag,ierror) subroutine MPI_Type_get_attr_f08(datatype,type_keyval,attribute_val,flag,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND
! See note in mpi-f-interfaces-bind.h for why we "use mpi" here and ! See note in mpi-f-interfaces-bind.h for why we "use mpi" here and
! call a PMPI_* subroutine below. ! call a PMPI_* subroutine below.
use :: mpi, only : PMPI_Type_get_attr use :: mpi, only : PMPI_Type_get_attr
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(OUT) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(OUT) :: attribute_val
LOGICAL, INTENT(OUT) :: flag LOGICAL, INTENT(OUT) :: flag
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call PMPI_Type_get_attr(type%MPI_VAL,type_keyval,attribute_val,flag,c_ierror) call PMPI_Type_get_attr(datatype%MPI_VAL,type_keyval,attribute_val,flag,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_get_attr_f08 end subroutine MPI_Type_get_attr_f08

Просмотреть файл

@ -1,21 +1,21 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_get_name_f08(type,type_name,resultlen,ierror) subroutine MPI_Type_get_name_f08(datatype,type_name,resultlen,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_MAX_OBJECT_NAME use :: mpi_f08_types, only : MPI_Datatype, MPI_MAX_OBJECT_NAME
use :: mpi_f08, only : ompi_type_get_name_f use :: mpi_f08, only : ompi_type_get_name_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
CHARACTER(LEN=*), INTENT(OUT) :: type_name CHARACTER(LEN=*), INTENT(OUT) :: type_name
INTEGER, INTENT(OUT) :: resultlen INTEGER, INTENT(OUT) :: resultlen
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_get_name_f(type%MPI_VAL,type_name,resultlen,c_ierror,len(type_name)) call ompi_type_get_name_f(datatype%MPI_VAL,type_name,resultlen,c_ierror,len(type_name))
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_get_name_f08 end subroutine MPI_Type_get_name_f08

Просмотреть файл

@ -1,20 +1,20 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All Rights reserved. ! All Rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_match_size_f08(typeclass,size,type,ierror) subroutine MPI_Type_match_size_f08(typeclass,size,datatype,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_match_size_f use :: mpi_f08, only : ompi_type_match_size_f
implicit none implicit none
INTEGER, INTENT(IN) :: typeclass, size INTEGER, INTENT(IN) :: typeclass, size
TYPE(MPI_Datatype), INTENT(OUT) :: type TYPE(MPI_Datatype), INTENT(OUT) :: datatype
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_match_size_f(typeclass,size,type%MPI_VAL,c_ierror) call ompi_type_match_size_f(typeclass,size,datatype%MPI_VAL,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_match_size_f08 end subroutine MPI_Type_match_size_f08

Просмотреть файл

@ -1,21 +1,21 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2009-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2009-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_set_attr_f08(type,type_keyval,attribute_val,ierror) subroutine MPI_Type_set_attr_f08(datatype,type_keyval,attribute_val,ierror)
use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND use :: mpi_f08_types, only : MPI_Datatype, MPI_ADDRESS_KIND
use :: mpi_f08, only : ompi_type_set_attr_f use :: mpi_f08, only : ompi_type_set_attr_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
INTEGER, INTENT(IN) :: type_keyval INTEGER, INTENT(IN) :: type_keyval
INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val INTEGER(MPI_ADDRESS_KIND), INTENT(IN) :: attribute_val
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_set_attr_f(type%MPI_VAL,type_keyval,attribute_val,c_ierror) call ompi_type_set_attr_f(datatype%MPI_VAL,type_keyval,attribute_val,c_ierror)
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_set_attr_f08 end subroutine MPI_Type_set_attr_f08

Просмотреть файл

@ -1,20 +1,20 @@
! -*- f90 -*- ! -*- f90 -*-
! !
! Copyright (c) 2010-2011 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2010-2018 Cisco Systems, Inc. All rights reserved
! Copyright (c) 2009-2012 Los Alamos National Security, LLC. ! Copyright (c) 2009-2012 Los Alamos National Security, LLC.
! All rights reserved. ! All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
subroutine MPI_Type_set_name_f08(type,type_name,ierror) subroutine MPI_Type_set_name_f08(datatype,type_name,ierror)
use :: mpi_f08_types, only : MPI_Datatype use :: mpi_f08_types, only : MPI_Datatype
use :: mpi_f08, only : ompi_type_set_name_f use :: mpi_f08, only : ompi_type_set_name_f
implicit none implicit none
TYPE(MPI_Datatype), INTENT(IN) :: type TYPE(MPI_Datatype), INTENT(IN) :: datatype
CHARACTER(LEN=*), INTENT(IN) :: type_name CHARACTER(LEN=*), INTENT(IN) :: type_name
INTEGER, OPTIONAL, INTENT(OUT) :: ierror INTEGER, OPTIONAL, INTENT(OUT) :: ierror
integer :: c_ierror integer :: c_ierror
call ompi_type_set_name_f(type%MPI_VAL,type_name,c_ierror,len(type_name)) call ompi_type_set_name_f(datatype%MPI_VAL,type_name,c_ierror,len(type_name))
if (present(ierror)) ierror = c_ierror if (present(ierror)) ierror = c_ierror
end subroutine MPI_Type_set_name_f08 end subroutine MPI_Type_set_name_f08

Просмотреть файл

@ -1,6 +1,6 @@
! -*- fortran -*- ! -*- fortran -*-
! !
! Copyright (c) 2006-2012 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2006-2018 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2007 Los Alamos National Security, LLC. All rights ! Copyright (c) 2007 Los Alamos National Security, LLC. All rights
! reserved. ! reserved.
! Copyright (c) 2012 The University of Tennessee and The University ! Copyright (c) 2012 The University of Tennessee and The University
@ -9,7 +9,7 @@
! Copyright (c) 2012 Inria. All rights reserved. ! Copyright (c) 2012 Inria. All rights reserved.
! Copyright (c) 2013-2015 Los Alamos National Security, LLC. All rights ! Copyright (c) 2013-2015 Los Alamos National Security, LLC. All rights
! reserved. ! reserved.
! Copyright (c) 2015 Research Organization for Information Science ! Copyright (c) 2015-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -6335,8 +6335,8 @@ end interface
interface MPI_Type_commit interface MPI_Type_commit
subroutine MPI_Type_commit(type, ierror) subroutine MPI_Type_commit(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_commit end subroutine MPI_Type_commit
@ -6344,8 +6344,8 @@ end interface
interface PMPI_Type_commit interface PMPI_Type_commit
subroutine PMPI_Type_commit(type, ierror) subroutine PMPI_Type_commit(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_commit end subroutine PMPI_Type_commit
@ -6723,8 +6723,8 @@ end interface
interface MPI_Type_delete_attr interface MPI_Type_delete_attr
subroutine MPI_Type_delete_attr(type, type_keyval, ierror) subroutine MPI_Type_delete_attr(datatype, type_keyval, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_delete_attr end subroutine MPI_Type_delete_attr
@ -6733,8 +6733,8 @@ end interface
interface PMPI_Type_delete_attr interface PMPI_Type_delete_attr
subroutine PMPI_Type_delete_attr(type, type_keyval, ierror) subroutine PMPI_Type_delete_attr(datatype, type_keyval, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_delete_attr end subroutine PMPI_Type_delete_attr
@ -6744,8 +6744,8 @@ end interface
interface MPI_Type_dup interface MPI_Type_dup
subroutine MPI_Type_dup(type, newtype, ierror) subroutine MPI_Type_dup(datatype, newtype, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: newtype integer, intent(out) :: newtype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_dup end subroutine MPI_Type_dup
@ -6754,8 +6754,8 @@ end interface
interface PMPI_Type_dup interface PMPI_Type_dup
subroutine PMPI_Type_dup(type, newtype, ierror) subroutine PMPI_Type_dup(datatype, newtype, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: newtype integer, intent(out) :: newtype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_dup end subroutine PMPI_Type_dup
@ -6765,8 +6765,8 @@ end interface
interface MPI_Type_extent interface MPI_Type_extent
subroutine MPI_Type_extent(type, extent, ierror) subroutine MPI_Type_extent(datatype, extent, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: extent integer, intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_extent end subroutine MPI_Type_extent
@ -6775,8 +6775,8 @@ end interface
interface PMPI_Type_extent interface PMPI_Type_extent
subroutine PMPI_Type_extent(type, extent, ierror) subroutine PMPI_Type_extent(datatype, extent, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: extent integer, intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_extent end subroutine PMPI_Type_extent
@ -6786,8 +6786,8 @@ end interface
interface MPI_Type_free interface MPI_Type_free
subroutine MPI_Type_free(type, ierror) subroutine MPI_Type_free(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_free end subroutine MPI_Type_free
@ -6795,8 +6795,8 @@ end interface
interface PMPI_Type_free interface PMPI_Type_free
subroutine PMPI_Type_free(type, ierror) subroutine PMPI_Type_free(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_free end subroutine PMPI_Type_free
@ -6824,9 +6824,9 @@ end interface
interface MPI_Type_get_attr interface MPI_Type_get_attr
subroutine MPI_Type_get_attr(type, type_keyval, attribute_val, flag, ierror) subroutine MPI_Type_get_attr(datatype, type_keyval, attribute_val, flag, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val
logical, intent(out) :: flag logical, intent(out) :: flag
@ -6837,9 +6837,9 @@ end interface
interface PMPI_Type_get_attr interface PMPI_Type_get_attr
subroutine PMPI_Type_get_attr(type, type_keyval, attribute_val, flag, ierror) subroutine PMPI_Type_get_attr(datatype, type_keyval, attribute_val, flag, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val
logical, intent(out) :: flag logical, intent(out) :: flag
@ -6851,10 +6851,10 @@ end interface
interface MPI_Type_get_contents interface MPI_Type_get_contents
subroutine MPI_Type_get_contents(mtype, max_integers, max_addresses, max_datatypes, array_of_integers, & subroutine MPI_Type_get_contents(datatype, max_integers, max_addresses, max_datatypes, array_of_integers, &
array_of_addresses, array_of_datatypes, ierror) array_of_addresses, array_of_datatypes, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(in) :: max_integers integer, intent(in) :: max_integers
integer, intent(in) :: max_addresses integer, intent(in) :: max_addresses
integer, intent(in) :: max_datatypes integer, intent(in) :: max_datatypes
@ -6868,10 +6868,10 @@ end interface
interface PMPI_Type_get_contents interface PMPI_Type_get_contents
subroutine PMPI_Type_get_contents(mtype, max_integers, max_addresses, max_datatypes, array_of_integers, & subroutine PMPI_Type_get_contents(datatype, max_integers, max_addresses, max_datatypes, array_of_integers, &
array_of_addresses, array_of_datatypes, ierror) array_of_addresses, array_of_datatypes, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(in) :: max_integers integer, intent(in) :: max_integers
integer, intent(in) :: max_addresses integer, intent(in) :: max_addresses
integer, intent(in) :: max_datatypes integer, intent(in) :: max_datatypes
@ -6886,9 +6886,9 @@ end interface
interface MPI_Type_get_envelope interface MPI_Type_get_envelope
subroutine MPI_Type_get_envelope(type, num_integers, num_addresses, num_datatypes, combiner& subroutine MPI_Type_get_envelope(datatype, num_integers, num_addresses, num_datatypes, combiner&
, ierror) , ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: num_integers integer, intent(out) :: num_integers
integer, intent(out) :: num_addresses integer, intent(out) :: num_addresses
integer, intent(out) :: num_datatypes integer, intent(out) :: num_datatypes
@ -6900,9 +6900,9 @@ end interface
interface PMPI_Type_get_envelope interface PMPI_Type_get_envelope
subroutine PMPI_Type_get_envelope(type, num_integers, num_addresses, num_datatypes, combiner& subroutine PMPI_Type_get_envelope(datatype, num_integers, num_addresses, num_datatypes, combiner&
, ierror) , ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: num_integers integer, intent(out) :: num_integers
integer, intent(out) :: num_addresses integer, intent(out) :: num_addresses
integer, intent(out) :: num_datatypes integer, intent(out) :: num_datatypes
@ -6915,9 +6915,9 @@ end interface
interface MPI_Type_get_extent interface MPI_Type_get_extent
subroutine MPI_Type_get_extent(type, lb, extent, ierror) subroutine MPI_Type_get_extent(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb
integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -6927,9 +6927,9 @@ end interface
interface PMPI_Type_get_extent interface PMPI_Type_get_extent
subroutine PMPI_Type_get_extent(type, lb, extent, ierror) subroutine PMPI_Type_get_extent(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb
integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -6940,9 +6940,9 @@ end interface
interface MPI_Type_get_extent_x interface MPI_Type_get_extent_x
subroutine MPI_Type_get_extent_x(type, lb, extent, ierror) subroutine MPI_Type_get_extent_x(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: lb integer(kind=MPI_COUNT_KIND), intent(out) :: lb
integer(kind=MPI_COUNT_KIND), intent(out) :: extent integer(kind=MPI_COUNT_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -6952,9 +6952,9 @@ end interface
interface PMPI_Type_get_extent_x interface PMPI_Type_get_extent_x
subroutine PMPI_Type_get_extent_x(type, lb, extent, ierror) subroutine PMPI_Type_get_extent_x(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: lb integer(kind=MPI_COUNT_KIND), intent(out) :: lb
integer(kind=MPI_COUNT_KIND), intent(out) :: extent integer(kind=MPI_COUNT_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -6965,8 +6965,8 @@ end interface
interface MPI_Type_get_name interface MPI_Type_get_name
subroutine MPI_Type_get_name(type, type_name, resultlen, ierror) subroutine MPI_Type_get_name(datatype, type_name, resultlen, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(out) :: type_name character(len=*), intent(out) :: type_name
integer, intent(out) :: resultlen integer, intent(out) :: resultlen
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -6976,8 +6976,8 @@ end interface
interface PMPI_Type_get_name interface PMPI_Type_get_name
subroutine PMPI_Type_get_name(type, type_name, resultlen, ierror) subroutine PMPI_Type_get_name(datatype, type_name, resultlen, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(out) :: type_name character(len=*), intent(out) :: type_name
integer, intent(out) :: resultlen integer, intent(out) :: resultlen
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -7125,8 +7125,8 @@ end interface
interface MPI_Type_lb interface MPI_Type_lb
subroutine MPI_Type_lb(type, lb, ierror) subroutine MPI_Type_lb(datatype, lb, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: lb integer, intent(out) :: lb
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_lb end subroutine MPI_Type_lb
@ -7135,8 +7135,8 @@ end interface
interface PMPI_Type_lb interface PMPI_Type_lb
subroutine PMPI_Type_lb(type, lb, ierror) subroutine PMPI_Type_lb(datatype, lb, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: lb integer, intent(out) :: lb
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_lb end subroutine PMPI_Type_lb
@ -7146,10 +7146,10 @@ end interface
interface MPI_Type_match_size interface MPI_Type_match_size
subroutine MPI_Type_match_size(typeclass, size, type, ierror) subroutine MPI_Type_match_size(typeclass, size, datatype, ierror)
integer, intent(in) :: typeclass integer, intent(in) :: typeclass
integer, intent(in) :: size integer, intent(in) :: size
integer, intent(out) :: type integer, intent(out) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_match_size end subroutine MPI_Type_match_size
@ -7157,10 +7157,10 @@ end interface
interface PMPI_Type_match_size interface PMPI_Type_match_size
subroutine PMPI_Type_match_size(typeclass, size, type, ierror) subroutine PMPI_Type_match_size(typeclass, size, datatype, ierror)
integer, intent(in) :: typeclass integer, intent(in) :: typeclass
integer, intent(in) :: size integer, intent(in) :: size
integer, intent(out) :: type integer, intent(out) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_match_size end subroutine PMPI_Type_match_size
@ -7169,9 +7169,9 @@ end interface
interface MPI_Type_set_attr interface MPI_Type_set_attr
subroutine MPI_Type_set_attr(type, type_keyval, attr_val, ierror) subroutine MPI_Type_set_attr(datatype, type_keyval, attr_val, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -7181,9 +7181,9 @@ end interface
interface PMPI_Type_set_attr interface PMPI_Type_set_attr
subroutine PMPI_Type_set_attr(type, type_keyval, attr_val, ierror) subroutine PMPI_Type_set_attr(datatype, type_keyval, attr_val, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -7194,8 +7194,8 @@ end interface
interface MPI_Type_set_name interface MPI_Type_set_name
subroutine MPI_Type_set_name(type, type_name, ierror) subroutine MPI_Type_set_name(datatype, type_name, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(in) :: type_name character(len=*), intent(in) :: type_name
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_set_name end subroutine MPI_Type_set_name
@ -7204,8 +7204,8 @@ end interface
interface PMPI_Type_set_name interface PMPI_Type_set_name
subroutine PMPI_Type_set_name(type, type_name, ierror) subroutine PMPI_Type_set_name(datatype, type_name, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(in) :: type_name character(len=*), intent(in) :: type_name
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_set_name end subroutine PMPI_Type_set_name
@ -7215,8 +7215,8 @@ end interface
interface MPI_Type_size interface MPI_Type_size
subroutine MPI_Type_size(type, size, ierror) subroutine MPI_Type_size(datatype, size, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: size integer, intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_size end subroutine MPI_Type_size
@ -7225,8 +7225,8 @@ end interface
interface PMPI_Type_size interface PMPI_Type_size
subroutine PMPI_Type_size(type, size, ierror) subroutine PMPI_Type_size(datatype, size, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: size integer, intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_size end subroutine PMPI_Type_size
@ -7236,9 +7236,9 @@ end interface
interface MPI_Type_size_x interface MPI_Type_size_x
subroutine MPI_Type_size_x(type, size, ierror) subroutine MPI_Type_size_x(datatype, size, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: size integer(kind=MPI_COUNT_KIND), intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_size_x end subroutine MPI_Type_size_x
@ -7247,9 +7247,9 @@ end interface
interface PMPI_Type_size_x interface PMPI_Type_size_x
subroutine PMPI_Type_size_x(type, size, ierror) subroutine PMPI_Type_size_x(datatype, size, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: size integer(kind=MPI_COUNT_KIND), intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_size_x end subroutine PMPI_Type_size_x
@ -7288,8 +7288,8 @@ end interface
interface MPI_Type_ub interface MPI_Type_ub
subroutine MPI_Type_ub(mtype, ub, ierror) subroutine MPI_Type_ub(datatype, ub, ierror)
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(out) :: ub integer, intent(out) :: ub
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_ub end subroutine MPI_Type_ub
@ -7298,8 +7298,8 @@ end interface
interface PMPI_Type_ub interface PMPI_Type_ub
subroutine PMPI_Type_ub(mtype, ub, ierror) subroutine PMPI_Type_ub(datatype, ub, ierror)
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(out) :: ub integer, intent(out) :: ub
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_ub end subroutine PMPI_Type_ub

Просмотреть файл

@ -11,7 +11,7 @@
! Copyright (c) 2004-2005 The Regents of the University of California. ! Copyright (c) 2004-2005 The Regents of the University of California.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2006-2014 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2006-2014 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2016 Research Organization for Information Science ! Copyright (c) 2016-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -1481,8 +1481,8 @@ end interface
interface MPI_Type_commit interface MPI_Type_commit
subroutine MPI_Type_commit(type, ierror) subroutine MPI_Type_commit(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_commit end subroutine MPI_Type_commit
@ -1666,8 +1666,8 @@ end interface
interface MPI_Type_delete_attr interface MPI_Type_delete_attr
subroutine MPI_Type_delete_attr(type, type_keyval, ierror) subroutine MPI_Type_delete_attr(datatype, type_keyval, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_delete_attr end subroutine MPI_Type_delete_attr
@ -1677,8 +1677,8 @@ end interface
interface MPI_Type_dup interface MPI_Type_dup
subroutine MPI_Type_dup(type, newtype, ierror) subroutine MPI_Type_dup(oldtype, newtype, ierror)
integer, intent(in) :: type integer, intent(in) :: oldtype
integer, intent(out) :: newtype integer, intent(out) :: newtype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_dup end subroutine MPI_Type_dup
@ -1688,8 +1688,8 @@ end interface
interface MPI_Type_extent interface MPI_Type_extent
subroutine MPI_Type_extent(type, extent, ierror) subroutine MPI_Type_extent(datatype, extent, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: extent integer, intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_extent end subroutine MPI_Type_extent
@ -1699,8 +1699,8 @@ end interface
interface MPI_Type_free interface MPI_Type_free
subroutine MPI_Type_free(type, ierror) subroutine MPI_Type_free(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_free end subroutine MPI_Type_free
@ -1719,9 +1719,9 @@ end interface
interface MPI_Type_get_attr interface MPI_Type_get_attr
subroutine MPI_Type_get_attr(type, type_keyval, attribute_val, flag, ierror) subroutine MPI_Type_get_attr(datatype, type_keyval, attribute_val, flag, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val
logical, intent(out) :: flag logical, intent(out) :: flag
@ -1733,10 +1733,10 @@ end interface
interface MPI_Type_get_contents interface MPI_Type_get_contents
subroutine MPI_Type_get_contents(mtype, max_integers, max_addresses, max_datatypes, array_of_integers, & subroutine MPI_Type_get_contents(datatype, max_integers, max_addresses, max_datatypes, array_of_integers, &
array_of_addresses, array_of_datatypes, ierror) array_of_addresses, array_of_datatypes, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(in) :: max_integers integer, intent(in) :: max_integers
integer, intent(in) :: max_addresses integer, intent(in) :: max_addresses
integer, intent(in) :: max_datatypes integer, intent(in) :: max_datatypes
@ -1751,9 +1751,9 @@ end interface
interface MPI_Type_get_envelope interface MPI_Type_get_envelope
subroutine MPI_Type_get_envelope(type, num_integers, num_addresses, num_datatypes, combiner& subroutine MPI_Type_get_envelope(datatype, num_integers, num_addresses, num_datatypes, combiner&
, ierror) , ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: num_integers integer, intent(out) :: num_integers
integer, intent(out) :: num_addresses integer, intent(out) :: num_addresses
integer, intent(out) :: num_datatypes integer, intent(out) :: num_datatypes
@ -1766,9 +1766,9 @@ end interface
interface MPI_Type_get_extent interface MPI_Type_get_extent
subroutine MPI_Type_get_extent(type, lb, extent, ierror) subroutine MPI_Type_get_extent(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb
integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1779,9 +1779,9 @@ end interface
interface MPI_Type_get_extent_x interface MPI_Type_get_extent_x
subroutine MPI_Type_get_extent_x(type, lb, extent, ierror) subroutine MPI_Type_get_extent_x(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: lb integer(kind=MPI_COUNT_KIND), intent(out) :: lb
integer(kind=MPI_COUNT_KIND), intent(out) :: extent integer(kind=MPI_COUNT_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1792,8 +1792,8 @@ end interface
interface MPI_Type_get_name interface MPI_Type_get_name
subroutine MPI_Type_get_name(type, type_name, resultlen, ierror) subroutine MPI_Type_get_name(datatype, type_name, resultlen, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(out) :: type_name character(len=*), intent(out) :: type_name
integer, intent(out) :: resultlen integer, intent(out) :: resultlen
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1875,8 +1875,8 @@ end interface
interface MPI_Type_lb interface MPI_Type_lb
subroutine MPI_Type_lb(type, lb, ierror) subroutine MPI_Type_lb(datatype, lb, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: lb integer, intent(out) :: lb
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_lb end subroutine MPI_Type_lb
@ -1886,10 +1886,10 @@ end interface
interface MPI_Type_match_size interface MPI_Type_match_size
subroutine MPI_Type_match_size(typeclass, size, type, ierror) subroutine MPI_Type_match_size(typeclass, size, datatype, ierror)
integer, intent(in) :: typeclass integer, intent(in) :: typeclass
integer, intent(in) :: size integer, intent(in) :: size
integer, intent(out) :: type integer, intent(out) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_match_size end subroutine MPI_Type_match_size
@ -1898,9 +1898,9 @@ end interface
interface MPI_Type_set_attr interface MPI_Type_set_attr
subroutine MPI_Type_set_attr(type, type_keyval, attr_val, ierror) subroutine MPI_Type_set_attr(datatype, type_keyval, attr_val, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1911,8 +1911,8 @@ end interface
interface MPI_Type_set_name interface MPI_Type_set_name
subroutine MPI_Type_set_name(type, type_name, ierror) subroutine MPI_Type_set_name(datatype, type_name, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(in) :: type_name character(len=*), intent(in) :: type_name
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_set_name end subroutine MPI_Type_set_name
@ -1922,8 +1922,8 @@ end interface
interface MPI_Type_size interface MPI_Type_size
subroutine MPI_Type_size(type, size, ierror) subroutine MPI_Type_size(datatype, size, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: size integer, intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_size end subroutine MPI_Type_size
@ -1933,9 +1933,9 @@ end interface
interface MPI_Type_size_x interface MPI_Type_size_x
subroutine MPI_Type_size_x(type, size, ierror) subroutine MPI_Type_size_x(datatype, size, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: size integer(kind=MPI_COUNT_KIND), intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_size_x end subroutine MPI_Type_size_x
@ -1960,8 +1960,8 @@ end interface
interface MPI_Type_ub interface MPI_Type_ub
subroutine MPI_Type_ub(mtype, ub, ierror) subroutine MPI_Type_ub(datatype, ub, ierror)
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(out) :: ub integer, intent(out) :: ub
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine MPI_Type_ub end subroutine MPI_Type_ub

Просмотреть файл

@ -10,8 +10,8 @@
! University of Stuttgart. All rights reserved. ! University of Stuttgart. All rights reserved.
! Copyright (c) 2004-2005 The Regents of the University of California. ! Copyright (c) 2004-2005 The Regents of the University of California.
! All rights reserved. ! All rights reserved.
! Copyright (c) 2006-2014 Cisco Systems, Inc. All rights reserved. ! Copyright (c) 2006-2018 Cisco Systems, Inc. All rights reserved.
! Copyright (c) 2016 Research Organization for Information Science ! Copyright (c) 2016-2018 Research Organization for Information Science
! and Technology (RIST). All rights reserved. ! and Technology (RIST). All rights reserved.
! $COPYRIGHT$ ! $COPYRIGHT$
! !
@ -1481,8 +1481,8 @@ end interface
interface PMPI_Type_commit interface PMPI_Type_commit
subroutine PMPI_Type_commit(type, ierror) subroutine PMPI_Type_commit(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_commit end subroutine PMPI_Type_commit
@ -1666,8 +1666,8 @@ end interface
interface PMPI_Type_delete_attr interface PMPI_Type_delete_attr
subroutine PMPI_Type_delete_attr(type, type_keyval, ierror) subroutine PMPI_Type_delete_attr(datatype, type_keyval, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_delete_attr end subroutine PMPI_Type_delete_attr
@ -1677,8 +1677,8 @@ end interface
interface PMPI_Type_dup interface PMPI_Type_dup
subroutine PMPI_Type_dup(type, newtype, ierror) subroutine PMPI_Type_dup(datatype, newtype, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: newtype integer, intent(out) :: newtype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_dup end subroutine PMPI_Type_dup
@ -1688,8 +1688,8 @@ end interface
interface PMPI_Type_extent interface PMPI_Type_extent
subroutine PMPI_Type_extent(type, extent, ierror) subroutine PMPI_Type_extent(datatype, extent, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: extent integer, intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_extent end subroutine PMPI_Type_extent
@ -1699,8 +1699,8 @@ end interface
interface PMPI_Type_free interface PMPI_Type_free
subroutine PMPI_Type_free(type, ierror) subroutine PMPI_Type_free(datatype, ierror)
integer, intent(inout) :: type integer, intent(inout) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_free end subroutine PMPI_Type_free
@ -1719,9 +1719,9 @@ end interface
interface PMPI_Type_get_attr interface PMPI_Type_get_attr
subroutine PMPI_Type_get_attr(type, type_keyval, attribute_val, flag, ierror) subroutine PMPI_Type_get_attr(datatype, type_keyval, attribute_val, flag, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val integer(kind=MPI_ADDRESS_KIND), intent(out) :: attribute_val
logical, intent(out) :: flag logical, intent(out) :: flag
@ -1733,10 +1733,10 @@ end interface
interface PMPI_Type_get_contents interface PMPI_Type_get_contents
subroutine PMPI_Type_get_contents(mtype, max_integers, max_addresses, max_datatypes, array_of_integers, & subroutine PMPI_Type_get_contents(datatype, max_integers, max_addresses, max_datatypes, array_of_integers, &
array_of_addresses, array_of_datatypes, ierror) array_of_addresses, array_of_datatypes, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(in) :: max_integers integer, intent(in) :: max_integers
integer, intent(in) :: max_addresses integer, intent(in) :: max_addresses
integer, intent(in) :: max_datatypes integer, intent(in) :: max_datatypes
@ -1751,9 +1751,9 @@ end interface
interface PMPI_Type_get_envelope interface PMPI_Type_get_envelope
subroutine PMPI_Type_get_envelope(type, num_integers, num_addresses, num_datatypes, combiner& subroutine PMPI_Type_get_envelope(datatype, num_integers, num_addresses, num_datatypes, combiner&
, ierror) , ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: num_integers integer, intent(out) :: num_integers
integer, intent(out) :: num_addresses integer, intent(out) :: num_addresses
integer, intent(out) :: num_datatypes integer, intent(out) :: num_datatypes
@ -1766,9 +1766,9 @@ end interface
interface PMPI_Type_get_extent interface PMPI_Type_get_extent
subroutine PMPI_Type_get_extent(type, lb, extent, ierror) subroutine PMPI_Type_get_extent(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb integer(kind=MPI_ADDRESS_KIND), intent(out) :: lb
integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent integer(kind=MPI_ADDRESS_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1779,9 +1779,9 @@ end interface
interface PMPI_Type_get_extent_x interface PMPI_Type_get_extent_x
subroutine PMPI_Type_get_extent_x(type, lb, extent, ierror) subroutine PMPI_Type_get_extent_x(datatype, lb, extent, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: lb integer(kind=MPI_COUNT_KIND), intent(out) :: lb
integer(kind=MPI_COUNT_KIND), intent(out) :: extent integer(kind=MPI_COUNT_KIND), intent(out) :: extent
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1792,8 +1792,8 @@ end interface
interface PMPI_Type_get_name interface PMPI_Type_get_name
subroutine PMPI_Type_get_name(type, type_name, resultlen, ierror) subroutine PMPI_Type_get_name(datatype, type_name, resultlen, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(out) :: type_name character(len=*), intent(out) :: type_name
integer, intent(out) :: resultlen integer, intent(out) :: resultlen
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1875,8 +1875,8 @@ end interface
interface PMPI_Type_lb interface PMPI_Type_lb
subroutine PMPI_Type_lb(type, lb, ierror) subroutine PMPI_Type_lb(datatype, lb, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: lb integer, intent(out) :: lb
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_lb end subroutine PMPI_Type_lb
@ -1886,10 +1886,10 @@ end interface
interface PMPI_Type_match_size interface PMPI_Type_match_size
subroutine PMPI_Type_match_size(typeclass, size, type, ierror) subroutine PMPI_Type_match_size(typeclass, size, datatype, ierror)
integer, intent(in) :: typeclass integer, intent(in) :: typeclass
integer, intent(in) :: size integer, intent(in) :: size
integer, intent(out) :: type integer, intent(out) :: datatype
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_match_size end subroutine PMPI_Type_match_size
@ -1898,9 +1898,9 @@ end interface
interface PMPI_Type_set_attr interface PMPI_Type_set_attr
subroutine PMPI_Type_set_attr(type, type_keyval, attr_val, ierror) subroutine PMPI_Type_set_attr(datatype, type_keyval, attr_val, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(in) :: type_keyval integer, intent(in) :: type_keyval
integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val integer(kind=MPI_ADDRESS_KIND), intent(in) :: attr_val
integer, intent(out) :: ierror integer, intent(out) :: ierror
@ -1911,8 +1911,8 @@ end interface
interface PMPI_Type_set_name interface PMPI_Type_set_name
subroutine PMPI_Type_set_name(type, type_name, ierror) subroutine PMPI_Type_set_name(datatype, type_name, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
character(len=*), intent(in) :: type_name character(len=*), intent(in) :: type_name
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_set_name end subroutine PMPI_Type_set_name
@ -1922,8 +1922,8 @@ end interface
interface PMPI_Type_size interface PMPI_Type_size
subroutine PMPI_Type_size(type, size, ierror) subroutine PMPI_Type_size(datatype, size, ierror)
integer, intent(in) :: type integer, intent(in) :: datatype
integer, intent(out) :: size integer, intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_size end subroutine PMPI_Type_size
@ -1933,9 +1933,9 @@ end interface
interface PMPI_Type_size_x interface PMPI_Type_size_x
subroutine PMPI_Type_size_x(type, size, ierror) subroutine PMPI_Type_size_x(datatype, size, ierror)
include 'mpif-config.h' include 'mpif-config.h'
integer, intent(in) :: type integer, intent(in) :: datatype
integer(kind=MPI_COUNT_KIND), intent(out) :: size integer(kind=MPI_COUNT_KIND), intent(out) :: size
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_size_x end subroutine PMPI_Type_size_x
@ -1960,8 +1960,8 @@ end interface
interface PMPI_Type_ub interface PMPI_Type_ub
subroutine PMPI_Type_ub(mtype, ub, ierror) subroutine PMPI_Type_ub(datatype, ub, ierror)
integer, intent(in) :: mtype integer, intent(in) :: datatype
integer, intent(out) :: ub integer, intent(out) :: ub
integer, intent(out) :: ierror integer, intent(out) :: ierror
end subroutine PMPI_Type_ub end subroutine PMPI_Type_ub