@@ -21,6 +21,7 @@ module mpi
21
21
real (8 ), parameter :: MPI_IN_PLACE = - 1002
22
22
integer , parameter :: MPI_SUM = - 2300
23
23
integer , parameter :: MPI_MAX = - 2301
24
+ integer , parameter :: MPI_LOR = - 2302
24
25
integer , parameter :: MPI_INFO_NULL = - 2000
25
26
integer , parameter :: MPI_STATUS_SIZE = 5
26
27
integer :: MPI_STATUS_IGNORE = 0
@@ -99,6 +100,7 @@ module mpi
99
100
module procedure MPI_Allreduce_1D_recv_proc
100
101
module procedure MPI_Allreduce_1D_real_proc
101
102
module procedure MPI_Allreduce_1D_int_proc
103
+ module procedure MPI_Allreduce_scalar_logical_proc
102
104
end interface
103
105
104
106
interface MPI_Gatherv
@@ -168,14 +170,16 @@ module mpi
168
170
contains
169
171
170
172
integer (kind= MPI_HANDLE_KIND) function handle_mpi_op_f2c(op_f) result(c_op)
171
- use mpi_c_bindings, only: c_mpi_op_f2c, c_mpi_sum, c_mpi_max
173
+ use mpi_c_bindings, only: c_mpi_op_f2c, c_mpi_sum, c_mpi_max, c_mpi_lor
172
174
integer , intent (in ) :: op_f
173
175
if (op_f == MPI_SUM) then
174
176
c_op = c_mpi_sum
175
177
else if (op_f == MPI_MAX) then
176
178
c_op = c_MPI_MAX
179
+ else if (op_f == MPI_LOR) then
180
+ c_op = c_mpi_lor
177
181
else
178
- c_op = c_mpi_op_f2c(op_f)
182
+ c_op = c_mpi_op_f2c(op_f) ! For other operations, use the C binding
179
183
end if
180
184
end function
181
185
@@ -795,6 +799,35 @@ subroutine MPI_Allreduce_1D_int_proc(sendbuf, recvbuf, count, datatype, op, comm
795
799
end if
796
800
end subroutine MPI_Allreduce_1D_int_proc
797
801
802
+ subroutine MPI_Allreduce_scalar_logical_proc (sendbuf , recvbuf , count , datatype , op , comm , ierror )
803
+ use iso_c_binding, only: c_int, c_ptr, c_loc
804
+ use mpi_c_bindings, only: c_mpi_allreduce, c_mpi_comm_f2c
805
+ logical , intent (in ), target :: sendbuf
806
+ logical , intent (out ), target :: recvbuf
807
+ integer , intent (in ) :: count, datatype, op, comm
808
+ integer , intent (out ), optional :: ierror
809
+ type (c_ptr) :: sendbuf_ptr, recvbuf_ptr
810
+ integer (kind= MPI_HANDLE_KIND) :: c_datatype, c_op, c_comm
811
+ integer (c_int) :: local_ierr
812
+
813
+ sendbuf_ptr = c_loc(sendbuf)
814
+ recvbuf_ptr = c_loc(recvbuf)
815
+ c_datatype = handle_mpi_datatype_f2c(datatype)
816
+ c_op = handle_mpi_op_f2c(op)
817
+
818
+ c_comm = handle_mpi_comm_f2c(comm)
819
+
820
+ local_ierr = c_mpi_allreduce(sendbuf_ptr, recvbuf_ptr, count, c_datatype, c_op, c_comm)
821
+
822
+ if (present (ierror)) then
823
+ ierror = local_ierr
824
+ else
825
+ if (local_ierr /= MPI_SUCCESS) then
826
+ print * , " MPI_Allreduce_1D_recv_proc failed with error code: " , local_ierr
827
+ end if
828
+ end if
829
+ end subroutine MPI_Allreduce_scalar_logical_proc
830
+
798
831
function MPI_Wtime_proc () result(time)
799
832
use mpi_c_bindings, only: c_mpi_wtime
800
833
real (8 ) :: time
0 commit comments