TABLE OF CONTENTS


ABINIT/xmpi_land_log0d [ Functions ]

[ Top ] [ Functions ]

NAME

  xmpi_land_log0d

FUNCTION

  Logical AND accross the nodes.
  Combines value from all processes and distribute the result back to all processes.
  Target: logical scalar 

SOURCE

13 subroutine xmpi_land_log0d(xval, comm)
14 
15 !Arguments ------------------------------------
16  logical,intent(inout) :: xval
17  integer,intent(in) :: comm
18 
19 !Local variables-------------------------------
20  integer :: ierr
21 #if defined HAVE_MPI
22  logical :: out_val(1)
23 #endif
24 
25 ! *************************************************************************
26 
27  ierr=0
28 #if defined HAVE_MPI
29  if (comm /= MPI_COMM_SELF .and. comm /= MPI_COMM_NULL) then
30    call MPI_ALLREDUCE([xval], out_val, 1, MPI_LOGICAL, MPI_LAND, comm, ierr)
31    xval = out_val(1)
32  end if
33 #endif
34 
35 end subroutine xmpi_land_log0d

ABINIT/xmpi_lor_log1d [ Functions ]

[ Top ] [ Functions ]

NAME

  xmpi_lor_log1d

FUNCTION

  Combines values from all processes and distribute
  the result back to all processes.
  Target: one-dimensional logical arrays.

INPUTS

  comm= MPI communicator

SIDE EFFECTS

  xval= buffer array

SOURCE

57 subroutine xmpi_lor_log1d(xval,comm)
58 
59 !Arguments ------------------------------------
60  integer,intent(in) :: comm
61  logical, DEV_CONTARRD intent(inout) :: xval(:)
62 
63 !Local variables-------------------------------
64 #if defined HAVE_MPI
65  integer :: ierr,n1
66  logical,allocatable :: xsum(:)
67 #endif
68 
69 ! *************************************************************************
70 
71 #if defined HAVE_MPI
72  if (comm /= MPI_COMM_SELF .and. comm /= MPI_COMM_NULL) then
73 !  Accumulate xval on all proc. in comm
74    n1 = size(xval)
75    ABI_STAT_MALLOC(xsum,(n1), ierr)
76    if (ierr/= 0) call xmpi_abort(msg='error allocating xsum in xmpi_lor_log1d')
77    call MPI_ALLREDUCE(xval,xsum,n1,MPI_LOGICAL,MPI_LOR,comm,ierr)
78    xval (:) = xsum(:)
79    ABI_FREE(xsum)
80  end if
81 #endif
82 
83 end subroutine xmpi_lor_log1d

ABINIT/xmpi_lor_log2d [ Functions ]

[ Top ] [ Functions ]

NAME

  xmpi_lor_log2d

FUNCTION

  Combines values from all processes and distribute
  the result back to all processes.
  Target: two-dimensional logical arrays.

INPUTS

  comm= MPI communicator

SIDE EFFECTS

  xval= buffer array

SOURCE

105 subroutine xmpi_lor_log2d(xval,comm)
106 
107 !Arguments ------------------------------------
108  integer,intent(in) :: comm
109  logical, DEV_CONTARRD intent(inout) :: xval(:,:)
110 
111 !Local variables-------------------------------
112 #if defined HAVE_MPI
113  integer :: my_dt,my_op,n1,n2,ierr
114  integer(kind=int64) :: ntot
115  logical,allocatable :: xsum(:,:)
116 #endif
117 
118 ! *************************************************************************
119 
120 #if defined HAVE_MPI
121  if (comm /= MPI_COMM_SELF .and. comm /= MPI_COMM_NULL) then
122 !  Accumulate xval on all proc. in comm
123    n1 = size(xval,1)
124    n2 = size(xval,2)
125 
126    ABI_STAT_MALLOC(xsum,(n1,n2), ierr)
127    if (ierr/= 0) call xmpi_abort(msg='error allocating xsum in xmpi_lor_log2d')
128 
129    !This product of dimensions can be greater than a 32bit integer
130    !We use a INT64 to store it. If it is too large, we switch to an
131    !alternate routine because MPI<4 doesnt handle 64 bit counts.
132    ntot=int(n1*n2,kind=int64)
133 
134    if (ntot<=xmpi_maxint32_64) then
135      call MPI_ALLREDUCE(xval,xsum,n1*n2,MPI_LOGICAL,MPI_LOR,comm,ierr)
136    else
137      call xmpi_largetype_create(ntot,MPI_LOGICAL,my_dt,my_op,MPI_LOR)
138      call MPI_ALLREDUCE(xval,xsum,1,my_dt,my_op,comm,ierr)
139      call xmpi_largetype_free(my_dt,my_op)
140    end if
141 
142    xval (:,:) = xsum(:,:)
143    ABI_FREE(xsum)
144  end if
145 #endif
146 
147 end subroutine xmpi_lor_log2d

ABINIT/xmpi_lor_log3d [ Functions ]

[ Top ] [ Functions ]

NAME

  xmpi_lor_log3d

FUNCTION

  Combines values from all processes and distribute
  the result back to all processes.
  Target: three-dimensional logical arrays.

INPUTS

  comm= MPI communicator

SIDE EFFECTS

  xval= buffer array

SOURCE

169 subroutine xmpi_lor_log3d(xval,comm)
170 
171 !Arguments ------------------------------------
172  integer,intent(in) :: comm
173  logical, DEV_CONTARRD intent(inout) :: xval(:,:,:)
174 
175 !Local variables-------------------------------
176 #if defined HAVE_MPI
177  integer :: my_dt,my_op,n1,n2,n3,ierr
178  integer(kind=int64) :: ntot
179  logical,allocatable :: xsum(:,:,:)
180 #endif
181 
182 ! *************************************************************************
183 
184 #if defined HAVE_MPI
185  if (comm /= MPI_COMM_SELF .and. comm /= MPI_COMM_NULL) then
186 !  Accumulate xval on all proc. in comm
187    n1 = size(xval,1)
188    n2 = size(xval,2)
189    n3 = size(xval,3)
190 
191 !  #if defined HAVE_MPI2_INPLACE
192 !  call MPI_ALLREDUCE(MPI_IN_PLACE,xval,n1*n2*n3,MPI_LOGICAL,MPI_LOR,comm,ierr)
193 !  #else
194    ABI_STAT_MALLOC(xsum,(n1,n2,n3), ierr)
195    if (ierr/= 0) call xmpi_abort(msg='error allocating xsum in xmpi_lor_log3d')
196 
197    !This product of dimensions can be greater than a 32bit integer
198    !We use a INT64 to store it. If it is too large, we switch to an
199    !alternate routine because MPI<4 doesnt handle 64 bit counts.
200    ntot=int(n1*n2*n3,kind=int64)
201 
202    if (ntot<=xmpi_maxint32_64) then
203      call MPI_ALLREDUCE(xval,xsum,n1*n2*n3,MPI_LOGICAL,MPI_LOR,comm,ierr)
204    else
205      call xmpi_largetype_create(ntot,MPI_LOGICAL,my_dt,my_op,MPI_LOR)
206      call MPI_ALLREDUCE(xval,xsum,1,my_dt,my_op,comm,ierr)
207      call xmpi_largetype_free(my_dt,my_op)
208    end if
209 
210    xval (:,:,:) = xsum(:,:,:)
211    ABI_FREE(xsum)
212 !  #endif
213  end if
214 #endif
215 
216 end subroutine xmpi_lor_log3d