OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dfac_determinant.F
Go to the documentation of this file.
1C
2C This file is part of MUMPS 5.5.1, released
3C on Tue Jul 12 13:17:24 UTC 2022
4C
5C
6C Copyright 1991-2022 CERFACS, CNRS, ENS Lyon, INP Toulouse, Inria,
7C Mumps Technologies, University of Bordeaux.
8C
9C This version of MUMPS is provided to you free of charge. It is
10C released under the CeCILL-C license
11C (see doc/CeCILL-C_V1-en.txt, doc/CeCILL-C_V1-fr.txt, and
12C https://cecill.info/licences/Licence_CeCILL-C_V1-en.html)
13C
14 SUBROUTINE dmumps_updatedeter(PIV, DETER, NEXP)
15 IMPLICIT NONE
16 DOUBLE PRECISION, intent(in) :: PIV
17 DOUBLE PRECISION, intent(inout) :: DETER
18 INTEGER, intent(inout) :: NEXP
19 deter=deter*fraction(piv)
20 nexp=nexp+exponent(piv)+exponent(deter)
21 deter=fraction(deter)
22 RETURN
23 END SUBROUTINE dmumps_updatedeter
24 SUBROUTINE dmumps_updatedeter_scaling(PIV, DETER, NEXP)
25 IMPLICIT NONE
26 DOUBLE PRECISION, intent(in) :: PIV
27 DOUBLE PRECISION, intent(inout) :: DETER
28 INTEGER, intent(inout) :: NEXP
29 deter=deter*fraction(piv)
30 nexp=nexp+exponent(piv)+exponent(deter)
31 deter=fraction(deter)
32 RETURN
33 END SUBROUTINE dmumps_updatedeter_scaling
34 SUBROUTINE dmumps_getdeter2d(BLOCK_SIZE,IPIV,
35 & MYROW, MYCOL, NPROW, NPCOL,
36 & A, LOCAL_M, LOCAL_N, N, MYID,
37 & DETER,NEXP,SYM)
38 IMPLICIT NONE
39 INTEGER, intent (in) :: SYM
40 INTEGER, intent (inout) :: NEXP
41 DOUBLE PRECISION, intent (inout) :: DETER
42 INTEGER, intent (in) :: BLOCK_SIZE, NPROW, NPCOL,
43 & local_m, local_n, n
44 INTEGER, intent (in) :: MYROW, MYCOL, MYID, IPIV(LOCAL_M)
45 DOUBLE PRECISION, intent(in) :: A(*)
46 INTEGER I,IMX,DI,NBLOCK,IBLOCK,ILOC,JLOC,
47 & row_proc,col_proc, k
48 di = local_m + 1
49 nblock = ( n - 1 ) / block_size
50 DO iblock = 0, nblock
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
60 & + 1
61 k=1
62 DO WHILE ( i .LT. imx )
63 CALL dmumps_updatedeter(a(i),deter,nexp)
64 IF (sym.EQ.1) THEN
65 CALL dmumps_updatedeter(a(i),deter,nexp)
66 ENDIF
67 IF (sym.NE.1) THEN
68 IF (ipiv(iloc+k) .NE. iblock*block_size+k) THEN
69 deter = -deter
70 ENDIF
71 ENDIF
72 k = k + 1
73 i = i + di
74 END DO
75 END IF
76 END IF
77 END DO
78 RETURN
79 END SUBROUTINE dmumps_getdeter2d
81 & COMM, DETER_IN, NEXP_IN,
82 & DETER_OUT, NEXP_OUT, NPROCS)
83 IMPLICIT NONE
84 INTEGER, intent(in) :: COMM, NPROCS
85 DOUBLE PRECISION, intent(in) :: DETER_IN
86 INTEGER,intent(in) :: NEXP_IN
87 DOUBLE PRECISION,intent(out):: DETER_OUT
88 INTEGER,intent(out):: NEXP_OUT
89 INTEGER :: IERR_MPI
91 INTEGER TWO_SCALARS_TYPE, DETERREDUCE_OP
92 DOUBLE PRECISION :: INV(2)
93 DOUBLE PRECISION :: OUTV(2)
94 include 'mpif.h'
95 IF (nprocs .EQ. 1) THEN
96 deter_out = deter_in
97 nexp_out = nexp_in
98 RETURN
99 ENDIF
100 CALL mpi_type_contiguous(2, mpi_double_precision,
101 & two_scalars_type,
102 & ierr_mpi)
103 CALL mpi_type_commit(two_scalars_type, ierr_mpi)
105 & .true.,
106 & deterreduce_op,
107 & ierr_mpi)
108 inv(1)=deter_in
109 inv(2)=dble(nexp_in)
110 CALL mpi_allreduce( inv, outv, 1, two_scalars_type,
111 & deterreduce_op, comm, ierr_mpi)
112 CALL mpi_op_free(deterreduce_op, ierr_mpi)
113 CALL mpi_type_free(two_scalars_type, ierr_mpi)
114 deter_out = outv(1)
115 nexp_out = int(outv(2))
116 RETURN
117 END SUBROUTINE dmumps_deter_reduction
118 SUBROUTINE dmumps_deterreduce_func(INV, INOUTV, NEL, DATATYPE)
119 IMPLICIT NONE
120#if defined(WORKAROUNDINTELILP64MPI2INTEGER) || defined(WORKAROUNDILP64MPICUSTOMREDUCE)
121 INTEGER(4), INTENT(IN) :: NEL, DATATYPE
122#else
123 INTEGER, INTENT(IN) :: NEL, DATATYPE
124#endif
125 DOUBLE PRECISION, INTENT(IN) :: INV ( 2 * NEL )
126 DOUBLE PRECISION, INTENT(INOUT) :: INOUTV ( 2 * NEL )
127 INTEGER I, TMPEXPIN, TMPEXPINOUT
128 DO i = 1, nel
129 tmpexpin = int(inv(i*2))
130 tmpexpinout = int(inoutv(i*2))
131 CALL dmumps_updatedeter(inv(i*2-1),
132 & inoutv(i*2-1),
133 & tmpexpinout)
134 tmpexpinout = tmpexpinout + tmpexpin
135 inoutv(i*2) = dble(tmpexpinout)
136 ENDDO
137 RETURN
138 END SUBROUTINE dmumps_deterreduce_func
139 SUBROUTINE dmumps_deter_square(DETER, NEXP)
140 IMPLICIT NONE
141 INTEGER, intent (inout) :: NEXP
142 DOUBLE PRECISION, intent (inout) :: DETER
143 deter=deter*deter
144 nexp=nexp+nexp
145 RETURN
146 END SUBROUTINE dmumps_deter_square
147 SUBROUTINE dmumps_deter_scaling_inverse(DETER, NEXP)
148 IMPLICIT NONE
149 INTEGER, intent (inout) :: NEXP
150 DOUBLE PRECISION, intent (inout) :: DETER
151 deter=1.0d0/deter
152 nexp=-nexp
153 RETURN
154 END SUBROUTINE dmumps_deter_scaling_inverse
155 SUBROUTINE dmumps_deter_sign_perm(DETER, N, VISITED, PERM)
156 IMPLICIT NONE
157 DOUBLE PRECISION, intent(inout) :: DETER
158 INTEGER, intent(in) :: N
159 INTEGER, intent(inout) :: VISITED(N)
160 INTEGER, intent(in) :: PERM(N)
161 INTEGER I, J, K
162 k = 0
163 DO i = 1, n
164 IF (visited(i) .GT. n) THEN
165 visited(i)=visited(i)-n-n-1
166 cycle
167 ENDIF
168 j = perm(i)
169 DO WHILE (j.NE.i)
170 visited(j) = visited(j) + n + n + 1
171 k = k + 1
172 j = perm(j)
173 ENDDO
174 ENDDO
175 IF (mod(k,2).EQ.1) THEN
176 deter = -deter
177 ENDIF
178 RETURN
179 END SUBROUTINE dmumps_deter_sign_perm
181 & BLOCK_SIZE,IPIV,
182 & MYROW, MYCOL, NPROW, NPCOL,
183 & A, LOCAL_M, LOCAL_N, N, MYID,
184 & DKEEP, KEEP, SYM)
187 IMPLICIT NONE
188 INTEGER, intent (in) :: BLOCK_SIZE, NPROW, NPCOL,
189 & local_m, local_n, n, sym
190 INTEGER, intent (in) :: MYROW, MYCOL, MYID, IPIV(LOCAL_M)
191 DOUBLE PRECISION, intent(in) :: A(*)
192 DOUBLE PRECISION, INTENT(INOUT) :: DKEEP(230)
193 INTEGER, INTENT(IN) :: KEEP(500)
194 INTEGER I,IMX,DI,NBLOCK,IBLOCK,ILOC,JLOC,
195 & ROW_PROC,COL_PROC, K
196 DOUBLE PRECISION :: ABSPIVOT
197 di = local_m + 1
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
209 & + 1
210 k=1
211 DO WHILE ( i .LT. imx )
212 IF (sym.NE.1) THEN
213 abspivot = abs(a(i))
214 ELSE
215 abspivot = abs(a(i)*a(i))
216 ENDIF
218 & ( abspivot,
219 & dkeep, keep, .false.)
220 k = k + 1
221 i = i + di
222 END DO
223 END IF
224 END IF
225 END DO
226 RETURN
227 END SUBROUTINE dmumps_par_root_minmax_piv_upd
subroutine dmumps_deter_square(deter, nexp)
subroutine dmumps_updatedeter(piv, deter, nexp)
subroutine dmumps_updatedeter_scaling(piv, deter, nexp)
subroutine dmumps_deter_sign_perm(deter, n, visited, perm)
subroutine dmumps_par_root_minmax_piv_upd(block_size, ipiv, myrow, mycol, nprow, npcol, a, local_m, local_n, n, myid, dkeep, keep, sym)
subroutine dmumps_deter_reduction(comm, deter_in, nexp_in, deter_out, nexp_out, nprocs)
subroutine dmumps_deterreduce_func(inv, inoutv, nel, datatype)
subroutine dmumps_getdeter2d(block_size, ipiv, myrow, mycol, nprow, npcol, a, local_m, local_n, n, myid, deter, nexp, sym)
subroutine dmumps_deter_scaling_inverse(deter, nexp)
#define min(a, b)
Definition macros.h:20
subroutine mpi_type_free(newtyp, ierr_mpi)
Definition mpi.f:399
subroutine mpi_type_contiguous(length, datatype, newtype, ierr_mpi)
Definition mpi.f:406
subroutine mpi_allreduce(sendbuf, recvbuf, cnt, datatype, operation, comm, ierr)
Definition mpi.f:103
subroutine mpi_type_commit(newtyp, ierr_mpi)
Definition mpi.f:393
subroutine mpi_op_create(func, commute, op, ierr)
Definition mpi.f:412
subroutine mpi_op_free(op, ierr)
Definition mpi.f:421
subroutine dmumps_update_minmax_pivot(diag, dkeep, keep, nullpivot)