So I need to write a program to implement the Jacobi Iteration Scheme but I am having some issues with it causing segmentation faults. I am not sure where the issue is occuring. Any help would be great.
Code:
PROGRAM 961
IMPLICIT NONE
! Declare Variables
INTEGER:: i, j, k, n, aux, max_iter, iter
REAL, ALLOCATABLE :: a(:,:),x(:),xold(:), ea(:)
REAL(KIND=8) :: tol, suma
CHARACTER(LEN=20) :: output
! Request File Information
WRITE(*,*)"Jacobi Iterative Method"
WRITE(*,*)
PRINT *, "Please specify output filename: "
READ (*,*) output
PRINT *, "Please specify number of variables: "
READ(*,*) n
PRINT *, "Please specify maimum number of iterations: "
READ(*,*) max_iter
PRINT *, "Please specify tolerance: "
READ(*,*) tol
OPEN(unit=20,file=output,status='replace')
ALLOCATE (a(n+1,n),x(n),ea(n),xold(n))
! Bulk Coding
DO i=1,n,1
WRITE(*,*)'xo(i):'
READ(*,*)xold(i)
END DO
x(1:n)=0
ea(:)=1
iter=0
DO i=1,n,1
DO j=1,n+1,1
WRITE(*,*) "a(",i,",",j,"):"
READ(*,*) a(i,j)
END DO
END DO
DO WHILE (iter <= max_iter)
aux=0
DO i=1,n,1
suma=0
DO k=1,n,1
IF (i /= k) THEN
suma=suma+xold(k)*a(k,i)
END IF
END DO
x(i)=(a(n+1,i)-suma)/a(i,i)
IF (xold(i) /= 0)THEN
ea(i)=abs(((x(i)-xold(i))/x(i)))
ELSE
IF (x(i) == 0)THEN
ea(i)=0
END IF
END IF
WRITE(*,*) ea(i)
END DO
DO i=1,n,1
WRITE(20,*) j,i,x(i),ea(i)
IF (ea(i) < tol) THEN
aux=aux+1
END IF
END DO
IF (aux == n) THEN
WRITE(*,*) "Number of Iterations: ", iter
WRITE(*,*)
WRITE(*,*) " i xi ea"
WRITE(*,*) "----------------------------"
DO i=1,n,1
WRITE(*,*)i,x(i),ea(i)
END DO
END IF
iter=iter+1
xold(1:n)=x(1:n)
ENDDO
CLOSE(20)
WRITE(*,*) "Solution"
WRITE(*,*)
WRITE(*,*) "Number of Iterations: ", j
WRITE(*,*)
WRITE(*,*) " i xi ea"
WRITE(*,*) "----------------------------"
DO i=1,n,1
WRITE(*,*)i,x(i),ea(i)
END DO
END PROGRAM 961