OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
mumps_type2_blocking.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
15 & ( slavef, k48, k821, k50,
16 & nfront, ncb, k375, k119)
17 IMPLICIT NONE
18 INTEGER, INTENT (IN) :: slavef, k48, k50, nfront, ncb
19 INTEGER, INTENT (IN) :: k375
20 INTEGER, INTENT (IN) :: k119
21 INTEGER(8), INTENT (IN) :: k821
22 INTEGER nslavesmin, nass, kmax
23 REAL wmaster, wtotal, wmax
24 INTEGER acc,x
26 INTEGER mumps_reg_getkmax
28 kmax = mumps_reg_getkmax( k821, ncb )
29 nass = nfront - ncb
30 nslavesmin = 1
31 IF ( k48 .EQ.0 .OR.
32 & (k48.EQ.5 .AND. (k119.EQ.1. or.k50.EQ.0))) THEN
33 nslavesmin = max(ncb/max(1,kmax),1)
34 ELSE IF (k48 .EQ. 3 .OR.(k48.EQ.5 .AND.k50.NE.0) ) THEN
35 wmax = mumps_bloc2_cout(kmax,nfront,nass)
36 wtotal = mumps_bloc2_cout(ncb,nfront,nass)
37 wmaster = real(nass)*real(nass)*real(nass)/(3.0e0)
38 IF ( wmaster .GT. wmax ) THEN
39 nslavesmin = max( nint( wtotal / wmaster ), 1 )
40 ELSE
41 nslavesmin = max( nint( wtotal / wmax ), 1 )
42 ENDIF
43 IF (k48 .EQ. 5) THEN
44 IF (k119.EQ.2) THEN
45 nslavesmin = max( nslavesmin/2, 1 )
46 ENDIF
47 END IF
48 ELSE IF (k48 .EQ. 4 ) THEN
49 IF ( k821 > 0_8 ) THEN
50 WRITE(*,*) 'Internal Error 1 in MUMPS_BLOC2_GET_NSLAVESMIN'
51 CALL mumps_abort()
52 ENDIF
54 & "K821 too large in MUMPS_BLOC2_GET_NSLAVESMIN" )
55 kmax=int(abs(k821))
56 IF(k50.EQ.0)THEN
57 nslavesmin = max(int(
58 & (int(ncb,8)*int(ncb,8))/int(kmax,8)
59 & ),1)
60 ELSE
61 acc=0
62 nslavesmin=0
63 DO WHILE (acc.NE.ncb)
64 x=int((-real(nfront-ncb+acc)
65 & +sqrt(((real(nfront-ncb+acc)*
66 & real(nfront-ncb+acc))+real(4)*
67 & real(kmax))))/
68 & real(2))
69 acc=acc+x
70 nslavesmin=nslavesmin+1
71 IF (((ncb-acc)*ncb).LT.kmax)THEN
72 acc=ncb
73 nslavesmin=nslavesmin+1
74 ENDIF
75 ENDDO
76 ENDIF
77 ENDIF
78 nslavesmin = min( nslavesmin,(slavef-1) )
80 & min( nslavesmin, ncb )
81 IF (k375 .EQ. 1) THEN
83 ENDIF
84 RETURN
85 END FUNCTION mumps_bloc2_get_nslavesmin
87 & ( slavef, k48, k821, k50,
88 & nfront, ncb, k375, k119 )
89 IMPLICIT NONE
90 INTEGER, INTENT (IN) :: slavef, k48, k50,nfront, ncb, k375, k119
91 INTEGER(8), INTENT(IN) :: k821
92 INTEGER nslavesmax, kmax, kmin
93 INTEGER nslavesmin
100 IF (k48 .eq. 0 .OR. k48.eq.3.OR.k48.EQ.5) THEN
101 kmax = mumps_reg_getkmax( k821, ncb )
102 kmin = mumps_getkmin( k821, k50, kmax, ncb)
103 nslavesmax = mumps_bloc2_get_ns_blsize(
104 & slavef, k48, k50, kmin, nfront, ncb )
105 ELSE
106 nslavesmax = slavef-1
107 ENDIF
108 nslavesmin = mumps_bloc2_get_nslavesmin(
109 & slavef, k48, k821, k50, nfront, ncb, k375, k119 )
110 nslavesmax = max( nslavesmax, nslavesmin )
112 & min( nslavesmax, ncb )
113 IF (k375 .EQ. 1) THEN
115 ENDIF
116 RETURN
117 END FUNCTION mumps_bloc2_get_nslavesmax
118 SUBROUTINE mumps_max_surfcb_nbrows( WHAT, KEEP,KEEP8,
119 & NCB, NFR, SLAVEF, NBROWMAX, MAXSURFCB8
120 & )
121 IMPLICIT NONE
122 INTEGER, intent(in) :: WHAT, NCB, NFR, SLAVEF
123 INTEGER, intent(in) :: KEEP(500)
124 INTEGER(8) KEEP8(150)
125 INTEGER, intent(out) :: NBROWMAX
126 INTEGER(8), intent(out) :: MAXSURFCB8
127 INTEGER KMAX, KMIN, NSLAVES, SIZEDUMMY, TABDUMMY(1)
130 INTEGER MUMPS_REG_GETKMAX, MUMPS_GETKMIN,
131 & MUMPS_BLOC2_GET_NSLAVESMIN
132 IF ( what .NE. 1 .and. what .NE. 2 ) THEN
133 IF (what .NE. 4 .and. what .NE. 5 .AND.
134 & keep(48).NE.5 ) THEN
135 WRITE(*,*) "Internal error 1 in MUMPS_MAX_SURFCB_NBROWS"
136 CALL mumps_abort()
137 END IF
138 ENDIF
139 kmax = mumps_reg_getkmax( keep8(21), ncb )
140 IF (what .EQ.1.OR.what.EQ.2) THEN
141 nslaves = mumps_bloc2_get_nslavesmin( slavef, keep(48),
142 & keep8(21), keep(50),
143 & nfr, ncb, keep(375), keep(119) )
144 ELSE
145 nslaves=slavef
146 ENDIF
147 IF ( keep(48) == 0 .OR. (keep(48).EQ.5.AND.keep(50).EQ.0)) THEN
148 nbrowmax = ncb / nslaves + mod( ncb, nslaves )
149 IF ( what == 2 .OR. what == 5 )
150 & maxsurfcb8 = int(nbrowmax,8) * int(ncb,8)
151 ELSE IF (keep(48) == 3.OR.(keep(48).EQ.5.AND.keep(50).NE.0))THEN
152 kmin = mumps_getkmin( keep8(21), keep(50), kmax, ncb )
153 sizedummy = 1
154 IF (what.GT.3) THEN
156 & what-3, nslaves, nfr, ncb,
157 & kmin, kmax, slavef,
158 & nbrowmax, maxsurfcb8, tabdummy, sizedummy)
159 ELSE
161 & what, nslaves, nfr, ncb,
162 & kmin, kmax, slavef,
163 & nbrowmax, maxsurfcb8, tabdummy, sizedummy)
164 ENDIF
165 ELSE IF ( keep(48) == 4 ) THEN
166 IF (keep8(21) > 0_8) THEN
167 WRITE(*,*) "Internal error 2 in MUMPS_MAX_SURFCB_NBROWS"
168 CALL mumps_abort()
169 END IF
170 IF(keep(50).EQ.0)THEN
171 IF ( abs(keep8(21)) * int( slavef - 1,8 ) >
172 & int( ncb,8) * int(nfr,8) ) THEN
173 nbrowmax = (ncb + slavef -2 ) / ( slavef - 1 )
174 IF ( what == 2 ) maxsurfcb8 = int(nbrowmax,8) *int(ncb,8)
175 ELSE
176 nbrowmax=int(
177 & (abs(keep8(21)) + int(nfr - 1,8))
178 & / int(nfr,8)
179 & )
180 IF ( what == 2 ) maxsurfcb8 = abs(keep8(21))
181 ENDIF
182 ELSE
183 nbrowmax=int((-real(nfr-ncb)
184 & +sqrt((real(nfr-ncb)*
185 & real(nfr-ncb))+real(4)*
186 & real(abs(keep8(21)))))/
187 & real(2))
188 IF ( what == 2 ) maxsurfcb8 = abs(keep8(21))
189 ENDIF
190 ELSE
191 nbrowmax = ncb
192 IF (what == 2) maxsurfcb8 = int(ncb,8) * int(ncb,8)
193 ENDIF
194 nbrowmax = min( max(nbrowmax, 1), ncb)
195 RETURN
196 END SUBROUTINE mumps_max_surfcb_nbrows
197 INTEGER FUNCTION mumps_bloc2_get_ns_blsize( SLAVEF, K48, K50,
198 & BLSIZE, NFRONT, NCB)
199 IMPLICIT NONE
200 INTEGER, INTENT (IN) :: slavef, k48, k50, blsize, nfront, ncb
201 INTEGER nslaves, nass
202 REAL wtotal, wblsize
204 EXTERNAL mumps_bloc2_cout
205 nass = nfront - ncb
206 nslaves = slavef-1
207 IF ( k48 .EQ.0 .OR. (k48.EQ.5 .AND. k50.EQ.0)) THEN
208 nslaves = max(ncb/max(1,blsize),1)
209 ELSE IF (k48.EQ.3 .OR. (k48.EQ.5 .AND. k50.NE.0))THEN
210 wblsize = mumps_bloc2_cout(blsize,nfront,nass)
211 wtotal = mumps_bloc2_cout(ncb,nfront,nass)
212 nslaves = max(nint( wtotal / wblsize ), 1)
213 ENDIF
215 & min( nslaves,(slavef-1) )
216 RETURN
217 END FUNCTION mumps_bloc2_get_ns_blsize
219 & GETPOSITIONS, NSLAVES, NFRONT, NCB,
220 & KMIN, KMAX, SLAVEF,
221 & NBROWMAX, MAXSURFCB, TABPOS, SIZETABPOS)
222 IMPLICIT NONE
223 INTEGER, INTENT (IN) :: GETPOSITIONS,
224 & nslaves, nfront, ncb,
225 & kmin, kmax, slavef, sizetabpos
226 INTEGER, INTENT (OUT) :: NBROWMAX
227 INTEGER(8), INTENT(OUT) :: MAXSURFCB
228 INTEGER, INTENT (OUT) :: TABPOS(SIZETABPOS)
229 REAL W, COSTni
230 REAL delta
231 INTEGER SumNi, NCOLim1, I, BLSIZE, NASS
232 LOGICAL GETROW, GETSURF, GETPOS, GET_AVGROW, GET_AVGSURF
233 REAL MUMPS_BLOC2_COUT
234 EXTERNAL mumps_bloc2_cout
235 getrow = (getpositions.EQ.1)
236 getsurf= (getpositions.EQ.2)
237 getpos = (getpositions.EQ.3)
238 get_avgrow = (getpositions.EQ.4)
239 get_avgsurf = (getpositions.EQ.5)
240 nbrowmax = 0
241 maxsurfcb = 0_8
242 IF (getpos) THEN
243 tabpos(1) = 1
244 tabpos(nslaves+1)= ncb+1
245 tabpos(slavef+2) = nslaves
246 ENDIF
247 IF (nslaves.EQ.1) THEN
248 IF ( getsurf ) THEN
249 nbrowmax = ncb
250 maxsurfcb = int(ncb,8)*int(ncb,8)
251 ELSEIF ( getrow ) THEN
252 nbrowmax = ncb
253 ENDIF
254 ELSE
255 nass = nfront - ncb
256 w = mumps_bloc2_cout(ncb,nfront,nass)
257 sumni = 0
258 ncolim1 = nass
259 DO i = 1, nslaves-1
260 delta = real(2*ncolim1-nass+1)**2 +
261 & (real(4)*w)/real(nass*(nslaves-i+1))
262 delta = sqrt(delta)
263 delta = (real(-2*ncolim1+nass-1) + delta )/real(2)
264 blsize = max(int(delta), 1)
265 IF ( (nfront-ncolim1-blsize) .LE. nslaves-i ) THEN
266 blsize = 1
267 ENDIF
268 ncolim1 = ncolim1+blsize
269 costni = mumps_bloc2_cout(blsize,ncolim1,nass)
270 w = w - costni
271 IF (getpos) tabpos(i) = sumni + 1
272 IF (getsurf) THEN
273 nbrowmax = max( nbrowmax,
274 & blsize )
275 maxsurfcb = max( maxsurfcb,
276 & int(blsize,8)* int(sumni+blsize,8) )
277 ELSEIF ( getrow ) THEN
278 nbrowmax = max( nbrowmax,
279 & blsize )
280 RETURN
281 ELSEIF (get_avgsurf) THEN
282 nbrowmax = nbrowmax + blsize
283 maxsurfcb = maxsurfcb + int(blsize,8)*int(sumni+blsize,8)
284 ELSEIF (get_avgrow) THEN
285 nbrowmax = nbrowmax + blsize
286 ENDIF
287 sumni = sumni + blsize
288 ENDDO
289 blsize = ncb - sumni
290 IF (blsize.LE.0) THEN
291 write(*,*) ' Error in MUMPS_BLOC2_SET_POSK483: ',
292 & ' size lastbloc ', blsize
293 CALL mumps_abort()
294 ENDIF
295 if (ncolim1+blsize.NE.nfront) then
296 write(*,*) ' Error in MUMPS_BLOC2_SET_POSK483: ',
297 & ' NCOLim1, BLSIZE, NFRONT=',
298 & ncolim1, blsize, nfront
299 CALL mumps_abort()
300 endif
301 IF (getpos) tabpos(nslaves) = sumni + 1
302 IF (getsurf) THEN
303 nbrowmax = max( nbrowmax,
304 & blsize )
305 maxsurfcb = max( maxsurfcb,
306 & int(blsize,8)* int(sumni+blsize,8 ))
307 ELSEIF ( getrow ) THEN
308 nbrowmax = max( nbrowmax,
309 & blsize )
310 ELSEIF (get_avgsurf) THEN
311 nbrowmax = nbrowmax + blsize
312 maxsurfcb = maxsurfcb + int(blsize,8)*int(sumni+blsize,8)
313 nbrowmax=(nbrowmax+nslaves-1)/nslaves
314 maxsurfcb=(maxsurfcb+int(nslaves-1,8))/int(nslaves,8)
315 ELSEIF (get_avgrow) THEN
316 nbrowmax = nbrowmax + blsize
317 nbrowmax=(nbrowmax+nslaves-1)/nslaves
318 ENDIF
319 ENDIF
320 RETURN
321 END SUBROUTINE mumps_bloc2_set_posk483
323 & KEEP,KEEP8, SLAVEF,
324 & TAB_POS_IN_PERE,
325 & NSLAVES, NFRONT, NCB
326 & )
327 IMPLICIT NONE
328 INTEGER, INTENT( IN ) :: NCB, NSLAVES, SLAVEF, NFRONT,
329 & keep(500)
330 INTEGER(8) KEEP8(150)
331 INTEGER TAB_POS_IN_PERE(SLAVEF+2)
332 INTEGER :: I, BLSIZE
333 INTEGER KMIN, KMAX, NBROWDUMMY,
334 & GETPOSITIONS, SIZECOLTAB
335 INTEGER(8) MAXSURFDUMMY8
336 INTEGER MUMPS_GETKMIN, MUMPS_REG_GETKMAX
337 EXTERNAL mumps_getkmin, mumps_reg_getkmax,
339 IF (keep(48).EQ.0) THEN
340 blsize = ncb / nslaves
341 tab_pos_in_pere( 1 ) = 1
342 DO i = 1, nslaves-1
343 tab_pos_in_pere( i+1 ) = tab_pos_in_pere(i) +
344 & blsize
345 ENDDO
346 tab_pos_in_pere(nslaves+1) = ncb+1
347 tab_pos_in_pere(slavef+2) = nslaves
348 RETURN
349 ELSE IF (keep(48).EQ.3 ) THEN
350 kmax = mumps_reg_getkmax(keep8(21), ncb)
351 kmin = mumps_getkmin(keep8(21), keep(50), kmax, ncb)
352 getpositions = 3
353 sizecoltab = slavef+2
355 & getpositions, nslaves, nfront, ncb,
356 & kmin, kmax, slavef,
357 & nbrowdummy, maxsurfdummy8,
358 & tab_pos_in_pere(1), sizecoltab)
359 ENDIF
360 RETURN
361 END SUBROUTINE mumps_bloc2_setpartition
363 & KEEP,KEEP8, INODE, STEP, N, SLAVEF,
364 & ISTEP_TO_INIV2, TAB_POS_IN_PERE,
365 &
366 & ISLAVE, NCB, NSLAVES, SIZE, FIRST_INDEX )
367 IMPLICIT NONE
368 INTEGER, INTENT( IN ) :: ISLAVE, NCB, NSLAVES, SLAVEF,
369 & KEEP(500), INODE, N
370 INTEGER(8) KEEP8(150)
371 INTEGER, INTENT( IN ) :: STEP(N),
372 & ISTEP_TO_INIV2(KEEP(71)),
373 & tab_pos_in_pere(slavef+2,max(1,keep(56)))
374 INTEGER, INTENT( OUT ):: SIZE, FIRST_INDEX
375 INTEGER BLSIZE, J
376 IF (keep(48).EQ.0) THEN
377 blsize = ncb / nslaves
378 IF ( islave .NE. nslaves ) THEN
379 SIZE = blsize
380 ELSE
381 SIZE = blsize + mod( ncb, nslaves )
382 END IF
383 first_index = ( islave - 1 ) * blsize + 1
384 ELSEIF (keep(48).EQ.3) THEN
385 j = istep_to_iniv2( step(inode) )
386 first_index = tab_pos_in_pere(islave,j)
387 SIZE = tab_pos_in_pere(islave+1,j) - first_index
388 ELSEIF (keep(48).EQ.4) THEN
389 j = istep_to_iniv2( step(inode) )
390 first_index = tab_pos_in_pere(islave,j)
391 SIZE = tab_pos_in_pere(islave+1,j) - first_index
392 ELSEIF (keep(48).EQ.5) THEN
393 j = istep_to_iniv2( step(inode) )
394 first_index = tab_pos_in_pere(islave,j)
395 SIZE = tab_pos_in_pere(islave+1,j) - first_index
396 ELSE
397 WRITE(*,*) 'Error in MUMPS_BLOC2 undef strat'
398 CALL mumps_abort()
399 ENDIF
400 RETURN
401 END SUBROUTINE mumps_bloc2_get_slave_info
402 REAL function mumps_bloc2_cout(nrow,ncol,nass)
403 IMPLICIT NONE
404 INTEGER, INTENT (IN) :: nrow,ncol,nass
405 mumps_bloc2_cout = real(nass)*real(nrow)*
406 & real(2*ncol - nass - nrow + 1)
407 RETURN
408 END FUNCTION mumps_bloc2_cout
409 INTEGER FUNCTION mumps_reg_get_nslaves
410 & (k821, k48, k50, slavef,
411 & ncb, nfront, nslaves_less, nmb_of_cand, k375, k119)
412 IMPLICIT NONE
413 INTEGER, INTENT( IN ) :: ncb, nfront, nslaves_less,
414 & k48, k50, slavef, nmb_of_cand, k375, k119
415 INTEGER(8), INTENT(IN) :: k821
416 INTEGER nslaves
417 INTEGER kmax, npiv,
418 & nslaves_ref, nslaves_max
419 REAL wk_master, wk_slave
425 EXTERNAL mumps_bloc2_cout
426 IF (nmb_of_cand.LE.0) THEN
427 ENDIF
428 IF ( (k48.EQ.0).OR. (k48.EQ.3) ) THEN
429 kmax = mumps_reg_getkmax( k821, ncb )
430 nslaves_ref = mumps_bloc2_get_nslavesmin(
431 & slavef, k48, k821, k50, nfront, ncb, k375, k119 )
432 nslaves = nslaves_ref
433 IF ( nslaves_ref.LT.slavef ) THEN
434 nslaves_max = mumps_bloc2_get_nslavesmax(
435 & slavef, k48, k821, k50, nfront, ncb, k375, k119 )
436 IF ( nslaves_max .LT. nslaves_less ) THEN
437 nslaves = nslaves_max
438 ELSE
439 nslaves = nslaves_less
440 ENDIF
441 nslaves = max(nslaves_ref,nslaves)
442 ENDIF
443 nslaves = min(nslaves, nmb_of_cand)
444 IF ( nslaves.GT.nslaves_ref) THEN
445 npiv = nfront - ncb
446 IF ( k50.EQ.0 ) THEN
447 wk_slave = real( npiv ) * real( ncb ) *
448 & ( 2.0e0 * real(nfront) - real(npiv) )
449 & / real(nslaves)
450 wk_master = 0.66667e0 *
451 & real(npiv)*real(npiv)*real(npiv)+
452 & real(npiv)*real(npiv)*real(ncb)
453 ELSE
454 wk_slave = mumps_bloc2_cout(ncb,nfront,npiv)
455 & / real(nslaves)
456 wk_master = real(npiv)*real(npiv)*real(npiv)/3.0e0
457 ENDIF
458 IF ( (wk_master.GT.wk_slave).AND.
459 & (wk_slave.GT.1.0e0) ) THEN
460 nslaves =
461 & int( real(nslaves) * (wk_slave/wk_master))
462 nslaves = max(nslaves_ref, nslaves)
463 ENDIF
464 ENDIF
465 ELSE
466 nslaves = nslaves_less
467 ENDIF
468 nslaves = min(nslaves, ncb)
469 nslaves = min(nslaves, nmb_of_cand)
470 mumps_reg_get_nslaves = nslaves
471 RETURN
472 END FUNCTION mumps_reg_get_nslaves
474 & KEEP,KEEP8, INODE, STEP, N, SLAVEF,
475 & ISTEP_TO_INIV2, TAB_POS_IN_PERE,
476 &
477 & NASS, NCB,
478 & NSLAVES, POSITION, ISLAVE, IPOSSLAVE )
479 IMPLICIT NONE
480 INTEGER, INTENT( IN ) :: KEEP(500),INODE,N,SLAVEF
481 INTEGER(8) KEEP8(150)
482 INTEGER, INTENT( IN ) :: STEP(N),
483 & istep_to_iniv2(keep(71)),
484 & tab_pos_in_pere(slavef+2,max(1,keep(56)))
485 INTEGER, INTENT( IN ) :: NASS, NCB,
486 & nslaves, position
487 INTEGER, INTENT( OUT ) :: ISLAVE, IPOSSLAVE
488 INTEGER BLSIZE, J, ISHIFT
489 IF ((nslaves.LE.0).OR.(position.LE.nass)) THEN
490 islave = 0
491 iposslave = position
492 RETURN
493 ENDIF
494 IF (keep(48).NE.0.and.keep(48).NE.3.and.keep(48).NE.4
495 & .and.keep(48).NE.5) THEN
496 WRITE(*,*) 'Error in MUMPS_BLOC2_GET_ISLAVE: undef strat'
497 CALL mumps_abort()
498 ENDIF
499 IF (keep(48).ne.0) THEN
500 j = istep_to_iniv2( step(inode) )
501 ishift = position - nass
502 DO islave = nslaves,1,-1
503 IF ( ishift .GE. tab_pos_in_pere(islave,j)) THEN
504 iposslave = ishift - tab_pos_in_pere(islave,j) + 1
505 EXIT
506 END IF
507 END DO
508 ELSE
509 blsize = ncb / nslaves
510 islave = min( nslaves,
511 & ( position - nass - 1 ) / blsize + 1 )
512 iposslave = position - nass - ( islave - 1 ) * blsize
513 ENDIF
514 RETURN
515 END SUBROUTINE mumps_bloc2_get_islave
516 INTEGER FUNCTION mumps_getkmin( K821, K50, KMAX, NCB )
517 IMPLICIT NONE
518 INTEGER, INTENT( IN ) :: kmax, ncb, k50
519 INTEGER(8), INTENT(IN) :: k821
520 INTEGER kmin, mingran
521 INTEGER(8) :: kminsurf
522 IF ( ( ncb .LE.0 ).OR. (kmax.LE.0) ) THEN
523 mumps_getkmin = 1
524 RETURN
525 ENDIF
526 IF (k50.EQ.0) THEN
527 kminsurf = 60000_8
528#if defined(t3e) || defined(sgi)
529 mingran = 40
530#else
531 mingran = 50
532#endif
533 ELSE
534 kminsurf = 30000_8
535#if defined(t3e) || defined(sgi)
536 mingran = 10
537#else
538 mingran = 20
539#endif
540 ENDIF
541 IF (k821.GT.0_8) THEN
542#if defined(t3e) || defined(sgi)
543 kmin = max(mingran,kmax/10)
544#else
545 kmin = max(mingran,kmax/20)
546#endif
547 ELSE
548 kminsurf = max( abs(k821)/500_8, kminsurf )
549 kmin = max(
550 & int( kminsurf / int(max(ncb,1),8) ),
551 & 1
552 & )
553 ENDIF
554 kmin = min(kmin,kmax)
555 kmin = max(kmin,1)
556 mumps_getkmin = kmin
557 RETURN
558 END FUNCTION mumps_getkmin
559 INTEGER FUNCTION mumps_reg_getkmax( KEEP821, NCB )
560 IMPLICIT NONE
561 INTEGER, intent( in ) :: ncb
562 INTEGER(8), intent( in ) :: keep821
563 INTEGER kmax
564 IF ( ncb .LE.0 ) THEN
566 RETURN
567 ENDIF
568 IF ( keep821.GT.0_8 ) THEN
569 kmax = int(keep821)
570 ELSE
571 kmax = -int(keep821/int(ncb,8))
572 ENDIF
573 kmax = min(ncb, kmax)
574 mumps_reg_getkmax = max( kmax, 1 )
575 RETURN
576 END FUNCTION mumps_reg_getkmax
#define mumps_abort
Definition VE_Metis.h:25
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
integer function mumps_bloc2_get_nslavesmin(slavef, k48, k821, k50, nfront, ncb, k375, k119)
subroutine mumps_bloc2_set_posk483(getpositions, nslaves, nfront, ncb, kmin, kmax, slavef, nbrowmax, maxsurfcb, tabpos, sizetabpos)
integer function mumps_bloc2_get_ns_blsize(slavef, k48, k50, blsize, nfront, ncb)
real function mumps_bloc2_cout(nrow, ncol, nass)
integer function mumps_getkmin(k821, k50, kmax, ncb)
integer function mumps_reg_get_nslaves(k821, k48, k50, slavef, ncb, nfront, nslaves_less, nmb_of_cand, k375, k119)
integer function mumps_bloc2_get_nslavesmax(slavef, k48, k821, k50, nfront, ncb, k375, k119)
subroutine mumps_max_surfcb_nbrows(what, keep, keep8, ncb, nfr, slavef, nbrowmax, maxsurfcb8)
integer function mumps_reg_getkmax(keep821, ncb)
subroutine mumps_bloc2_get_islave(keep, keep8, inode, step, n, slavef, istep_to_iniv2, tab_pos_in_pere nass, ncb, nslaves, position, islave, iposslave)
subroutine mumps_bloc2_get_slave_info(keep, keep8, inode, step, n, slavef, istep_to_iniv2, tab_pos_in_pere islave, ncb, nslaves, size, first_index)
subroutine mumps_bloc2_setpartition(keep, keep8, slavef, tab_pos_in_pere, nslaves, nfront, ncb)
subroutine mumps_abort_on_overflow(i8, string)