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

Go to the source code of this file.

Functions/Subroutines

subroutine smumps_process_node (myid, keep, keep8, dkeep, bufr, lbufr, lbufr_bytes, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, slavef, procnode_steps, dad, ptrist, ptrast, step, pimaster, pamaster, nstk_s, comp, fpere, flag, iflag, ierror, comm, itloc, rhs_mumps)

Function/Subroutine Documentation

◆ smumps_process_node()

subroutine smumps_process_node ( integer myid,
integer, dimension(500) keep,
integer(8), dimension(150) keep8,
real, dimension(230) dkeep,
integer, dimension( lbufr ) bufr,
integer lbufr,
integer lbufr_bytes,
integer iwpos,
integer iwposcb,
integer(8) iptrlu,
integer(8) lrlu,
integer(8) lrlus,
integer n,
integer, dimension( liw ) iw,
integer liw,
real, dimension( la ) a,
integer(8) la,
integer, intent(in) slavef,
integer, dimension(keep(28)), intent(in) procnode_steps,
integer, dimension(keep(28)), intent(in) dad,
integer, dimension( keep(28) ) ptrist,
integer(8), dimension (keep(28)) ptrast,
integer, dimension(n) step,
integer, dimension(keep(28)) pimaster,
integer(8), dimension(keep(28)) pamaster,
integer, dimension( keep(28) ) nstk_s,
integer comp,
integer fpere,
logical flag,
integer iflag,
integer ierror,
integer comm,
integer, dimension( n + keep(253) ) itloc,
real, dimension(keep(255)) rhs_mumps )

Definition at line 14 of file sfac_process_contrib_type1.F.

23 IMPLICIT NONE
24 include 'mpif.h'
25 INTEGER IERR
26 INTEGER MYID
27 INTEGER LBUFR, LBUFR_BYTES
28 INTEGER KEEP(500), BUFR( LBUFR )
29 INTEGER(8) KEEP8(150)
30 REAL DKEEP(230)
31 INTEGER(8) :: LA, IPTRLU, LRLU, LRLUS
32 INTEGER IWPOS, IWPOSCB
33 INTEGER N, LIW
34 INTEGER IW( LIW )
35 REAL A( LA )
36 INTEGER, INTENT(IN) :: SLAVEF
37 INTEGER, INTENT(IN) :: PROCNODE_STEPS(KEEP(28)), DAD(KEEP(28))
38 INTEGER(8) :: PTRAST (KEEP(28))
39 INTEGER(8) :: PAMASTER(KEEP(28))
40 INTEGER PTRIST( KEEP(28) )
41 INTEGER STEP(N), PIMASTER(KEEP(28))
42 INTEGER COMP, FPERE
43 LOGICAL FLAG
44 INTEGER NSTK_S( KEEP(28) ), ITLOC( N + KEEP(253) )
45 REAL :: RHS_MUMPS(KEEP(255))
46 INTEGER IFLAG, IERROR, COMM
47 INTEGER POSITION, FINODE, FLCONT, LREQ
48 INTEGER(8) :: LREQCB
49 INTEGER(8) :: IPOS_NODE, ISHIFT_PACKET
50 INTEGER SIZE_PACKET
51 INTEGER NBROWS_ALREADY_SENT, NBROWS_PACKET
52 include 'mumps_headers.h'
53 LOGICAL PACKED_CB
54 REAL, POINTER, DIMENSION(:) :: SON_A
55 INTEGER(8) :: DYN_SIZE
56 flag = .false.
57 position = 0
58 CALL mpi_unpack(bufr, lbufr_bytes, position,
59 & finode, 1, mpi_integer,
60 & comm, ierr)
61 CALL mpi_unpack(bufr, lbufr_bytes, position,
62 & fpere, 1, mpi_integer,
63 & comm, ierr)
64 CALL mpi_unpack(bufr, lbufr_bytes, position,
65 & flcont, 1, mpi_integer,
66 & comm, ierr)
67 CALL mpi_unpack(bufr, lbufr_bytes, position,
68 & nbrows_already_sent, 1, mpi_integer,
69 & comm, ierr)
70 CALL mpi_unpack(bufr, lbufr_bytes, position,
71 & nbrows_packet, 1, mpi_integer,
72 & comm, ierr)
73 packed_cb = (flcont.LT.0)
74 IF (packed_cb) THEN
75 flcont = -flcont
76 lreqcb = (int(flcont,8) * int(flcont+1,8)) / 2_8
77 ELSE
78 lreqcb = int(flcont,8) * int(flcont,8)
79 ENDIF
80 IF (nbrows_already_sent == 0) THEN
81 lreq = 2 * flcont + 6 + keep(ixsz)
82 CALL smumps_alloc_cb( .false., 0_8, .false.,.false.,
83 & myid,n, keep,keep8, dkeep, iw, liw, a, la,
84 & lrlu, iptrlu,iwpos,iwposcb, slavef, procnode_steps, dad,
85 & ptrist,ptrast,step, pimaster, pamaster,
86 & lreq, lreqcb, finode, s_notfree, .true.,
87 & comp, lrlus, keep8(67), iflag, ierror
88 & )
89 IF ( iflag .LT. 0 ) RETURN
90 pimaster(step( finode )) = iwposcb + 1
91 pamaster(step( finode )) = iptrlu + 1_8
92 IF (packed_cb) iw(iwposcb + 1 + xxs ) = s_cb1comp
93 CALL mpi_unpack(bufr, lbufr_bytes, position,
94 & iw(iwposcb + 1+keep(ixsz)), lreq-keep(ixsz),
95 & mpi_integer, comm, ierr)
96 ENDIF
97 IF (packed_cb) THEN
98 ishift_packet = int(nbrows_already_sent,8) *
99 & int(nbrows_already_sent+1,8) / 2_8
100 size_packet = (nbrows_packet * (nbrows_packet+1))/2 +
101 & nbrows_already_sent * nbrows_packet
102 ELSE
103 ishift_packet = int(nbrows_already_sent,8) * int(flcont,8)
104 size_packet = nbrows_packet * flcont
105 ENDIF
106 IF (nbrows_packet.NE.0) THEN
107 CALL mumps_geti8(dyn_size, iw(pimaster(step(finode))+xxd))
108 IF (dyn_size .GT. 0_8) THEN
109 CALL smumps_dm_set_ptr( pamaster(step(finode)),
110 & dyn_size, son_a )
111 ipos_node = 1_8
112 CALL mpi_unpack(bufr, lbufr_bytes, position,
113 & son_a(ipos_node + ishift_packet),
114 & size_packet, mpi_real, comm, ierr)
115 ELSE
116 ipos_node = pamaster(step(finode))
117 CALL mpi_unpack(bufr, lbufr_bytes, position,
118 & a(ipos_node + ishift_packet),
119 & size_packet, mpi_real, comm, ierr)
120 ENDIF
121 ENDIF
122 IF (nbrows_already_sent+nbrows_packet == flcont) THEN
123 nstk_s(step(fpere)) = nstk_s(step(fpere)) - 1
124 IF ( nstk_s(step(fpere)).EQ.0 ) THEN
125 flag = . true.
126 END IF
127 ENDIF
128 RETURN
subroutine mpi_unpack(inbuf, insize, position, outbuf, outcnt, datatype, comm, ierr)
Definition mpi.f:514
subroutine smumps_dm_set_ptr(address, sizfr8, cbptr)
int comp(int a, int b)
subroutine smumps_alloc_cb(inplace, min_space_in_place, ssarbr, process_bande, myid, n, keep, keep8, dkeep, iw, liw, a, la, lrlu, iptrlu, iwpos, iwposcb, slavef, procnode_steps, dad, ptrist, ptrast, step, pimaster, pamaster, lreq, lreqcb, node_arg, state_arg, set_header, comp, lrlus, lrlusm, iflag, ierror)
subroutine mumps_geti8(i8, int_array)