16 & PROCNODE_STEPS, SLAVEF,
17 & IWPOS, IWPOSCB, IPTRLU, LRLU, LRLUS,
19 & PTRIST, PTRAST, STEP, PIMASTER, PAMASTER, NSTK_S,
21 & IFLAG, IERROR, COMM, COMM_LOAD,
22 & IPOOL, LPOOL, LEAF, KEEP, KEEP8, DKEEP,
23 & ND, FILS, DAD, FRERE, ITLOC, RHS_MUMPS,
24 & ISTEP_TO_INIV2, TAB_POS_IN_PERE )
33 DOUBLE PRECISION DKEEP(230)
34 INTEGER LBUFR, LBUFR_BYTES
37 INTEGER(8) :: IPTRLU, LRLU, LRLUS, LA
38 INTEGER IWPOS, IWPOSCB
41 DOUBLE PRECISION A( LA )
42 INTEGER(8) :: PTRAST(KEEP(28))
43 INTEGER(8) :: PAMASTER(KEEP(28))
44 INTEGER PTRIST(KEEP(28)), STEP(N), PIMASTER(KEEP(28))
45 INTEGER PROCNODE_STEPS( KEEP(28) ), ITLOC( N +KEEP(253) )
46 DOUBLE PRECISION :: RHS_MUMPS(KEEP(255))
48 INTEGER NSTK_S( KEEP(28) )
49 INTEGER IFLAG, IERROR, COMM, COMM_LOAD
51 INTEGER IPOOL( LPOOL )
52 INTEGER ND(KEEP(28)), FILS( N ), DAD(KEEP(28)), FRERE(KEEP(28))
53 INTEGER ISTEP_TO_INIV2(KEEP(71)),
54 & tab_pos_in_pere(slavef+2,
max(1,keep(56)))
55 INTEGER POSITION, IFATH, ISON, NROW, NCOL, NELIM,
58 INTEGER NOINT, INIV2, NCOL_EFF
59 DOUBLE PRECISION FLOP1
60 INTEGER NBROWS_ALREADY_SENT, NBROWS_PACKET
63 include
'mumps_headers.h'
64 DOUBLE PRECISION,
POINTER,
DIMENSION(:) :: SON_A
65 INTEGER(8) :: DYN_SIZE
66 INTEGER MUMPS_TYPENODE
67 EXTERNAL mumps_typenode
70 & ifath, 1, mpi_integer
73 & ison , 1, mpi_integer,
77 & mpi_integer, comm, ierr )
79 & nrow , 1, mpi_integer
82 & ncol , 1, mpi_integer
85 & nbrows_already_sent, 1,
86 & mpi_integer, comm, ierr)
89 & mpi_integer, comm, ierr)
90 IF ( nslaves .NE. 0 .and. keep(50).ne.0 )
THEN
95 noreal_packet = nbrows_packet * ncol_eff
96 IF (nbrows_already_sent .EQ. 0)
THEN
97 noint = 6 + nrow + ncol + nslaves + keep(ixsz)
98 noreal= int(nrow,8) * int(ncol_eff,8)
100 & myid,n,keep,keep8,dkeep,iw,liw,a,la,
101 & lrlu, iptrlu,iwpos,iwposcb, slavef, procnode_steps, dad,
102 & ptrist,ptrast,step, pimaster, pamaster,
103 & noint, noreal, ison, s_notfree, .true.,
104 & comp, lrlus, keep8(67), iflag, ierror
106 IF ( iflag .LT. 0 )
THEN
109 pimaster(step( ison )) = iwposcb + 1
110 pamaster(step( ison )) = iptrlu + 1_8
111 iw( iwposcb + 1 + xxnbpr ) = 0
112 iw( iwposcb + 1 + keep(ixsz) ) = ncol
114 iw( iwposcb + 2 + keep(ixsz) ) = nelim
115 iw( iwposcb + 3 + keep(ixsz) ) = nrow
116 IF ( nslaves .NE. 0 .and. keep(50).ne.0 )
THEN
117 iw( iwposcb + 4 + keep(ixsz) ) = nrow - ncol
118 IF ( nrow - ncol .GE. 0 )
THEN
119 WRITE(*,*)
'Error in PROCESS_MAITRE2:',nrow,ncol
123 iw( iwposcb + 4 + keep(ixsz) ) = 0
125 iw( iwposcb + 5 + keep(ixsz) ) = 1
126 iw( iwposcb + 6 + keep(ixsz) ) = nslaves
127 IF (nslaves.GT.0)
THEN
129 & iw( iwposcb + 7 + keep(ixsz) ),
130 & nslaves, mpi_integer, comm, ierr )
133 & iw(iwposcb + 7 + keep(ixsz) + nslaves),
134 & nrow, mpi_integer, comm, ierr)
136 & iw(iwposcb + 7 + keep(ixsz) + nrow + nslaves),
137 & ncol, mpi_integer, comm, ierr)
138 IF ( nslaves .GT. 0 )
THEN
139 iniv2 = istep_to_iniv2( step(ison) )
141 & tab_pos_in_pere(1,iniv2),
142 & nslaves+1, mpi_integer, comm, ierr)
143 tab_pos_in_pere(slavef+2,iniv2) = nslaves
146 IF (noreal_packet.GT.0)
THEN
147 CALL mumps_geti8(dyn_size, iw(pimaster(step(ison))+xxd))
148 IF ( dyn_size .GT. 0_8 )
THEN
153 & int(nbrows_already_sent,8) * int(ncol_eff,8) ),
154 & noreal_packet, mpi_double_precision
157 & a( pamaster(step(ison)) +
158 & int(nbrows_already_sent,8) * int(ncol_eff,8) ),
159 & noreal_packet, mpi_double_precision, comm, ierr )
162 IF ( nbrows_already_sent + nbrows_packet .EQ. nrow )
THEN
163 peretype2 = ( mumps_typenode(procnode_steps(step(ifath)),
164 & keep(199)) .EQ. 2 )
165 nstk_s( step(ifath )) = nstk_s( step(ifath) ) - 1
166 IF ( nstk_s( step(ifath)) .EQ. 0 )
THEN
169 & keep(28), keep(76), keep(80), keep(47),
171 IF (keep(47) .GE. 3)
THEN
174 & procnode_steps, keep,keep8, slavef, comm_load,
175 & myid, step, n, nd, fils )
179 & fils,frere, step, pimaster,
180 & keep(28), keep(50), keep(253),
181 & flop1,iw, liw, keep(ixsz) )
182 IF (ifath.NE.keep(20))
subroutine dmumps_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 dmumps_process_master2(myid, bufr, lbufr, lbufr_bytes, procnode_steps, slavef, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, ptrist, ptrast, step, pimaster, pamaster, nstk_s, comp, iflag, ierror, comm, comm_load, ipool, lpool, leaf, keep, keep8, dkeep, nd, fils, dad, frere, itloc, rhs_mumps, istep_to_iniv2, tab_pos_in_pere)