- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I am running a program which is basically an example code of pasdiso in mkl. The program successfully solved the example equations in my computer. When I added a line to make a file connection without any other modifications in the program:
open(5,file='c:\cyhouwork\3d_elastic\ia.txt',status='unknown')
The program worked good. Then a second file connection, without other modifications
open(6,file='c:\cyhouwork\3d_elastic\ja.txt',status='unknown')
Everything went fine. But when I add a third file connection without any other modifications
open(8,file='c:\cyhouwork\3d_elastic\sparse.txt',status='unknown')
The 'access violation' (157) message showed up.
Anyone knows how to solve the problem? Thanks!! The code is shown below:
PROGRAM pardiso_sym_f90
USE mkl_pardiso
IMPLICIT NONE
INTEGER, PARAMETER :: dp = KIND(1.0D0)
!.. Internal solver memory pointer
TYPE(MKL_PARDISO_HANDLE), ALLOCATABLE :: pt(:)
!.. All other variables
INTEGER maxfct, mnum, mtype, phase, n, nrhs, error, msglvl, nnz
INTEGER error1,j
INTEGER, ALLOCATABLE :: iparm( : )
INTEGER, ALLOCATABLE :: ia( : )
INTEGER, ALLOCATABLE :: ja( : )
REAL(KIND=DP), ALLOCATABLE :: a( : )
REAL(KIND=DP), ALLOCATABLE :: b( : )
REAL(KIND=DP), ALLOCATABLE :: x( : )
INTEGER i, idum(1)
REAL(KIND=DP) ddum(1)
!.. Fill all arrays containing matrix data.
open(5,file='c:\cyhouwork\3d_elastic\ia.txt',status='unknown') <----
open(6,file='c:\cyhouwork\3d_elastic\ja.txt',status='unknown') <---- These are the lines causing the problem
open(8,file='c:\cyhouwork\3d_elastic\sparse.txt',status='unknown') <----
n = 9
nnz = 20
nrhs = 1
maxfct = 1
mnum = 1
msglvl=1
ALLOCATE(ia(n + 1))
ia = (/ 1, 5, 8, 10, 12, 15, 17, 18, 20, 21 /)
ALLOCATE(ja(nnz))
ja = (/ 1, 3, 6, 7, &
2, 3, 5, &
3, 8, &
4, 7, &
5, 6, 7, &
6, 8, &
7, &
8, 9, &
9 /)
ALLOCATE(a(nnz))
a = (/ 7.d0, 1.d0, 2.d0, 7.d0, &
-4.d0, 8.d0, 2.d0, &
1.d0, 5.d0, &
7.d0, 9.d0, &
5.d0, 1.d0, 5.d0, &
-1.d0, 5.d0, &
11.d0, &
5.d0, 3.d0&
-2.d0/)
ALLOCATE(b(n))
ALLOCATE(x(n))
!..
!.. Set up PARDISO control parameter
!..
ALLOCATE(iparm(64))
DO i = 1, 64
iparm(i) = 0
END DO
iparm(1) = 1 ! no solver default
iparm(2) = 2 ! fill-in reordering from METIS
iparm(4) = 0 ! no iterative-direct algorithm
iparm(5) = 0 ! no user fill-in reducing permutation
iparm(6) = 0 ! =0 solution on the first n components of x
iparm(8) = 2 ! numbers of iterative refinement steps
iparm(10) = 13 ! perturb the pivot elements with 1E-13
iparm(11) = 1 ! use nonsymmetric permutation and scaling MPS
iparm(13) = 0 ! maximum weighted matching algorithm is switched-off (default for symmetric). Try iparm(13) = 1 in case of inappropriate accuracy
iparm(14) = 0 ! Output: number of perturbed pivots
iparm(18) = -1 ! Output: number of nonzeros in the factor LU
iparm(19) = -1 ! Output: Mflops for LU factorization
iparm(20) = 0 ! Output: Numbers of CG Iterations
error = 0 ! initialize error flag
msglvl = 0 ! print statistical information
mtype = -2 ! symmetric, indefinite
!.. Initialize the internal solver memory pointer. This is only
! necessary for the FIRST call of the PARDISO solver.
ALLOCATE (pt(64))
DO i = 1, 64
! pt(i)%DUMMY = 0
END DO
!.. Reordering and Symbolic Factorization, This step also allocates
! all memory that is necessary for the factorization
!phase = 11 ! only reordering and symbolic factorization
!CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja, &
! idum, nrhs, iparm, msglvl, ddum, ddum, error)
!WRITE(*,*) 'Reordering completed ... '
!IF (error /= 0) THEN
! WRITE(*,*) 'The following ERROR was detected: ', error
! GOTO 1000
! END IF
!WRITE(*,*) 'Number of nonzeros in factors = ',iparm(18)
!WRITE(*,*) 'Number of factorization MFLOPS = ',iparm(19)
!.. Factorization.
!phase = 22 ! only factorization
!CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja, &
! idum, nrhs, iparm, msglvl, ddum, ddum, error)
!WRITE(*,*) 'Factorization completed ... '
!IF (error /= 0) THEN
! WRITE(*,*) 'The following ERROR was detected: ', error
! GOTO 1000
!ENDIF
!.. Back substitution and iterative refinement
iparm(8) = 2 ! max numbers of iterative refinement steps
phase = 13 ! only solving
!do j=1,10
DO i = 1, n
b(i) = 1.d0
END DO
print *,'*****'
CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja, &
idum, nrhs, iparm, msglvl, b, x, error)
print *,'*****'
!WRITE(*,*) 'Solve completed ... '
IF (error /= 0) THEN
WRITE(*,*) 'The following ERROR was detected: ', error
GOTO 1000
ENDIF
!WRITE(*,*) 'The solution of the system is '
DO i = 1, n
WRITE(*,*) ' x(',i,') = ', x(i)
END DO
!end do
1000 CONTINUE
!.. Termination and release of memory
phase = -1 ! release internal memory
CALL pardiso (pt, maxfct, mnum, mtype, phase, n, ddum, idum, idum, &
idum, nrhs, iparm, msglvl, ddum, ddum, error1)
IF (ALLOCATED(ia)) DEALLOCATE(ia)
IF (ALLOCATED(ja)) DEALLOCATE(ja)
IF (ALLOCATED(a)) DEALLOCATE(a)
IF (ALLOCATED(b)) DEALLOCATE(b)
IF (ALLOCATED(x)) DEALLOCATE(x)
IF (ALLOCATED(iparm)) DEALLOCATE(iparm)
IF (error1 /= 0) THEN
WRITE(*,*) 'The following ERROR on release stage was detected: ', error1
STOP 1
ENDIF
IF (error /= 0) STOP 1
END PROGRAM pardiso_sym_f90
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You are connecting units 5 and 6 to disk files, which may interfere with I/O to the standard input and output units. Even unit 8 can sometimes be used for print devices. Your program text does not show what you do with the files that you opened, but try using unit numbers larger than 9, instead.
You are opening files with "status='unknown'". If it is your intention to read from those files, use "status='old'" instead. If the current directory is not the one within which you expect to read the files, zero-length files will be created when you use "status='unknown'", and subsequent READ statements will fail.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I tried to replace the unit numbers 5, 6, and 8 with 101, 102, and 103, and the 'status=unknown' with 'status=old', but it did not work. I intend to open these files to read my equation coefficients. Those lines for reading the files are not yet in the code. Therefore, the coefficients used in the code are those provided by the example problem. I am pretty sure the files are successfully opened and the access violation problem occurs when the code calls pardiso. Because I respectively insert a line "print *,'*****'" right before and after the line "call pardiso(......)". The first star line are successfully printed, then the access violation message without the 2nd star line.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You have commented out the line that sets pt(i)%DUMMY = 0 . Either activate that line or make a call to pardisoinit(...) to perform the proper initializations.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, it was the pt(i)%DUMMY = 0 problem. Thank you very much!

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page