OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zfac_process_end_facto_slave.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
14 RECURSIVE SUBROUTINE zmumps_end_facto_slave(
15 & COMM_LOAD, ASS_IRECV,
16 & N, INODE, FPERE,
17 & root,
18 & MYID, COMM,
19 &
20 & BUFR, LBUFR, LBUFR_BYTES, PROCNODE_STEPS, POSFAC,
21 & IWPOS, IWPOSCB, IPTRLU, LRLU, LRLUS, IW, LIW, A, LA,
22 & PTRIST, PTLUST_S, PTRFAC, PTRAST, STEP, PIMASTER,
23 & PAMASTER,
24 & NSTK, COMP, IFLAG, IERROR, PERM,
25 & IPOOL, LPOOL, LEAF, NBFIN, SLAVEF,
26 & OPASSW, OPELIW, ITLOC, RHS_MUMPS, FILS, DAD, PTRARW, PTRAIW,
27 & INTARR, DBLARR, ICNTL, KEEP,KEEP8,DKEEP, ND, FRERE,
28 & LPTRAR, NELT, FRTPTR, FRTELT,
29 & ISTEP_TO_INIV2, TAB_POS_IN_PERE
30 & , LRGROUPS
31 & )
32 USE zmumps_load
33#if ! defined(NO_FDM_MAPROW)
35#endif
37 USE zmumps_struc_def, ONLY : zmumps_root_struc
38 IMPLICIT NONE
39 include 'mumps_headers.h'
40 include 'mpif.h'
41 include 'mumps_tags.h'
42 INTEGER inode, FPERE
43 TYPE (zmumps_root_struc) :: root
44 INTEGER comm, myid
45 INTEGER ICNTL( 60 ), keep( 500 )
46 INTEGER(8) keep8(150)
47 DOUBLE PRECISION dkeep(230)
48 INTEGER comm_load, ass_irecv
49 INTEGER n
50 INTEGER lbufr, lbufr_bytes
51 INTEGER bufr( lbufr )
52 INTEGER(8) :: posfac, iptrlu, lrlu, lrlus, LA
53 INTEGER procnode_steps(keep(28)), ptrist(keep(28)),
54 & nstk(keep(28)), ptlust_s(keep(28))
55 INTEGER iwpos, IWPOSCB
56 INTEGER liw
57 INTEGER iw( LIW )
58 COMPLEX(kind=8) a( la )
59 INTEGER, intent(in) :: lrgroups(n)
60 INTEGER lptrar, nelt
61 INTEGER frtptr( n+1 ), frtelt( nelt )
62 INTEGER(8) :: ptrast(keep(28))
63 INTEGER(8) :: ptrfac(keep(28))
64 INTEGER(8) :: pamaster(keep(28))
65 INTEGER step(n), pimaster(keep(28))
66 INTEGER comp, iflag, ierror
67 INTEGER perm(n)
68 INTEGER lpool, leaf
69 INTEGER ipool( lpool )
70 INTEGER nbfin, slavef
71 DOUBLE PRECISION opassw, opeliw
72 INTEGER itloc( n + keep(253) ), fils( n ), dad( keep(28) )
73 COMPLEX(kind=8) :: rhs_mumps(keep(255))
74 INTEGER nd( keep(28) )
75 INTEGER(8), INTENT(IN) :: ptrarw( lptrar ), ptraiw( lptrar )
76 INTEGER frere(keep(28))
77 INTEGER intarr( keep8(27) )
78 COMPLEX(kind=8) dblarr( keep8(26) )
79 INTEGER istep_to_iniv2(keep(71)),
80 & tab_pos_in_pere(slavef+2,max(1,keep(56)))
81 INTEGER mrs_inode
82 INTEGER mrs_ison
83 INTEGER mrs_nslaves_pere
84 INTEGER mrs_nass_pere
85 INTEGER mrs_nfront_pere
86 INTEGER mrs_lmap
87 INTEGER mrs_nfs4father
88 INTEGER, POINTER, DIMENSION(:) :: mrs_slaves_pere, mrs_trow
89 INTEGER itype2
90 INTEGER ihdr_rec
91 parameter(itype2=2)
92 INTEGER ioldps, nrow, lda
93 INTEGER npiv, lcont, nelim, nass, ncol_to_send,
94 & shift_list_row_son, shift_list_col_son
95 INTEGER(8) :: shift_val_son
96 INTEGER(8) :: mem_gain
97 INTEGER(8) :: dyn_size
98#if ! defined(NO_FDM_MAPROW)
99 TYPE(maprow_struc_t), POINTER :: mrs
100#endif
101 INTEGER :: iwhandler_save
102 INTEGER :: lrstatus
103 LOGICAL :: cb_stored_in_blrstruc, compress_cb
104 IF (keep(50).EQ.0) THEN
105 ihdr_rec=6
106 ELSE
107 ihdr_rec=8
108 ENDIF
109 ioldps = ptrist(step(inode))
110 iwhandler_save = iw(ioldps+xxa)
111 lrstatus = iw(ioldps+xxlr)
112 compress_cb = ((lrstatus.EQ.1).OR.
113 & (lrstatus.EQ.3))
114 IF (.NOT.
115 & (
116 & (keep(486).EQ.2)
117 & )
118 & .AND..NOT.compress_cb) THEN
119 CALL zmumps_blr_end_front(iw(ioldps+xxf), iflag, keep8,
120 & keep(34))
121 ENDIF
122 iw(ioldps+xxs)=s_all
123 ioldps = ptrist(step(inode))
124 lrstatus = iw(ioldps+xxlr)
125 IF ( (keep(214).EQ.1)
126 & ) THEN
127 CALL zmumps_stack_band( n, inode,
128 & ptrist, ptrast, ptlust_s, ptrfac, iw, liw, a, la,
129 & lrlu, lrlus, iwpos, iwposcb, posfac, comp,
130 & iptrlu, opeliw, step, pimaster, pamaster,
131 & iflag, ierror, slavef, procnode_steps, dad, myid, comm,
132 & keep,keep8, dkeep, itype2
133 & )
134 ioldps = ptrist(step(inode))
135 IF (keep(38).NE.fpere) THEN
136 cb_stored_in_blrstruc = .false.
137 lrstatus = iw(ioldps+xxlr)
138 IF ((lrstatus.EQ.1).OR.(lrstatus.EQ.3)) THEN
139 cb_stored_in_blrstruc = .true.
140 iw(ioldps+xxs) = s_nolnocb
141 CALL mumps_geti8(mem_gain, iw(ioldps+xxr))
142 lrlus = lrlus + mem_gain
143 keep8(69) = keep8(69) - mem_gain
144 CALL zmumps_load_mem_update(.false.,.false.,
145 & la-lrlus,0_8,-mem_gain,keep,keep8,lrlus)
146 ELSE
147 iw(ioldps+xxs)=s_nolcbnocontig
148 CALL mumps_geti8( dyn_size, iw(ioldps+xxd))
149 IF (dyn_size .GT.0) THEN
150 ELSE IF (keep(216).NE.3) THEN
151 mem_gain=int(iw( ioldps + 2 + keep(ixsz) ),8)*
152 & int(iw( ioldps + 3 + keep(ixsz) ),8)
153 lrlus = lrlus+mem_gain
154 keep8(69) = keep8(69) - mem_gain
155 CALL zmumps_load_mem_update(.false.,.false.,
156 & la-lrlus,0_8,-mem_gain,keep,keep8,lrlus)
157 ENDIF
158 ENDIF
159 ENDIF
160 CALL mumps_geti8( dyn_size, iw(ioldps+xxd))
161 IF (dyn_size > 0_8) THEN
162 ELSE IF (keep(216).EQ.2) THEN
163 IF (fpere.NE.keep(38)) THEN
164 IF (.NOT. cb_stored_in_blrstruc) THEN
165 CALL zmumps_makecbcontig(a,la,ptrast(step(inode)),
166 & iw( ioldps + 2 + keep(ixsz) ),
167 & iw( ioldps + keep(ixsz) ),
168 & iw( ioldps + 3 + keep(ixsz) )+
169 & iw( ioldps + keep(ixsz) ), 0,
170 & iw( ioldps + xxs ), 0_8 )
171 iw(ioldps+xxs)=s_nolcbcontig
172 ENDIF
173 ENDIF
174 ENDIF
175 ENDIF
176 IF ( keep(38).EQ.fpere) THEN
177 lcont = iw(ioldps+keep(ixsz))
178 nrow = iw(ioldps+2+keep(ixsz))
179 npiv = iw(ioldps+3+keep(ixsz))
180 nass = iw(ioldps+4+keep(ixsz))
181 nelim = nass-npiv
182 ncol_to_send = lcont-nelim
183 shift_list_row_son = 6 + iw(ioldps+5+keep(ixsz)) + keep(ixsz)
184 shift_list_col_son = shift_list_row_son + nrow + nass
185 shift_val_son = int(nass,8)
186 lda = lcont + npiv
187 IF (iw(ioldps+ihdr_rec+keep(ixsz)).EQ.s_rootband_init) THEN
188 iw(ioldps+ihdr_rec+keep(ixsz)) = s_rec_contstatic
189 ELSE
190 ENDIF
191 CALL zmumps_build_and_send_cb_root( comm_load, ass_irecv,
192 & n, inode, fpere,
193 & ptrist, ptrast,
194 & root, nrow, ncol_to_send, shift_list_row_son,
195 & shift_list_col_son , shift_val_son, lda,
196 & root_cont_static, myid, comm,
197 &
198 & bufr, lbufr, lbufr_bytes, procnode_steps, posfac,
199 & iwpos, iwposcb, iptrlu, lrlu, lrlus, iw, liw, a, la,
200 & ptrist, ptlust_s, ptrfac, ptrast, step, pimaster,
201 & pamaster,
202 & nstk, comp, iflag, ierror, perm,
203 & ipool, lpool, leaf, nbfin, slavef,
204 & opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw,
205 & intarr,dblarr,icntl,keep,keep8,dkeep,.false.,nd,frere,
206 & lptrar, nelt, frtptr, frtelt,
207 & istep_to_iniv2, tab_pos_in_pere
208 & , lrgroups
209 & )
210 IF ( iflag < 0 ) GOTO 600
211 IF (nelim.EQ.0) THEN
212 IF (keep(214).EQ.2) THEN
213 CALL zmumps_stack_band( n, inode,
214 & ptrist, ptrast, ptlust_s, ptrfac, iw, liw, a, la,
215 & lrlu, lrlus, iwpos, iwposcb, posfac, comp,
216 & iptrlu, opeliw, step, pimaster, pamaster,
217 & iflag, ierror, slavef, procnode_steps, dad, myid,
218 & comm, keep,keep8,dkeep, itype2
219 & )
220 ENDIF
221 CALL zmumps_free_band( n, inode, ptrist, ptrast, iw, liw,
222 & a, la, lrlu, lrlus, iwposcb, iptrlu, step,
223 & myid, keep, keep8, itype2
224 & )
225 ELSE
226 ioldps = ptrist(step(inode))
227 IF (iw(ioldps+ihdr_rec+keep(ixsz)).EQ.s_root2son_called) THEN
228 CALL zmumps_free_band( n, inode, ptrist, ptrast, iw, liw,
229 & a, la, lrlu, lrlus, iwposcb, iptrlu, step,
230 & myid, keep, keep8, itype2
231 & )
232 ELSE
233 iw(ioldps+ihdr_rec+keep(ixsz)) = s_rootband_init
234 IF (keep(214).EQ.1.AND.keep(216).NE.3) THEN
235 iw(ioldps+xxs)=s_nolcbnocontig38
236 CALL zmumps_sizefreeinrec( iw(ioldps),
237 & liw-ioldps+1,
238 & mem_gain, keep(ixsz) )
239 lrlus = lrlus + mem_gain
240 keep8(69) = keep8(69) - mem_gain
241 CALL zmumps_load_mem_update(.false.,.false.,
242 & la-lrlus,0_8,-mem_gain,keep,keep8,lrlus)
243 IF (keep(216).EQ.2) THEN
244 CALL zmumps_makecbcontig(a,la,ptrast(step(inode)),
245 & iw( ioldps + 2 + keep(ixsz) ),
246 & iw( ioldps + keep(ixsz) ),
247 & iw( ioldps + 3 + keep(ixsz) )+
248 & iw( ioldps + keep(ixsz) ),
249 & iw( ioldps + 4 + keep(ixsz) ) -
250 & iw( ioldps + 3 + keep(ixsz) ),
251 & iw( ioldps + xxs ),0_8)
252 iw(ioldps+xxs)=s_nolcbcontig38
253 ENDIF
254 ENDIF
255 ENDIF
256 ENDIF
257 ENDIF
258 600 CONTINUE
259#if ! defined(NO_FDM_MAPROW)
260 ioldps = ptrist(step(inode))
261 IF (fpere .NE. keep(38)) THEN
262 IF (mumps_fmrd_is_maprow_stored( iw(ioldps+xxa) )) THEN
263 CALL mumps_fmrd_retrieve_maprow( iw(ioldps+xxa), mrs )
264 IF (fpere .NE. mrs%INODE) THEN
265 WRITE(*,*) " Internal error 1 in ZMUMPS_END_FACTO_SLAVE",
266 & inode, mrs%INODE, fpere
267 CALL mumps_abort()
268 ENDIF
269 mrs_inode = mrs%INODE
270 mrs_ison = mrs%ISON
271 mrs_nslaves_pere = mrs%NSLAVES_PERE
272 mrs_nass_pere = mrs%NASS_PERE
273 mrs_nfront_pere = mrs%NFRONT_PERE
274 mrs_lmap = mrs%LMAP
275 mrs_nfs4father = mrs%NFS4FATHER
276 mrs_slaves_pere => mrs%SLAVES_PERE
277 mrs_trow => mrs%TROW
278 CALL zmumps_maplig( comm_load, ass_irecv,
279 & bufr, lbufr, lbufr_bytes,
280 & mrs_inode, mrs_ison,
281 & mrs_nslaves_pere, mrs_slaves_pere(1),
282 & mrs_nfront_pere, mrs_nass_pere, mrs_nfs4father,
283 & mrs_lmap, mrs_trow(1),
284 & procnode_steps, slavef, posfac, iwpos, iwposcb, iptrlu, lrlu,
285 & lrlus, n, iw, liw, a, la, ptrist, ptlust_s, ptrfac,
286 & ptrast, step, pimaster, pamaster, nstk, comp,
287 & iflag, ierror, myid, comm, perm, ipool, lpool, leaf,
288 & nbfin, icntl, keep,keep8,dkeep,
289 & root, opassw, opeliw,
290 & itloc, rhs_mumps,
291 & fils, dad, ptrarw, ptraiw, intarr, dblarr, nd, frere,
292 & lptrar, nelt, frtptr, frtelt,
293 &
294 & istep_to_iniv2, tab_pos_in_pere
295 & , lrgroups
296 & )
297 CALL mumps_fmrd_free_maprow_struc( iwhandler_save )
298 ENDIF
299 ENDIF
300#endif
301 RETURN
302 END SUBROUTINE zmumps_end_facto_slave
#define mumps_abort
Definition VE_Metis.h:25
#define max(a, b)
Definition macros.h:21
logical function, public mumps_fmrd_is_maprow_stored(iwhandler)
subroutine, public mumps_fmrd_free_maprow_struc(iwhandler)
subroutine, public mumps_fmrd_retrieve_maprow(iwhandler, maprow_struc)
integer, save, private myid
Definition zmumps_load.F:57
subroutine, public zmumps_load_mem_update(ssarbr, process_bande_arg, mem_value, new_lu, inc_mem_arg, keep, keep8, lrlus)
subroutine, public zmumps_blr_end_front(iwhandler, info1, keep8, k34, lrsolve_act_opt, mtk405)
int comp(int a, int b)
subroutine mumps_geti8(i8, int_array)
subroutine zmumps_makecbcontig(a, la, rcurrent, nrow, ncb, ld, nelim, nodestate, ishift)
subroutine zmumps_sizefreeinrec(iw, lrec, size_free, xsize)
recursive subroutine zmumps_end_facto_slave(comm_load, ass_irecv, n, inode, fpere, root, myid, comm bufr, lbufr, lbufr_bytes, procnode_steps, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, iw, liw, a, la, ptrist, ptlust_s, ptrfac, ptrast, step, pimaster, pamaster, nstk, comp, iflag, ierror, perm, ipool, lpool, leaf, nbfin, slavef, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, icntl, keep, keep8, dkeep, nd, frere, lptrar, nelt, frtptr, frtelt, istep_to_iniv2, tab_pos_in_pere, lrgroups)
recursive subroutine zmumps_maplig(comm_load, ass_irecv, bufr, lbufr, lbufr_bytes inode_pere, ison, nslaves_pere, list_slaves_pere, nfront_pere, nass_pere, nfs4father, lmap, trow, procnode_steps, slavef, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, ptrist, ptlust, ptrfac, ptrast, step, pimaster, pamaster, nstk, comp, iflag, ierror, myid, comm, perm, ipool, lpool, leaf, nbfin, icntl, keep, keep8, dkeep, root, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, nd, frere, lptrar, nelt, frtptr, frtelt, istep_to_iniv2, tab_pos_in_pere, lrgroups)
subroutine zmumps_free_band(n, ison, ptrist, ptrast, iw, liw, a, la, lrlu, lrlus, iwposcb, iptrlu, step, myid, keep, keep8, type_son)
Definition ztools.F:461
subroutine zmumps_stack_band(n, ison, ptrist, ptrast, ptlust_s, ptrfac, iw, liw, a, la, lrlu, lrlus, iwpos, iwposcb, posfac, comp, iptrlu, opeliw, step, pimaster, pamaster, iflag, ierror, slavef, procnode_steps, dad, myid, comm, keep, keep8, dkeep, type_son)
Definition ztools.F:219
recursive subroutine zmumps_build_and_send_cb_root(comm_load, ass_irecv, n, ison, iroot, ptri, ptrr, root, nbrow, nbcol, shift_list_row_son, shift_list_col_son, shift_val_son_arg, lda_arg, tag, myid, comm, bufr, lbufr, lbufr_bytes, procnode_steps, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, iw, liw, a, la, ptrist, ptlust_s, ptrfac, ptrast, step, pimaster, pamaster, nstk, comp, iflag, ierror, perm, ipool, lpool, leaf, nbfin, slavef, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, icntl, keep, keep8, dkeep, transpose_asm, nd, frere, lptrar, nelt, frtptr, frtelt, istep_to_iniv2, tab_pos_in_pere, lrgroups)
Definition ztype3_root.F:84