31 #define MAXMEM 16000000 !In kilobytes 50 subroutine dgetdiaginv(sizeA, nonzerosA, a, ia, ja, invA, error)
58 TYPE(mkl_pardiso_handle),
pointer :: PT(:) => null()
59 integer*4,
pointer :: idum(:) => null(), pia(:) => null(), pja(:) => null()
60 real(KIND=8), pointer :: ddum(:) => null(), pa(:) => null(), pb(:,:) => null(), px(:,:) => null()
61 INTEGER*4 maxfct, mnum, mtype, phase, nrhs, error, msglvl, i, nnz, numIterations, idxIterations, offset
66 INTEGER*4 sizeA, nonzerosA
67 INTEGER*4,
TARGET :: ia(sizeA+1), ja(nonzerosA)
68 real*8,
TARGET :: a(nonzerosa)
70 INTEGER*4,
ALLOCATABLE :: perm(:)
77 DATA nrhs /1/, maxfct /1/, mnum /1/
78 allocate( pt(64), idum(0), ddum(0) )
91 write(0,*)
'The input matrix: (getDiagInv)' 94 if (jdx >= ia(idx+1))
then 98 if (jdx < ia(idx+1))
then 102 write(0,*)
'The size of the diagonal vector to be calculated:', sizea
114 call pardisoinit(pt, mtype, iparm)
151 if (nrhs.GT.sizea)
then 159 write(0,*)
'number of right sides: ', nrhs
162 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
163 idum, nrhs, iparm, msglvl, ddum, ddum, error)
164 maxmem = (iparm(16)+iparm(17))
167 write(0,*)
'maxmem: ', maxmem,
' kbytes' 168 write(0,*)
'maxmem total: ', maxmem+sizea*nrhs*16/1000,
' kbytes' 171 IF ((maxmem+sizea*nrhs*16/1000).GT.maxmem)
then 172 nrhs = floor(real(maxmem-maxmem)/real(sizea*16)*1000)
173 write(0,*)
'number of right sides: ', nrhs
181 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
182 idum, nrhs, iparm, msglvl, ddum, ddum, error)
185 write(0,*)
'Reordering and factorization completed ... ' 187 IF (error .NE. 0)
THEN 188 write(0,*)
'The following ERROR was detected at the factorization step: ', error
197 allocate( perm(sizea) )
200 if (modulo(sizea, nrhs).EQ.0)
then 201 numiterations = sizea/nrhs
203 numiterations = floor(real(sizea)/real(nrhs)) + 1
207 write(0,*)
'Number of iterations to obtain the right solutions ', numiterations
212 allocate( pb(sizea, nrhs) )
213 allocate( px(sizea, nrhs) )
215 do idxiterations = 1, numiterations
217 offset = (idxiterations-1)*nrhs
219 if ((sizea-offset).LT.nrhs)
then 222 allocate( pb(sizea, nrhs) )
223 allocate( px(sizea, nrhs) )
236 pb(offset+idx, idx) = 1.d0
239 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
240 perm, nrhs, iparm, msglvl, pb, px, error)
242 IF (error .NE. 0)
THEN 248 inva(offset+idx) = px(offset+idx, idx)
253 deallocate(pb, px, perm)
256 IF (error .NE. 0)
THEN 257 write(0,*)
'The following ERROR was detected at the solution step: ', error
264 write(0,*) idx,
'th element of a = ', inva(idx)
273 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, ddum, &
275 idum, nrhs, iparm, msglvl, ddum, ddum, error)
277 deallocate(idum, ddum, pt)
279 IF (error .NE. 0)
THEN 280 write(0,*)
'The following ERROR was detected at releasing the memory: ', error
302 subroutine zgetdiaginv(sizeA, nonzerosA, a, ia, ja, real_invA, imag_invA, error)
309 TYPE(mkl_pardiso_handle),
pointer :: PT(:) => null()
310 integer*4,
pointer :: idum(:) => null(), pia(:) => null(), pja(:) => null()
311 complex(KIND=8),
pointer :: ddum(:) => null(), pa(:) => null(), pb(:,:) => null(), px(:,:) => null()
312 INTEGER*4 maxfct, mnum, mtype, phase, nrhs, error, msglvl, nnz, numIterations, idxIterations, offset
317 INTEGER*4 sizeA, nonzerosA
318 INTEGER*4,
TARGET :: ia(sizeA+1), ja(nonzerosA)
319 COMPLEX*16,
TARGET :: a(nonzerosA)
321 INTEGER*4,
ALLOCATABLE :: perm(:)
323 real*8 :: real_inva(sizea)
324 real*8 :: imag_inva(sizea)
326 INTEGER*4 idx, jdx, maxmem
330 DATA maxfct /1/, mnum /1/
331 allocate( pt(64), idum(0), ddum(0) )
345 write(0,*)
'The input matrix: (getPartialInv)' 347 do jdx = 1, nonzerosa
348 if (jdx >= ia(idx+1))
then 352 if (jdx < ia(idx+1))
then 356 write(0,*)
'The size of the diagonal vector to be calculated:', sizea
368 call pardisoinit(pt, mtype, iparm)
404 if (nrhs.GT.sizea)
then 412 write(0,*)
'number of right sides: ', nrhs
417 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
418 idum, nrhs, iparm, msglvl, ddum, ddum, error)
419 maxmem = (iparm(16)+iparm(17))
422 write(0,*)
'maxmem: ', maxmem,
' kbytes' 423 write(0,*)
'maxmem total: ', maxmem+sizea*nrhs*32/1000,
' kbytes' 426 IF ((maxmem+sizea*nrhs*32/1000).GT.maxmem)
then 427 nrhs = floor(real(maxmem-maxmem)/real(sizea*32)*1000)
428 write(0,*)
'number of right sides: ', nrhs
436 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
437 idum, nrhs, iparm, msglvl, ddum, ddum, error)
440 write(0,*)
'Reordering and factorization completed ... ' 442 IF (error .NE. 0)
THEN 443 write(0,*)
'The following ERROR was detected at the factorization step: ', error
452 allocate( perm(sizea) )
455 if (modulo(sizea, nrhs).EQ.0)
then 456 numiterations = sizea/nrhs
458 numiterations = floor(real(sizea)/real(nrhs)) + 1
462 write(0,*)
'Number of iterations to obtain the right solutions ', numiterations
466 allocate( pb(sizea, nrhs) )
467 allocate( px(sizea, nrhs) )
469 do idxiterations = 1, numiterations
471 offset = (idxiterations-1)*nrhs
473 if ((sizea-offset).LT.nrhs)
then 476 allocate( pb(sizea, nrhs) )
477 allocate( px(sizea, nrhs) )
490 pb(offset+idx, idx) = (1.d0, 0.d0)
493 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, pa, pia, pja, &
494 perm, nrhs, iparm, msglvl, pb, px, error)
496 IF (error .NE. 0)
THEN 501 real_inva(offset+idx) = real(px(offset+idx, idx))
502 imag_inva(offset+idx) = aimag(px(offset+idx, idx))
507 deallocate(pb, px, perm)
510 IF (error .NE. 0)
THEN 511 write(0,*)
'The following ERROR was detected at the solution step: ', error
518 CALL pardiso (pt, maxfct, mnum, mtype, phase, sizea, ddum, &
520 idum, nrhs, iparm, msglvl, ddum, ddum, error)
522 deallocate(idum, ddum, pt)
524 IF (error .NE. 0)
THEN 525 write(0,*)
'The following ERROR was detected at releasing the memory: ', error
Module to calculate the diagonal of the inverse of a real/complex sparse matrix via the PARDISO libra...
subroutine zgetdiaginv(sizeA, nonzerosA, a, ia, ja, real_invA, imag_invA, error)
Get the diagonal part of the inverse of double valued complex matrices.
subroutine dgetdiaginv(sizeA, nonzerosA, a, ia, ja, invA, error)
Get the diagonal part of the inverse of double valued real matrices.