21 COMPLEX,
DIMENSION(:),
ALLOCATABLE ::
buf_io
24 INTEGER(8),
SAVE,
DIMENSION(:),
ALLOCATABLE ::
27 INTEGER,
SAVE,
DIMENSION(:),
ALLOCATABLE ::
84 INTEGER,
intent(out) :: IERR
89 DO typef_loc = 1, typef_last
106 INTEGER IOREQUEST,IERR
109 INTEGER(8) :: FROM_BUFIO_POS, SIZE
111 INTEGER ADDR_INT1,ADDR_INT2
113 INTEGER SIZE_INT1,SIZE_INT2
136 &
buf_io(from_bufio_pos),size_int1,size_int2,
137 & first_inode,iorequest,
138 &
TYPE,addr_int1,addr_int2,ierr)
173 IF (allocok > 0)
THEN
175 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
184 IF (allocok > 0)
THEN
186 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
195 IF (allocok > 0)
THEN
197 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
206 IF (allocok > 0)
THEN
208 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
217 IF (allocok > 0)
THEN
219 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
228 IF (allocok > 0)
THEN
230 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
239 IF (allocok > 0)
THEN
241 WRITE(
icntl1,*)
'PB allocation in CMUMPS_INIT_OOC'
255 IF (allocok > 0)
THEN
257 WRITE(
icntl1,*)
'PB allocation in ',
258 &
'CMUMPS_INIT_OOC_BUF_PANEL'
270 IF (allocok > 0)
THEN
272 WRITE(
icntl1,*)
'PB allocation in ',
273 &
'CMUMPS_INIT_OOC_BUF_PANEL'
285 IF (allocok > 0)
THEN
287 WRITE(
icntl1,*)
'PB allocation in ',
288 &
'CMUMPS_INIT_OOC_BUF_PANEL'
355 INTEGER(8) :: SIZE_OF_BLOCK
356 COMPLEX BLOCK(SIZE_OF_BLOCK)
357 INTEGER,
intent(out) :: IERR
368 DO i = 1_8, size_of_block
379 INTEGER(8) :: DIM_BUF_IO_L_OR_U
380 INTEGER TYPEF, TYPEF_LAST
381 INTEGER NB_DOUBLE_BUFFERS
385 & int(nb_double_buffers,kind=kind(dim_buf_io_l_or_u))
391 DO typef = 1, typef_last
393 IF (typef == 1 )
THEN
412 INTEGER,
INTENT(in) :: TYPEF
413 INTEGER,
INTENT(out) :: IERR
415 INTEGER NEW_IOREQUEST
431 ELSE IF(iflag.LT.0)
THEN
441 INTEGER(8),
INTENT(in) :: VADDR
442 INTEGER,
INTENT(in) :: TYPEF
450 & AddVirtCour, IPIVBEG, IPIVEND, LPANELeff,
453 INTEGER,
INTENT(IN) :: TYPEF, IPIVBEG, IPIVEND, STRAT
454 INTEGER(8),
INTENT(IN) :: LAFAC
455 COMPLEX,
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
466 write(6,*)
' CMUMPS_COPY_LU_TO_BUFFER: STRAT Not implemented '
469 nbpiveff = ipivend - ipivbeg + 1
470 IF (monbloc%MASTER .AND. monbloc%Typenode .NE. 3)
THEN
472 lpaneleff = (monbloc%NROW-ipivbeg+1)*nbpiveff
474 lpaneleff = (monbloc%NCOL-ipivbeg+1)*nbpiveff
477 lpaneleff = monbloc%NROW*nbpiveff
490 IF (ierr.EQ.1)
RETURN
492 write(6,*)
'CMUMPS_COPY_LU_TO_BUFFER: STRAT Not implemented'
502 IF (monbloc%MASTER .AND. monbloc%Typenode .NE. 3)
THEN
503 idiag = int(ipivbeg-1,8)*int(monbloc%NCOL,8) + int(ipivbeg,8)
508 DO ii = ipivbeg, ipivend
509 CALL ccopy(monbloc%NROW-ipivbeg+1,
510 & afac(ipos), monbloc%NCOL,
512 idest = idest + int(monbloc%NROW-ipivbeg+1,8)
516 DO ii = ipivbeg, ipivend
517 CALL ccopy(monbloc%NCOL-ipivbeg+1,
520 idest = idest + int(monbloc%NCOL
521 ipos = ipos + int(monbloc%NCOL,8)
527 IF (monbloc%Typenode.EQ.3)
THEN
528 deltaipos = int(monbloc%NROW,8)
532 strideipos = monbloc%NCOL
534 ipos = 1_8 + int(ipivbeg - 1,8) * deltaipos
535 DO ii = ipivbeg, ipivend
536 CALL ccopy(monbloc%NROW,
537 & afac(ipos), strideipos,
539 idest = idest+int(monbloc%NROW,8)
540 ipos = ipos + deltaipos
if(complex_arithmetic) id
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine mumps_ooc_convert_bigintto2int(int1, int2, bigint)
integer, dimension(:), allocatable, save last_iorequest
integer(8), dimension(:), allocatable, save i_shift_cur_hbuf
subroutine cmumps_ooc_buf_clean_pending(ierr)
integer(8), dimension(:), allocatable first_vaddr_in_buf
subroutine cmumps_ooc_init_db_buffer()
subroutine cmumps_ooc_tryio_chbuf_panel(typef, ierr)
integer, save i_cur_hbuf_fstpos
integer, save earliest_write_min_size
subroutine cmumps_init_ooc_buf(i1, i2, ierr)
subroutine cmumps_ooc_wrt_cur_buf2disk(typef_arg, iorequest, ierr)
subroutine cmumps_ooc_next_hbuf(typef_arg)
integer, dimension(:), allocatable i_cur_hbuf_nextpos
subroutine cmumps_end_ooc_buf()
integer(8), dimension(:), allocatable, save i_rel_pos_cur_hbuf
integer, dimension(:), allocatable, save cur_hbuf
subroutine cmumps_ooc_init_db_buffer_panel()
integer(8), dimension(:), allocatable, save i_shift_first_hbuf
subroutine cmumps_copy_lu_to_buffer(strat, typef, monbloc, afac, lafac, addvirtcour, ipivbeg, ipivend, lpaneleff, ierr)
complex, dimension(:), allocatable buf_io
subroutine cmumps_ooc_do_io_and_chbuf(typef_arg, ierr)
subroutine cmumps_ooc_copy_data_to_buffer(block, size_of_block, ierr)
integer(8), dimension(:), allocatable, save i_shift_second_hbuf
integer, save ooc_fct_type_loc
subroutine cmumps_ooc_upd_vaddr_cur_buf(typef, vaddr)
integer(8), dimension(:), allocatable nextaddvirtbuffer
integer, save i_sub_hbuf_fstpos
integer(8), dimension(:,:), pointer ooc_vaddr
integer(8), save hbuf_size
character(len=1), dimension(err_str_ooc_max_len) err_str_ooc
integer, save low_level_strat_io
logical, save strat_io_async
integer, public strat_try_write
integer, dimension(:), pointer step_ooc
integer, public strat_write_max
integer(8), dimension(:), allocatable addvirtlibre
integer, dimension(:,:), pointer ooc_inode_sequence
integer(8), save dim_buf_io
integer, dimension(:), pointer keep_ooc