OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zmumps_ooc_buffer Module Reference

Functions/Subroutines

subroutine zmumps_ooc_next_hbuf (typef_arg)
subroutine zmumps_ooc_do_io_and_chbuf (typef_arg, ierr)
subroutine zmumps_ooc_buf_clean_pending (ierr)
subroutine zmumps_ooc_wrt_cur_buf2disk (typef_arg, iorequest, ierr)
subroutine zmumps_init_ooc_buf (i1, i2, ierr)
subroutine zmumps_end_ooc_buf ()
subroutine zmumps_ooc_init_db_buffer ()
subroutine zmumps_ooc_copy_data_to_buffer (block, size_of_block, ierr)
subroutine zmumps_ooc_init_db_buffer_panel ()
subroutine zmumps_ooc_tryio_chbuf_panel (typef, ierr)
subroutine zmumps_ooc_upd_vaddr_cur_buf (typef, vaddr)
subroutine zmumps_copy_lu_to_buffer (strat, typef, monbloc, afac, lafac, addvirtcour, ipivbeg, ipivend, lpaneleff, ierr)

Variables

integer first_hbuf
integer second_hbuf
integer, save ooc_fct_type_loc
complex(kind=8), dimension(:), allocatable buf_io
logical, save panel_flag
integer, save earliest_write_min_size
integer(8), dimension(:), allocatable, save i_shift_first_hbuf
integer(8), dimension(:), allocatable, save i_shift_second_hbuf
integer(8), dimension(:), allocatable, save i_shift_cur_hbuf
integer(8), dimension(:), allocatable, save i_rel_pos_cur_hbuf
integer, dimension(:), allocatable, save last_iorequest
integer, dimension(:), allocatable, save cur_hbuf
integer, dimension(:), allocatable i_cur_hbuf_nextpos
integer, save i_cur_hbuf_fstpos
integer, save i_sub_hbuf_fstpos
integer(8) bufferempty
integer(8), dimension(:), allocatable nextaddvirtbuffer
integer(8), dimension(:), allocatable first_vaddr_in_buf

Function/Subroutine Documentation

◆ zmumps_copy_lu_to_buffer()

subroutine zmumps_ooc_buffer::zmumps_copy_lu_to_buffer ( integer, intent(in) strat,
integer, intent(in) typef,
type(io_block), intent(in) monbloc,
complex(kind=8), dimension(lafac), intent(in) afac,
integer(8), intent(in) lafac,
integer(8), intent(in) addvirtcour,
integer, intent(in) ipivbeg,
integer, intent(in) ipivend,
integer, intent(out) lpaneleff,
integer, intent(out) ierr )

Definition at line 448 of file zmumps_ooc_buffer.F.

452 IMPLICIT NONE
453 INTEGER, INTENT(IN) :: TYPEF, IPIVBEG, IPIVEND, STRAT
454 INTEGER(8), INTENT(IN) :: LAFAC
455 COMPLEX(kind=8), INTENT(IN) :: AFAC(LAFAC)
456 INTEGER(8), INTENT(IN) :: AddVirtCour
457 TYPE(IO_BLOCK), INTENT(IN) :: MonBloc
458 INTEGER, INTENT(OUT):: LPANELeff
459 INTEGER, INTENT(OUT):: IERR
460 INTEGER :: II, NBPIVeff
461 INTEGER(8) :: IPOS, IDIAG, IDEST
462 INTEGER(8) :: DeltaIPOS
463 INTEGER :: StrideIPOS
464 ierr=0
465 IF (strat.NE.strat_write_max.AND.strat.NE.strat_try_write) THEN
466 write(6,*) ' ZMUMPS_COPY_LU_TO_BUFFER: STRAT Not implemented '
467 CALL mumps_abort()
468 ENDIF
469 nbpiveff = ipivend - ipivbeg + 1
470 IF (monbloc%MASTER .AND. monbloc%Typenode .NE. 3) THEN
471 IF (typef.EQ.typef_l) THEN
472 lpaneleff = (monbloc%NROW-ipivbeg+1)*nbpiveff
473 ELSE
474 lpaneleff = (monbloc%NCOL-ipivbeg+1)*nbpiveff
475 ENDIF
476 ELSE
477 lpaneleff = monbloc%NROW*nbpiveff
478 ENDIF
479 IF ( ( i_rel_pos_cur_hbuf(typef) + int(lpaneleff - 1,8)
480 & >
481 & hbuf_size )
482 & .OR.
483 & ( (addvirtcour.NE.nextaddvirtbuffer(typef)) .AND.
484 & (nextaddvirtbuffer(typef).NE.bufferempty) )
485 & ) THEN
486 IF (strat.EQ.strat_write_max) THEN
487 CALL zmumps_ooc_do_io_and_chbuf(typef,ierr)
488 ELSE IF (strat.EQ.strat_try_write) THEN
489 CALL zmumps_ooc_tryio_chbuf_panel(typef,ierr)
490 IF (ierr.EQ.1) RETURN
491 ELSE
492 write(6,*) 'ZMUMPS_COPY_LU_TO_BUFFER: STRAT Not implemented'
493 ENDIF
494 ENDIF
495 IF (ierr < 0 ) THEN
496 RETURN
497 ENDIF
498 IF (nextaddvirtbuffer(typef).EQ. bufferempty) THEN
499 CALL zmumps_ooc_upd_vaddr_cur_buf (typef,addvirtcour)
500 nextaddvirtbuffer(typef) = addvirtcour
501 ENDIF
502 IF (monbloc%MASTER .AND. monbloc%Typenode .NE. 3) THEN
503 idiag = int(ipivbeg-1,8)*int(monbloc%NCOL,8) + int(ipivbeg,8)
504 ipos = idiag
505 idest = i_shift_cur_hbuf(typef) +
506 & i_rel_pos_cur_hbuf(typef)
507 IF (typef.EQ.typef_l) THEN
508 DO ii = ipivbeg, ipivend
509 CALL zcopy(monbloc%NROW-ipivbeg+1,
510 & afac(ipos), monbloc%NCOL,
511 & buf_io(idest), 1)
512 idest = idest + int(monbloc%NROW-ipivbeg+1,8)
513 ipos = ipos + 1_8
514 ENDDO
515 ELSE
516 DO ii = ipivbeg, ipivend
517 CALL zcopy(monbloc%NCOL-ipivbeg+1,
518 & afac(ipos), 1,
519 & buf_io(idest), 1)
520 idest = idest + int(monbloc%NCOL-ipivbeg+1,8)
521 ipos = ipos + int(monbloc%NCOL,8)
522 ENDDO
523 ENDIF
524 ELSE
525 idest = i_shift_cur_hbuf(typef) +
526 & i_rel_pos_cur_hbuf(typef)
527 IF (monbloc%Typenode.EQ.3) THEN
528 deltaipos = int(monbloc%NROW,8)
529 strideipos = 1
530 ELSE
531 deltaipos = 1_8
532 strideipos = monbloc%NCOL
533 ENDIF
534 ipos = 1_8 + int(ipivbeg - 1,8) * deltaipos
535 DO ii = ipivbeg, ipivend
536 CALL zcopy(monbloc%NROW,
537 & afac(ipos), strideipos,
538 & buf_io(idest), 1)
539 idest = idest+int(monbloc%NROW,8)
540 ipos = ipos + deltaipos
541 ENDDO
542 ENDIF
543 i_rel_pos_cur_hbuf(typef) =
544 & i_rel_pos_cur_hbuf(typef) + int(lpaneleff,8)
545 nextaddvirtbuffer(typef) = nextaddvirtbuffer(typef)
546 & + int(lpaneleff,8)
547 RETURN
#define mumps_abort
Definition VE_Metis.h:25
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
Definition zcopy.f:81

◆ zmumps_end_ooc_buf()

subroutine zmumps_ooc_buffer::zmumps_end_ooc_buf

Definition at line 302 of file zmumps_ooc_buffer.F.

303 IMPLICIT NONE
304 IF(allocated(buf_io))THEN
305 DEALLOCATE(buf_io)
306 ENDIF
307 IF(allocated(i_shift_first_hbuf))THEN
308 DEALLOCATE(i_shift_first_hbuf)
309 ENDIF
310 IF(allocated(i_shift_second_hbuf))THEN
311 DEALLOCATE(i_shift_second_hbuf)
312 ENDIF
313 IF(allocated(i_shift_cur_hbuf))THEN
314 DEALLOCATE(i_shift_cur_hbuf)
315 ENDIF
316 IF(allocated(i_rel_pos_cur_hbuf))THEN
317 DEALLOCATE(i_rel_pos_cur_hbuf)
318 ENDIF
319 IF(allocated(last_iorequest))THEN
320 DEALLOCATE(last_iorequest)
321 ENDIF
322 IF(allocated(cur_hbuf))THEN
323 DEALLOCATE(cur_hbuf)
324 ENDIF
325 IF(panel_flag)THEN
326 IF(allocated(nextaddvirtbuffer))THEN
327 DEALLOCATE(nextaddvirtbuffer)
328 ENDIF
329 IF(allocated(addvirtlibre))THEN
330 DEALLOCATE(addvirtlibre)
331 ENDIF
332 IF(allocated(first_vaddr_in_buf))THEN
333 DEALLOCATE(first_vaddr_in_buf)
334 ENDIF
335 ENDIF
336 RETURN

◆ zmumps_init_ooc_buf()

subroutine zmumps_ooc_buffer::zmumps_init_ooc_buf ( integer i1,
integer i2,
integer ierr )

Definition at line 146 of file zmumps_ooc_buffer.F.

147 IMPLICIT NONE
148 INTEGER I1,I2,IERR
149 INTEGER allocok
150 ierr=0
151 panel_flag=.false.
152 IF(allocated(i_shift_first_hbuf))THEN
153 DEALLOCATE(i_shift_first_hbuf)
154 ENDIF
155 IF(allocated(i_shift_second_hbuf))THEN
156 DEALLOCATE(i_shift_second_hbuf)
157 ENDIF
158 IF(allocated(i_shift_cur_hbuf))THEN
159 DEALLOCATE(i_shift_cur_hbuf)
160 ENDIF
161 IF(allocated(i_rel_pos_cur_hbuf))THEN
162 DEALLOCATE(i_rel_pos_cur_hbuf)
163 ENDIF
164 IF(allocated(last_iorequest))THEN
165 DEALLOCATE(last_iorequest)
166 ENDIF
167 IF(allocated(cur_hbuf))THEN
168 DEALLOCATE(cur_hbuf)
169 ENDIF
170 dim_buf_io = int(keep_ooc(100),8)
171 ALLOCATE(i_shift_first_hbuf(ooc_nb_file_type),
172 & stat=allocok)
173 IF (allocok > 0) THEN
174 IF (icntl1>0) THEN
175 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
176 ENDIF
177 i1 = -13
178 i2 = ooc_nb_file_type
179 ierr=-1
180 RETURN
181 ENDIF
182 ALLOCATE(i_shift_second_hbuf(ooc_nb_file_type),
183 & stat=allocok)
184 IF (allocok > 0) THEN
185 IF (icntl1>0) THEN
186 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
187 ENDIF
188 i1 = -13
189 i2 = ooc_nb_file_type
190 ierr=-1
191 RETURN
192 ENDIF
193 ALLOCATE(i_shift_cur_hbuf(ooc_nb_file_type),
194 & stat=allocok)
195 IF (allocok > 0) THEN
196 IF (icntl1>0) THEN
197 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
198 ENDIF
199 i1 = -13
200 i2 = ooc_nb_file_type
201 ierr=-1
202 RETURN
203 ENDIF
204 ALLOCATE(i_rel_pos_cur_hbuf(ooc_nb_file_type),
205 & stat=allocok)
206 IF (allocok > 0) THEN
207 IF (icntl1>0) THEN
208 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
209 ENDIF
210 i1 = -13
211 i2 = ooc_nb_file_type
212 ierr=-1
213 RETURN
214 ENDIF
215 ALLOCATE(last_iorequest(ooc_nb_file_type),
216 & stat=allocok)
217 IF (allocok > 0) THEN
218 IF (icntl1>0) THEN
219 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
220 ENDIF
221 i1 = -13
222 i2 = ooc_nb_file_type
223 ierr=-1
224 RETURN
225 ENDIF
226 ALLOCATE(cur_hbuf(ooc_nb_file_type),
227 & stat=allocok)
228 IF (allocok > 0) THEN
229 IF (icntl1>0) THEN
230 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
231 ENDIF
232 i1 = -13
233 i2 = ooc_nb_file_type
234 ierr=-1
235 RETURN
236 ENDIF
237 ooc_fct_type_loc=ooc_nb_file_type
238 ALLOCATE(buf_io(dim_buf_io), stat=allocok)
239 IF (allocok > 0) THEN
240 IF (icntl1>0) THEN
241 WRITE(icntl1,*) 'PB allocation in ZMUMPS_INIT_OOC'
242 ENDIF
243 i1 = -13
244 CALL mumps_set_ierror(dim_buf_io, i2)
245 RETURN
246 ENDIF
247 panel_flag=(keep_ooc(201).EQ.1)
248 IF (panel_flag) THEN
249 ierr=0
250 keep_ooc(228)=0
251 IF(allocated(addvirtlibre))THEN
252 DEALLOCATE(addvirtlibre)
253 ENDIF
254 ALLOCATE(addvirtlibre(ooc_nb_file_type), stat=allocok)
255 IF (allocok > 0) THEN
256 IF (icntl1>0) THEN
257 WRITE(icntl1,*) 'PB allocation in ',
258 & 'ZMUMPS_INIT_OOC_BUF_PANEL'
259 ENDIF
260 ierr=-1
261 i1=-13
262 i2=ooc_nb_file_type
263 RETURN
264 ENDIF
265 addvirtlibre(1:ooc_nb_file_type)=0_8
266 IF(allocated(nextaddvirtbuffer))THEN
267 DEALLOCATE(nextaddvirtbuffer)
268 ENDIF
269 ALLOCATE(nextaddvirtbuffer(ooc_nb_file_type), stat=allocok)
270 IF (allocok > 0) THEN
271 IF (icntl1>0) THEN
272 WRITE(icntl1,*) 'PB allocation in ',
273 & 'ZMUMPS_INIT_OOC_BUF_PANEL'
274 ENDIF
275 ierr=-1
276 i1=-13
277 i2=ooc_nb_file_type
278 RETURN
279 ENDIF
280 nextaddvirtbuffer(1:ooc_nb_file_type) = bufferempty
281 IF(allocated(first_vaddr_in_buf))THEN
282 DEALLOCATE(first_vaddr_in_buf)
283 ENDIF
284 ALLOCATE(first_vaddr_in_buf(ooc_nb_file_type), stat=allocok)
285 IF (allocok > 0) THEN
286 IF (icntl1>0) THEN
287 WRITE(icntl1,*) 'PB allocation in ',
288 & 'ZMUMPS_INIT_OOC_BUF_PANEL'
289 ENDIF
290 ierr=-1
291 i1=-13
292 i2=ooc_nb_file_type
293 RETURN
294 ENDIF
295 CALL zmumps_ooc_init_db_buffer_panel()
296 ELSE
297 CALL zmumps_ooc_init_db_buffer()
298 ENDIF
299 keep_ooc(223)=int(hbuf_size)
300 RETURN
subroutine mumps_set_ierror(size8, ierror)

◆ zmumps_ooc_buf_clean_pending()

subroutine zmumps_ooc_buffer::zmumps_ooc_buf_clean_pending ( integer, intent(out) ierr)

Definition at line 82 of file zmumps_ooc_buffer.F.

83 IMPLICIT NONE
84 INTEGER, intent(out) :: IERR
85 INTEGER TYPEF_LAST
86 INTEGER TYPEF_LOC
87 ierr = 0
88 typef_last = ooc_nb_file_type
89 DO typef_loc = 1, typef_last
90 ierr=0
91 CALL zmumps_ooc_do_io_and_chbuf(typef_loc,ierr)
92 IF(ierr.LT.0)THEN
93 RETURN
94 ENDIF
95 ierr=0
96 CALL zmumps_ooc_do_io_and_chbuf(typef_loc,ierr)
97 IF(ierr.LT.0)THEN
98 RETURN
99 ENDIF
100 ENDDO
101 RETURN

◆ zmumps_ooc_copy_data_to_buffer()

subroutine zmumps_ooc_buffer::zmumps_ooc_copy_data_to_buffer ( complex(kind=8), dimension(size_of_block) block,
integer(8) size_of_block,
integer, intent(out) ierr )

Definition at line 352 of file zmumps_ooc_buffer.F.

354 IMPLICIT NONE
355 INTEGER(8) :: SIZE_OF_BLOCK
356 COMPLEX(kind=8) BLOCK(SIZE_OF_BLOCK)
357 INTEGER, intent(out) :: IERR
358 INTEGER(8) :: I
359 ierr=0
360 IF (i_rel_pos_cur_hbuf(ooc_fct_type_loc) +
361 & size_of_block <= hbuf_size + 1_8) THEN
362 ELSE
363 CALL zmumps_ooc_do_io_and_chbuf(ooc_fct_type_loc,ierr)
364 IF(ierr.LT.0)THEN
365 RETURN
366 ENDIF
367 END IF
368 DO i = 1_8, size_of_block
369 buf_io(i_shift_cur_hbuf(ooc_fct_type_loc) +
370 & i_rel_pos_cur_hbuf(ooc_fct_type_loc) + i - 1_8) =
371 & block(i)
372 END DO
373 i_rel_pos_cur_hbuf(ooc_fct_type_loc) =
374 & i_rel_pos_cur_hbuf(ooc_fct_type_loc) + size_of_block
375 RETURN

◆ zmumps_ooc_do_io_and_chbuf()

subroutine zmumps_ooc_buffer::zmumps_ooc_do_io_and_chbuf ( integer typef_arg,
integer ierr )

Definition at line 57 of file zmumps_ooc_buffer.F.

58 IMPLICIT NONE
59 INTEGER TYPEF_ARG
60 INTEGER NEW_IOREQUEST
61 INTEGER IERR
62 ierr=0
63 CALL zmumps_ooc_wrt_cur_buf2disk(typef_arg,new_iorequest,
64 & ierr)
65 IF(ierr.LT.0)THEN
66 RETURN
67 ENDIF
68 ierr=0
69 CALL mumps_wait_request(last_iorequest(typef_arg),ierr)
70 IF(ierr.LT.0)THEN
71 IF (icntl1>0)
72 & WRITE(icntl1,*) myid_ooc,': ',err_str_ooc(1:dim_err_str_ooc)
73 RETURN
74 ENDIF
75 last_iorequest(typef_arg) = new_iorequest
76 CALL zmumps_ooc_next_hbuf(typef_arg)
77 IF(panel_flag)THEN
78 nextaddvirtbuffer(typef_arg)=bufferempty
79 ENDIF
80 RETURN

◆ zmumps_ooc_init_db_buffer()

subroutine zmumps_ooc_buffer::zmumps_ooc_init_db_buffer

Definition at line 338 of file zmumps_ooc_buffer.F.

339 IMPLICIT NONE
340 ooc_fct_type_loc=1
341 hbuf_size = dim_buf_io / int(2,kind=kind(dim_buf_io))
342 earliest_write_min_size = 0
343 i_shift_first_hbuf(ooc_fct_type_loc) = 0_8
344 i_shift_second_hbuf(ooc_fct_type_loc) = hbuf_size
345 last_iorequest(ooc_fct_type_loc) = -1
346 i_cur_hbuf_nextpos = 1
347 i_cur_hbuf_fstpos = 1
348 i_sub_hbuf_fstpos = 1
349 cur_hbuf(ooc_fct_type_loc) = second_hbuf
350 CALL zmumps_ooc_next_hbuf(ooc_fct_type_loc)

◆ zmumps_ooc_init_db_buffer_panel()

subroutine zmumps_ooc_buffer::zmumps_ooc_init_db_buffer_panel

Definition at line 377 of file zmumps_ooc_buffer.F.

378 IMPLICIT NONE
379 INTEGER(8) :: DIM_BUF_IO_L_OR_U
380 INTEGER TYPEF, TYPEF_LAST
381 INTEGER NB_DOUBLE_BUFFERS
382 typef_last = ooc_nb_file_type
383 nb_double_buffers = ooc_nb_file_type
384 dim_buf_io_l_or_u = dim_buf_io /
385 & int(nb_double_buffers,kind=kind(dim_buf_io_l_or_u))
386 IF(.NOT.strat_io_async)THEN
387 hbuf_size = dim_buf_io_l_or_u
388 ELSE
389 hbuf_size = dim_buf_io_l_or_u / 2_8
390 ENDIF
391 DO typef = 1, typef_last
392 last_iorequest(typef) = -1
393 IF (typef == 1 ) THEN
394 i_shift_first_hbuf(typef) = 0_8
395 ELSE
396 i_shift_first_hbuf(typef) = dim_buf_io_l_or_u
397 ENDIF
398 IF(.NOT.strat_io_async)THEN
399 i_shift_second_hbuf(typef) = i_shift_first_hbuf(typef)
400 ELSE
401 i_shift_second_hbuf(typef) = i_shift_first_hbuf(typef) +
402 & hbuf_size
403 ENDIF
404 cur_hbuf(typef) = second_hbuf
405 CALL zmumps_ooc_next_hbuf(typef)
406 ENDDO
407 i_cur_hbuf_nextpos = 1
408 RETURN

◆ zmumps_ooc_next_hbuf()

subroutine zmumps_ooc_buffer::zmumps_ooc_next_hbuf ( integer typef_arg)

Definition at line 37 of file zmumps_ooc_buffer.F.

38 IMPLICIT NONE
39 INTEGER TYPEF_ARG
40 SELECT CASE(cur_hbuf(typef_arg))
41 CASE (first_hbuf)
42 cur_hbuf(typef_arg) = second_hbuf
43 i_shift_cur_hbuf(typef_arg) =
44 & i_shift_second_hbuf(typef_arg)
45 CASE (second_hbuf)
46 cur_hbuf(typef_arg) = first_hbuf
47 i_shift_cur_hbuf(typef_arg) =
48 & i_shift_first_hbuf(typef_arg)
49 END SELECT
50 IF(.NOT.panel_flag)THEN
51 i_sub_hbuf_fstpos =i_cur_hbuf_fstpos
52 i_cur_hbuf_fstpos =i_cur_hbuf_nextpos(typef_arg)
53 ENDIF
54 i_rel_pos_cur_hbuf(typef_arg) = 1_8
55 RETURN

◆ zmumps_ooc_tryio_chbuf_panel()

subroutine zmumps_ooc_buffer::zmumps_ooc_tryio_chbuf_panel ( integer, intent(in) typef,
integer, intent(out) ierr )

Definition at line 410 of file zmumps_ooc_buffer.F.

411 IMPLICIT NONE
412 INTEGER, INTENT(in) :: TYPEF
413 INTEGER, INTENT(out) :: IERR
414 INTEGER IFLAG
415 INTEGER NEW_IOREQUEST
416 ierr=0
417 CALL mumps_test_request_c(last_iorequest(typef),iflag,
418 & ierr)
419 IF (iflag.EQ.1) THEN
420 ierr = 0
421 CALL zmumps_ooc_wrt_cur_buf2disk(typef,
422 & new_iorequest,
423 & ierr)
424 IF(ierr.LT.0)THEN
425 RETURN
426 ENDIF
427 last_iorequest(typef) = new_iorequest
428 CALL zmumps_ooc_next_hbuf(typef)
429 nextaddvirtbuffer(typef)=bufferempty
430 RETURN
431 ELSE IF(iflag.LT.0)THEN
432 WRITE(*,*)myid_ooc,': ',err_str_ooc(1:dim_err_str_ooc)
433 RETURN
434 ELSE
435 ierr = 1
436 RETURN
437 ENDIF

◆ zmumps_ooc_upd_vaddr_cur_buf()

subroutine zmumps_ooc_buffer::zmumps_ooc_upd_vaddr_cur_buf ( integer, intent(in) typef,
integer(8), intent(in) vaddr )

Definition at line 439 of file zmumps_ooc_buffer.F.

440 IMPLICIT NONE
441 INTEGER(8), INTENT(in) :: VADDR
442 INTEGER, INTENT(in) :: TYPEF
443 IF(i_rel_pos_cur_hbuf(typef).EQ.1_8)THEN
444 first_vaddr_in_buf(typef)=vaddr
445 ENDIF
446 RETURN

◆ zmumps_ooc_wrt_cur_buf2disk()

subroutine zmumps_ooc_buffer::zmumps_ooc_wrt_cur_buf2disk ( integer typef_arg,
integer iorequest,
integer ierr )

Definition at line 103 of file zmumps_ooc_buffer.F.

105 IMPLICIT NONE
106 INTEGER IOREQUEST,IERR
107 INTEGER TYPEF_ARG
108 INTEGER FIRST_INODE
109 INTEGER(8) :: FROM_BUFIO_POS, SIZE
110 INTEGER TYPE
111 INTEGER ADDR_INT1,ADDR_INT2
112 INTEGER(8) TMP_VADDR
113 INTEGER SIZE_INT1,SIZE_INT2
114 ierr=0
115 IF (i_rel_pos_cur_hbuf(typef_arg) == 1_8) THEN
116 iorequest=-1
117 RETURN
118 END IF
119 IF(panel_flag)THEN
120 TYPE=typef_arg-1
121 first_inode=-9999
122 tmp_vaddr=first_vaddr_in_buf(typef_arg)
123 ELSE
124 TYPE=fct
125 first_inode =
126 & ooc_inode_sequence(i_cur_hbuf_fstpos,typef_arg)
127 tmp_vaddr=ooc_vaddr(step_ooc(first_inode),typef_arg)
128 ENDIF
129 from_bufio_pos=i_shift_cur_hbuf(typef_arg)+1_8
130 SIZE = i_rel_pos_cur_hbuf(typef_arg)-1_8
131 CALL mumps_ooc_convert_bigintto2int(addr_int1,addr_int2,
132 & tmp_vaddr)
133 CALL mumps_ooc_convert_bigintto2int(size_int1,size_int2,
134 & size)
135 CALL mumps_low_level_write_ooc_c(low_level_strat_io,
136 & buf_io(from_bufio_pos),size_int1,size_int2,
137 & first_inode,iorequest,
138 & TYPE,ADDR_INT1,ADDR_INT2,IERR)
139 IF(ierr.LT.0)THEN
140 IF (icntl1>0)
141 & WRITE(icntl1,*)myid_ooc,': ',err_str_ooc(1:dim_err_str_ooc)
142 RETURN
143 ENDIF
144 RETURN
subroutine mumps_ooc_convert_bigintto2int(int1, int2, bigint)

Variable Documentation

◆ buf_io

complex(kind=8), dimension(:), allocatable zmumps_ooc_buffer::buf_io

Definition at line 21 of file zmumps_ooc_buffer.F.

21 COMPLEX(kind=8), DIMENSION(:),ALLOCATABLE :: BUF_IO

◆ bufferempty

integer(8) zmumps_ooc_buffer::bufferempty

Definition at line 32 of file zmumps_ooc_buffer.F.

32 INTEGER(8) :: BufferEmpty

◆ cur_hbuf

integer, dimension(:), allocatable, save zmumps_ooc_buffer::cur_hbuf

Definition at line 27 of file zmumps_ooc_buffer.F.

◆ earliest_write_min_size

integer, save zmumps_ooc_buffer::earliest_write_min_size

Definition at line 23 of file zmumps_ooc_buffer.F.

23 INTEGER,SAVE :: EARLIEST_WRITE_MIN_SIZE

◆ first_hbuf

integer zmumps_ooc_buffer::first_hbuf

Definition at line 18 of file zmumps_ooc_buffer.F.

18 INTEGER FIRST_HBUF,SECOND_HBUF

◆ first_vaddr_in_buf

integer(8), dimension(:), allocatable zmumps_ooc_buffer::first_vaddr_in_buf

Definition at line 35 of file zmumps_ooc_buffer.F.

35 INTEGER(8), DIMENSION(:),ALLOCATABLE :: FIRST_VADDR_IN_BUF

◆ i_cur_hbuf_fstpos

integer, save zmumps_ooc_buffer::i_cur_hbuf_fstpos

Definition at line 30 of file zmumps_ooc_buffer.F.

30 INTEGER,SAVE :: I_CUR_HBUF_FSTPOS,
31 & I_SUB_HBUF_FSTPOS

◆ i_cur_hbuf_nextpos

integer, dimension(:), allocatable zmumps_ooc_buffer::i_cur_hbuf_nextpos

Definition at line 29 of file zmumps_ooc_buffer.F.

29 INTEGER, DIMENSION(:),ALLOCATABLE :: I_CUR_HBUF_NEXTPOS

◆ i_rel_pos_cur_hbuf

integer(8), dimension(:), allocatable, save zmumps_ooc_buffer::i_rel_pos_cur_hbuf

Definition at line 24 of file zmumps_ooc_buffer.F.

◆ i_shift_cur_hbuf

integer(8), dimension(:), allocatable, save zmumps_ooc_buffer::i_shift_cur_hbuf

Definition at line 24 of file zmumps_ooc_buffer.F.

◆ i_shift_first_hbuf

integer(8), dimension(:), allocatable, save zmumps_ooc_buffer::i_shift_first_hbuf

Definition at line 24 of file zmumps_ooc_buffer.F.

24 INTEGER(8),SAVE,DIMENSION(:), ALLOCATABLE ::
25 & I_SHIFT_FIRST_HBUF, I_SHIFT_SECOND_HBUF,
26 & I_SHIFT_CUR_HBUF, I_REL_POS_CUR_HBUF

◆ i_shift_second_hbuf

integer(8), dimension(:), allocatable, save zmumps_ooc_buffer::i_shift_second_hbuf

Definition at line 24 of file zmumps_ooc_buffer.F.

◆ i_sub_hbuf_fstpos

integer, save zmumps_ooc_buffer::i_sub_hbuf_fstpos

Definition at line 30 of file zmumps_ooc_buffer.F.

◆ last_iorequest

integer, dimension(:), allocatable, save zmumps_ooc_buffer::last_iorequest

Definition at line 27 of file zmumps_ooc_buffer.F.

27 INTEGER, SAVE, DIMENSION(:), ALLOCATABLE ::
28 & LAST_IOREQUEST, CUR_HBUF

◆ nextaddvirtbuffer

integer(8), dimension(:), allocatable zmumps_ooc_buffer::nextaddvirtbuffer

Definition at line 34 of file zmumps_ooc_buffer.F.

34 INTEGER(8), DIMENSION(:),ALLOCATABLE :: NextAddVirtBuffer

◆ ooc_fct_type_loc

integer, save zmumps_ooc_buffer::ooc_fct_type_loc

Definition at line 20 of file zmumps_ooc_buffer.F.

20 INTEGER,SAVE :: OOC_FCT_TYPE_LOC

◆ panel_flag

logical, save zmumps_ooc_buffer::panel_flag

Definition at line 22 of file zmumps_ooc_buffer.F.

22 LOGICAL,SAVE :: PANEL_FLAG

◆ second_hbuf

integer zmumps_ooc_buffer::second_hbuf

Definition at line 18 of file zmumps_ooc_buffer.F.