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

Go to the source code of this file.

Modules

module  mumps_build_sort_index_m

Functions/Subroutines

subroutine mumps_build_sort_index_m::mumps_build_sort_index (myid, inode, n, ioldps, hf, lp, lpok, nfront, nfront_eff, perm, dad, nass1, nass, numstk, numorg, iwposcb, iwpos, ifson, step, pimaster, ptrist, ptraiw, iw, liw, intarr, lintarr, itloc, fils, frere_steps, son_level2, niv1, keep, keep8, iflag, ison_in_place, procnode_steps, slavef, sonrows_per_row, lsonrows_per_row, mumps_tps_arr, l0_omp_mapping)
subroutine mumps_sort (n, perm, iw, liw)
subroutine mumps_sorted_merge (n, nass1, perm, itloc, small, lsmall, large, llarge, merge, lmerge)

Function/Subroutine Documentation

◆ mumps_sort()

subroutine mumps_sort ( integer n,
integer, dimension( n ) perm,
integer, dimension( liw ) iw,
integer liw )

Definition at line 626 of file fac_asm_build_sort_index_m.F.

627 IMPLICIT NONE
628 INTEGER N, LIW
629 INTEGER PERM( N ), IW( LIW )
630 INTEGER I, SWAP
631 LOGICAL DONE
632 done = .false.
633 DO WHILE ( .NOT. done )
634 done = .true.
635 DO i = 1, liw - 1
636 IF ( perm( iw( i ) ) .GT. perm( iw( i + 1 ) ) ) THEN
637 done = .false.
638 swap = iw( i + 1 )
639 iw( i + 1 ) = iw( i )
640 iw( i ) = swap
641 END IF
642 END DO
643 END DO
644 RETURN
#define swap(a, b, tmp)
Definition macros.h:40

◆ mumps_sorted_merge()

subroutine mumps_sorted_merge ( integer n,
integer nass1,
integer, dimension( n ) perm,
integer, dimension( n ) itloc,
integer, dimension(lsmall) small,
integer lsmall,
integer, dimension(llarge) large,
integer llarge,
integer, dimension(lmerge) merge,
integer lmerge )

Definition at line 646 of file fac_asm_build_sort_index_m.F.

650 IMPLICIT NONE
651 INTEGER N, NASS1, LSMALL, LLARGE, LMERGE
652 INTEGER PERM( N ), ITLOC( N )
653 INTEGER SMALL(LSMALL), LARGE(LLARGE), MERGE(LMERGE)
654 INTEGER PSMALL, PLARGE, PMERGE, VSMALL, VLARGE, VMERGE
655 psmall = 1
656 plarge = 1
657 pmerge = 1
658 DO WHILE ( psmall .LE. lsmall .or. plarge.LE. llarge )
659 IF ( psmall .GT. lsmall ) THEN
660 vmerge = large( plarge )
661 plarge = plarge + 1
662 ELSE IF ( plarge .GT. llarge ) THEN
663 vmerge = small( psmall )
664 psmall = psmall + 1
665 ELSE
666 vsmall = small( psmall )
667 vlarge = large( plarge )
668 IF ( perm( vsmall ) .LT. perm( vlarge ) ) THEN
669 vmerge = vsmall
670 psmall = psmall + 1
671 ELSE
672 vmerge = vlarge
673 plarge = plarge + 1
674 END IF
675 END IF
676 merge( pmerge ) = vmerge
677 itloc( vmerge ) = pmerge + nass1
678 pmerge = pmerge + 1
679 END DO
680 pmerge = pmerge - 1
681 RETURN
subroutine merge(x, itab, itabm1, cmerge, imerge, imerge2, iadmerge2, nmerge_tot)
Definition merge.F:36