OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dooc_panel_piv.F File Reference

Go to the source code of this file.

Functions/Subroutines

integer function dmumps_ooc_get_panel_size (hbuf_size, nnmax, k227, k50)
subroutine dmumps_permute_panel (ipiv, lpiv, ishift, the_panel, nbrow, nbcol, kbeforepanel)
subroutine dmumps_get_ooc_perm_ptr (typef, nbpanels, i_pivptr, i_piv, ipos, iw, liw)
subroutine dmumps_ooc_pp_set_ptr (k50, nbpanels_l, nbpanels_u, nass, ipos, iw, liw)
subroutine dmumps_ooc_pp_tryrelease_space (iwpos, ioldps, iw, liw, monbloc, nfront, keep)
subroutine dmumps_ooc_get_pp_sizes (k50, nbrow_l, nbcol_u, nass, nbpanels_l, nbpanels_u, lreq)
subroutine dmumps_ooc_pp_check_perm_freed (iw_location, must_be_permuted)

Function/Subroutine Documentation

◆ dmumps_get_ooc_perm_ptr()

subroutine dmumps_get_ooc_perm_ptr ( integer, intent(in) typef,
integer, intent(out) nbpanels,
integer, intent(out) i_pivptr,
integer, intent(out) i_piv,
integer, intent(in) ipos,
integer, dimension(liw) iw,
integer, intent(in) liw )

Definition at line 130 of file dooc_panel_piv.F.

133 USE mumps_ooc_common ! To access TYPEF_L and TYPEF_U
134 IMPLICIT NONE
135 include 'mumps_headers.h'
136C
137C Purpose:
138C =======
139C
140C Get the pointers in IW on pivoting information to be stored
141C during factorization and used during the solve phase. This
142C routine is both for the symmetric (TYPEF=TYPEF_L) and unsymmetric
143C cases (TYPEF=TYPEF_L or TYPEF_U).
144C The total size of this space is estimated during
145C fac_ass.F / fac_ass_ELT.F and must be:
146C * Symmetric case: 1 for NASS + 1 for NBPANELS_L + NBPANELS_L + NASS
147C * Unsymmetric case: 1 + (1+NBPANELS_L+NASS) + (1+NBPANELS_U+NASS)
148C Size computation is in routine DMUMPS_OOC_GET_PP_SIZES.
149C
150C At the end of the standard description of the structure of a node
151C (header, nb slaves, <slaves_list>, row indices, col indices), we
152C add, when panel version with pivoting is used:
153C
154C NASS (nb of fully summed variables)
155C NBPANELS_L
156C PIVRPTR(1:NBPANELS_L)
157C PIV_L (1:NASS) NASS (=IW(IPOS)(or NASS-PIVRPTR(1) in
158C the future, after compression)
159C NBPANELS_U
160C PIVRPTR(1:NBPANELS_U)
161C PIV_U (1:NASS) NASS (=IW(IPOS)(or NASS-PIVRPTR(1) in
162C the future, after compression)
163C
164C
165C Output parameters:
166C =================
167C NBPANELS : nb of panels as estimated during assembly
168C I_PIVPTR : position in IW of the starting of the pointer list
169C (of size NBPANELS) of the pointers to the list of pivots
170C I_PIV : position in IW of the starting of the pivot permutation list
171C
172 INTEGER, intent(out) :: NBPANELS, I_PIVPTR, I_PIV
173 INTEGER, intent(in) :: TYPEF ! TYPEF_L or TYPEF_U
174 INTEGER, intent(in) :: LIW, IPOS
175 INTEGER IW(LIW)
176C Locals
177 INTEGER I_NBPANELS, I_NASS
178C
179 i_nass = ipos
180 i_nbpanels = i_nass + 1 ! L
181 nbpanels = iw(i_nbpanels) ! L
182 i_pivptr = i_nbpanels + 1 ! L
183 i_piv = i_pivptr + nbpanels ! L
184C ... of size NASS = IW(I_NASS)
185 IF (typef==typef_u) THEN
186 i_nbpanels = i_piv+iw(i_nass) ! U
187 nbpanels = iw(i_nbpanels) ! U
188 i_pivptr = i_nbpanels + 1 ! U
189 i_piv = i_pivptr + nbpanels ! U
190 ENDIF
191 RETURN
integer, public typef_u

◆ dmumps_ooc_get_panel_size()

integer function dmumps_ooc_get_panel_size ( integer(8), intent(in) hbuf_size,
integer, intent(in) nnmax,
integer, intent(in) k227,
integer, intent(in) k50 )

Definition at line 24 of file dooc_panel_piv.F.

26 IMPLICIT NONE
27C
28C Arguments:
29C =========
30C
31 INTEGER, INTENT(IN) :: NNMAX, K227, K50
32 INTEGER(8), INTENT(IN) :: HBUF_SIZE
33C
34C Purpose:
35C =======
36C
37C - Compute the effective size (maximum number of pivots in a panel)
38C for a front with NNMAX entries in its row (for U) /
39C column (for L).
40C - Be able to adapt the fixed number of columns in panel
41C depending on NNMAX, and size of IO buffer HBUF_SIZE
42C
43C Local variables
44C ===============
45C
46 INTEGER K227_LOC
47 INTEGER NBCOL_MAX
48 INTEGER EFFECTIVE_SIZE
49 nbcol_max=int(hbuf_size / int(nnmax,8))
50C KEEP(227): Maximum size (nb of col/row) of a panel
51 k227_loc = abs(k227)
52 IF (k50.EQ.2) THEN
53C for 2x2 pivots we may end-up having the first part
54C of a 2x2 pivot in the last col of the panel; the
55C adopted solution consists in adding the next column
56C to the panel; therefore we need be able to
57C dynamically increase the panel size by one.
58C note that we also maintain property:
59C KEEP(227): Maximum size (nb of col/row) of a panel
60 k227_loc=max(k227_loc,2)
61 effective_size = min(nbcol_max-1, k227_loc-1)
62cN - during bwd the effective size is useless
63 ELSE
64C complete buffer space can be used for a panel
65 effective_size = min(nbcol_max, k227_loc)
66 ENDIF
67 IF (effective_size.LE.0) THEN
68 write(6,*) 'Internal buffers too small to store ',
69 & ' ONE col/row of size', nnmax
70 CALL mumps_abort()
71 ENDIF
72 dmumps_ooc_get_panel_size = effective_size
73 RETURN
#define mumps_abort
Definition VE_Metis.h:25
integer function dmumps_ooc_get_panel_size(hbuf_size, nnmax, k227, k50)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21

◆ dmumps_ooc_get_pp_sizes()

subroutine dmumps_ooc_get_pp_sizes ( integer, intent(in) k50,
integer, intent(in) nbrow_l,
integer, intent(in) nbcol_u,
integer, intent(in) nass,
integer, intent(out) nbpanels_l,
integer, intent(out) nbpanels_u,
integer, intent(out) lreq )

Definition at line 301 of file dooc_panel_piv.F.

303 USE dmumps_ooc ! To call DMUMPS_OOC_PANEL_SIZE
304 IMPLICIT NONE
305C
306C Purpose
307C =======
308C
309C Compute the size of the workspace required to store the permutation
310C information during factorization, so that solve can permute back
311C what has to be permuted (this could not be done during factorization
312C because it was already on disk).
313C
314C Arguments
315C =========
316C
317 INTEGER, intent(IN) :: K50, NBROW_L, NBCOL_U, NASS
318 INTEGER, intent(OUT) :: NBPANELS_L, NBPANELS_U, LREQ
319 nbpanels_l=-99999
320 nbpanels_u=-99999
321C
322C Quick return in SPD case (no pivoting)
323C
324 IF (k50.EQ.1) THEN
325 lreq = 0
326 RETURN
327 ENDIF
328C
329C L information is always computed
330C
331 nbpanels_l = (nass / dmumps_ooc_panel_size(nbrow_l))+1
332 lreq = 1 ! Store NASS
333 & + 1 ! Store NBPANELS_L
334 & + nass ! Store permutations
335 & + nbpanels_l ! Store pointers on permutations
336 IF (k50.eq.0) THEN
337C
338C Also take U information into account
339C
340 nbpanels_u = (nass / dmumps_ooc_panel_size(nbcol_u) ) +1
341 lreq = lreq + 1 ! Store NBPANELS_U
342 & + nass ! Store permutations
343 & + nbpanels_u ! Store pointers on permutations
344 ENDIF
345 RETURN
integer function, public dmumps_ooc_panel_size(nnmax)

◆ dmumps_ooc_pp_check_perm_freed()

subroutine dmumps_ooc_pp_check_perm_freed ( integer, intent(in) iw_location,
logical, intent(inout) must_be_permuted )

Definition at line 347 of file dooc_panel_piv.F.

349 IMPLICIT NONE
350 INTEGER, INTENT(IN) :: IW_LOCATION
351 LOGICAL, INTENT(INOUT) :: MUST_BE_PERMUTED
352C
353C Purpose
354C =======
355C
356C Reset MUST_BE_PERMUTED to .FALSE. when we detect
357C that the DMUMPS_OOC_PP_TRY_RELEASE_SPACE has freed
358C the permutation information (see that routine).
359C
360 IF (iw_location .EQ. -7777) THEN
361 must_be_permuted = .false.
362 ENDIF
363 RETURN

◆ dmumps_ooc_pp_set_ptr()

subroutine dmumps_ooc_pp_set_ptr ( integer k50,
integer nbpanels_l,
integer nbpanels_u,
integer nass,
integer ipos,
integer, dimension(liw) iw,
integer liw )

Definition at line 193 of file dooc_panel_piv.F.

195 IMPLICIT NONE
196C
197C Purpose:
198C =======
199C
200C Initialize the contents of PIV/PIVPTR/etc. that will store
201C pivoting information during the factorization.
202C NASS and NBPANELS are recorded. PIVPTR(1:NBPANELS)
203C is initialized to NASS+1. This will be modified during
204C the factorization in cases where permutations have to
205C be performed during the solve phase.
206C
207C Arguments:
208C =========
209C
210 INTEGER K50
211 INTEGER IPOS, NASS, NBPANELS_L, NBPANELS_U, LIW
212 INTEGER IW(LIW)
213C
214C Local variables:
215C ===============
216C
217 INTEGER IPOS_U
218C Executable statements
219 IF (k50.EQ.1) THEN
220 WRITE(*,*) "Internal error: DMUMPS_OOC_PP_SET_PTR called"
221 ENDIF
222 iw(ipos)=nass
223 iw(ipos+1)=nbpanels_l
224 iw(ipos+2:ipos+1+nbpanels_l)=nass+1
225 IF (k50 == 0) THEN
226 ipos_u=ipos+2+nass+nbpanels_l
227 iw(ipos_u)=nbpanels_u
228 iw(ipos_u+1:ipos_u+nbpanels_u)=nass+1
229 ENDIF
230 RETURN

◆ dmumps_ooc_pp_tryrelease_space()

subroutine dmumps_ooc_pp_tryrelease_space ( integer, intent(inout) iwpos,
integer, intent(in) ioldps,
integer, dimension(liw), intent(inout) iw,
integer, intent(in) liw,
type(io_block), intent(in) monbloc,
integer, intent(in) nfront,
integer, dimension(500), intent(in) keep )

Definition at line 232 of file dooc_panel_piv.F.

235 USE dmumps_ooc
236 IMPLICIT NONE
237 include 'mumps_headers.h'
238C
239C Purpose:
240C =======
241C If space used was at the top of the stack then
242C try to free space by detecting that
243C no permutation needs to be applied during
244C solve on panels.
245C One position is left (I_NASS) and set to -1
246C to indicate that permutation not needed at solve.
247C
248C Arguments:
249C =========
250C
251 INTEGER, INTENT(IN) :: IOLDPS, LIW, NFRONT,
252 & KEEP(500)
253 INTEGER, INTENT(INOUT) :: IWPOS, IW(LIW)
254 TYPE(IO_BLOCK), INTENT(IN):: MonBloc
255C
256C Local variables:
257C ===============
258C
259 INTEGER :: NBPANELS_L,I_PIVRPTR_L, I_PIVR_L, NBPANELS_U,
260 & I_PIVRPTR_U, I_PIVR_U, XSIZE, IBEGOOC
261 LOGICAL FREESPACE ! set to true when permutation not needed
262C Executable statements
263 IF (keep(50).EQ.1) RETURN ! no pivoting
264C --------------------------------
265C quick return if record is not at
266C the top of stack of L factors
267 IF ((ioldps+iw(ioldps+xxi)).NE.iwpos) RETURN
268C ---------------------------------------------
269C Panel+pivoting: get pointers on each subarray
270C ---------------------------------------------
271 xsize = keep(ixsz)
272 ibegooc = ioldps+2*nfront+6+iw(ioldps+5+xsize)+xsize
273C -- get L related data
274 CALL dmumps_get_ooc_perm_ptr(typef_l, nbpanels_l,
275 & i_pivrptr_l, i_pivr_l,
276 & ibegooc, iw, liw)
277 freespace =
278 & (monbloc%LastPiv.EQ.(iw(i_pivrptr_l)-1))
279 IF (keep(50).EQ.0) THEN
280C -- get U related dataA
281 CALL dmumps_get_ooc_perm_ptr(typef_u, nbpanels_u,
282 & i_pivrptr_u, i_pivr_u,
283 & ibegooc, iw, liw)
284 freespace = freespace .AND.
285 & (monbloc%LastPiv.EQ.(iw(i_pivrptr_u)-1))
286 ENDIF
287C ---------------------------------
288C Check if permutations eed be
289C performed on panels during solve
290C --------------------------------
291 IF (freespace) THEN
292C -- compress memory for that node: keep one entry set to -7777
293 iw(ibegooc) = -7777 ! will be tested during solve
294 iw(ioldps+xxi) = ibegooc
295 & - ioldps + 1 ! new size of inode's record
296 iwpos = ibegooc+1 ! move back to top of stack
297 ENDIF
298 RETURN
subroutine dmumps_get_ooc_perm_ptr(typef, nbpanels, i_pivptr, i_piv, ipos, iw, liw)

◆ dmumps_permute_panel()

subroutine dmumps_permute_panel ( integer, dimension(lpiv) ipiv,
integer lpiv,
integer ishift,
double precision, dimension(nbrow, nbcol) the_panel,
integer nbrow,
integer nbcol,
integer kbeforepanel )

Definition at line 76 of file dooc_panel_piv.F.

78 IMPLICIT NONE
79C
80C Purpose:
81C =======
82C
83C Permute rows of a panel, stored by columns, according
84C to permutation array IPIV.
85C IPIV is such that, for I = 1 to LPIV, row ISHIFT + I
86C in the front must be permuted with row IPIV( I )
87C
88C Since the panel is not necessary at the beginning of
89C the front, let KbeforePanel be the number of pivots in the
90C front before the first pivot of the panel.
91C
92C In the panel, row ISHIFT+I-KbeforePanel is permuted with
93C row IPIV(I)-KbeforePanel
94C
95C Note:
96C ====
97C
98C This routine can also be used to permute the columns of
99C a matrix (U) stored by rows. In that case, the argument
100C NBROW represents the number of columns, and NBCOL represents
101C the number of rows.
102C
103C
104C Arguments:
105C =========
106C
107 INTEGER LPIV, ISHIFT, NBROW, NBCOL, KbeforePanel
108 INTEGER IPIV(LPIV)
109 DOUBLE PRECISION THE_PANEL(NBROW, NBCOL)
110C
111C Local variables:
112C ===============
113C
114 INTEGER I, IPERM
115C
116C Executable statements
117C =====================
118C
119 DO i = 1, lpiv
120C Swap rows ISHIFT + I and PIV(I)
121 iperm=ipiv(i)
122 IF ( i+ishift.NE.iperm) THEN
123 CALL dswap(nbcol,
124 & the_panel(i+ishift-kbeforepanel,1), nbrow,
125 & the_panel(iperm-kbeforepanel,1), nbrow)
126 ENDIF
127 END DO
128 RETURN
subroutine dswap(n, dx, incx, dy, incy)
DSWAP
Definition dswap.f:82