16 REAL,
intent(in) :: PIV
17 REAL,
intent(inout) :: DETER
18 INTEGER,
intent(inout) :: NEXP
19 deter=deter*fraction(piv)
20 nexp=nexp+exponent(piv)+exponent(deter)
26 REAL,
intent(in) :: PIV
27 REAL,
intent(inout) :: DETER
28 INTEGER,
intent(inout) :: NEXP
29 deter=deter*fraction(piv)
30 nexp=nexp+exponent(piv)+exponent(deter)
35 & MYROW, MYCOL, NPROW, NPCOL,
36 & A, LOCAL_M, LOCAL_N, N, MYID,
39 INTEGER,
intent (in) :: SYM
40 INTEGER,
intent (inout) :: NEXP
41 REAL,
intent (inout) :: DETER
42 INTEGER,
intent (in) :: BLOCK_SIZE, NPROW, NPCOL,
44 INTEGER,
intent (in) :: MYROW, MYCOL, MYID, IPIV(LOCAL_M)
45 REAL,
intent(in) :: A(*)
46 INTEGER I,IMX,DI,NBLOCK,IBLOCK,ILOC,JLOC,
47 & row_proc,col_proc, k
49 nblock = ( n - 1 ) / block_size
51 row_proc = mod( iblock, nprow )
52 IF ( myrow.EQ.row_proc )
THEN
53 col_proc = mod( iblock, npcol )
54 IF ( mycol.EQ.col_proc )
THEN
55 iloc = ( iblock / nprow ) * block_size
56 jloc = ( iblock / npcol ) * block_size
57 i = iloc + jloc * local_m + 1
58 imx =
min(iloc+block_size,local_m)
59 & + (
min(jloc+block_size,local_n)-1)*local_m
62 DO WHILE ( i .LT. imx )
68 IF (ipiv(iloc+k) .NE. iblock*block_size+k)
THEN
81 & COMM, DETER_IN, NEXP_IN,
82 & DETER_OUT, NEXP_OUT, NPROCS)
84 INTEGER,
intent(in) :: COMM, NPROCS
85 REAL,
intent(in) :: DETER_IN
86 INTEGER,
intent(in) :: NEXP_IN
87 REAL,
intent(out):: DETER_OUT
88 INTEGER,
intent(out):: NEXP_OUT
91 INTEGER TWO_SCALARS_TYPE, DETERREDUCE_OP
95 IF (nprocs .EQ. 1)
THEN
111 & deterreduce_op, comm, ierr_mpi)
115 nexp_out = int(outv(2))
120#if defined(WORKAROUNDINTELILP64MPI2INTEGER) || defined(WORKAROUNDILP64MPICUSTOMREDUCE)
121 INTEGER(4),
INTENT(IN) :: NEL, DATATYPE
123 INTEGER,
INTENT(IN) :: NEL, DATATYPE
125 REAL,
INTENT(IN) :: INV ( 2 * NEL )
126 REAL,
INTENT(INOUT) :: INOUTV ( 2 * NEL )
127 INTEGER I, TMPEXPIN, TMPEXPINOUT
129 tmpexpin = int(inv (i*2))
130 tmpexpinout = int(inoutv(i*2))
134 tmpexpinout = tmpexpinout + tmpexpin
135 inoutv(i*2) = real(tmpexpinout)
141 INTEGER,
intent (inout) :: NEXP
142 REAL,
intent (inout) :: DETER
149 INTEGER,
intent (inout) :: NEXP
150 REAL,
intent (inout) :: DETER
157 REAL,
intent(inout) :: DETER
158 INTEGER,
intent(in) :: N
159 INTEGER,
intent(inout) :: VISITED(N)
160 INTEGER,
intent(in) :: PERM(N)
164 IF (visited(i) .GT. n)
THEN
165 visited(i)=visited(i)-n-n-1
170 visited(j) = visited(j) + n + n + 1
175 IF (mod(k,2).EQ.1)
THEN
182 & MYROW, MYCOL, NPROW, NPCOL,
183 & A, LOCAL_M, LOCAL_N, N, MYID,
188 INTEGER,
intent (in) :: BLOCK_SIZE, NPROW, NPCOL,
189 & local_m, local_n, n, sym
190 INTEGER,
intent (in) :: , MYCOL, MYID, IPIV(LOCAL_M)
191 REAL,
intent(in) :: (*)
192 REAL,
INTENT(INOUT) :: DKEEP(230)
193 INTEGER,
INTENT(IN) :: KEEP(500)
194 INTEGER I,IMX,DI,NBLOCK,IBLOCK,ILOC,JLOC,
198 nblock = ( n - 1 ) / block_size
199 DO iblock = 0, nblock
200 row_proc = mod( iblock, nprow )
201 IF ( myrow.EQ.row_proc )
THEN
202 col_proc = mod( iblock, npcol )
203 IF ( mycol.EQ.col_proc )
THEN
204 iloc = ( iblock / nprow ) * block_size
205 jloc = ( iblock / npcol ) * block_size
206 i = iloc + jloc * local_m + 1
207 imx =
min(iloc+block_size,local_m)
208 & + (
min(jloc+block_size,local_n)-1)*local_m
211 DO WHILE ( i .LT. imx )
215 abspivot = abs(a(i)*a(i))
subroutine mpi_type_free(newtyp, ierr_mpi)
subroutine mpi_type_contiguous(length, datatype, newtype, ierr_mpi)
subroutine mpi_allreduce(sendbuf, recvbuf, cnt, datatype, operation, comm, ierr)
subroutine mpi_type_commit(newtyp, ierr_mpi)
subroutine mpi_op_create(func, commute, op, ierr)
subroutine mpi_op_free(op, ierr)
subroutine smumps_update_minmax_pivot(diag, dkeep, keep, nullpivot)
subroutine smumps_deter_sign_perm(deter, n, visited, perm)
subroutine smumps_updatedeter(piv, deter, nexp)
subroutine smumps_deterreduce_func(inv, inoutv, nel, datatype)
subroutine smumps_deter_square(deter, nexp)
subroutine smumps_deter_scaling_inverse(deter, nexp)
subroutine smumps_deter_reduction(comm, deter_in, nexp_in, deter_out, nexp_out, nprocs)
subroutine smumps_par_root_minmax_piv_upd(block_size, ipiv, myrow, mycol, nprow, npcol, a, local_m, local_n, n, myid, dkeep, keep, sym)
subroutine smumps_updatedeter_scaling(piv, deter, nexp)
subroutine smumps_getdeter2d(block_size, ipiv, myrow, mycol, nprow, npcol, a, local_m, local_n, n, myid, deter, nexp, sym)