Silverfrost Forums

Welcome to our forums

Array problem

24 Apr 2011 7:49 #8115

I have a code like this:

MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS

CONTAINS

FUNCTION CroutDecomp(AA,total_rows,total_columns,no_of_equations)



END MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS

PROGRAM LINEAR_EQUATIONS_SOLVER

USE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS

!IMPLICIT NONE

REAL,DIMENSION(100,100)::AA,x REAL,DIMENSION(100)::b

INTEGER::total_rows,total_columns,no_of_equations,i,j

PRINT*, 'ENTER THE TOTAL NUMBER OF ROWS AND COLUMNS'

READ*, total_rows,total_columns

PRINT*, 'ENTER THE TOTAL NUMBER OF EQUATIONS'

READ*, no_of_equations

PRINT*, 'ENTER THE A MATRIX OF Ax = b'

ROW_LOOP:DO i=1,total_rows

COLUMN_LOOP:DO j=1,total_columns

READ,AA(i)(j)*

END DO COLUMN_LOOP

END DO ROW_LOOP

PRINT*, 'ENTER THE b MATRIX OF Ax = b'

ROW_LOOP:DO i=1,total_rows

READ*,b(i)

END DO ROW_LOOP

x=CroutDecomp(AA,total_rows,total_columns,no_of_equations)

END PROGRAM LINEAR_EQUATIONS_SOLVER

Now,

On compiling, I get the following errors:

  1. error 199- array AA appears in this expression as rank 1, but was declared as rank 2 (see the line in bold).

2)error 612 ':' found when not expected. Same bold line.

Can anyone tell me where I'm going wrong?

I'm new to Fortran.Sorry for a funda doubt.

Please help!

24 Apr 2011 10:31 #8117

It is the format of the array subscripts. I modified the program as follows, by adding some dummy bits into the function to get it to compile without error as it did nothing in your example.

MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 
CONTAINS 
FUNCTION CroutDecomp(AA,total_rows,total_columns,no_of_equations) 
INTEGER::total_rows,total_columns ,no_of_equations
real aa(total_rows,total_columns)
print *,'in CroutDecomp', aa(1,1),no_of_equations
CroutDecomp = 1d0
end function
!----- 
!----- 
END MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 
PROGRAM LINEAR_EQUATIONS_SOLVER 
USE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 
!IMPLICIT NONE 
REAL,DIMENSION(100,100)::AA,x 
REAL,DIMENSION(100)::b 
INTEGER::total_rows,total_columns,no_of_equations,i,j 
PRINT*, 'ENTER THE TOTAL NUMBER OF ROWS AND COLUMNS' 
READ*, total_rows,total_columns 
PRINT*, 'ENTER THE TOTAL NUMBER OF EQUATIONS' 
READ*, no_of_equations 
PRINT*, 'ENTER THE A MATRIX OF Ax = b' 
ROW_LOOP:DO i=1,total_rows 
COLUMN_LOOP:DO j=1,total_columns 
READ*,AA(i,j) 
END DO COLUMN_LOOP 
END DO ROW_LOOP 
PRINT*, 'ENTER THE b MATRIX OF Ax = b' 
ROW_LOOP:DO i=1,total_rows 
READ*,b(i) 
END DO ROW_LOOP 
x=CroutDecomp(AA,total_rows,total_columns,no_of_equations) 
END PROGRAM LINEAR_EQUATIONS_SOLVER 

And as you are new to Fortran, you should consider reading about the precision of REAL variables and use REAL8 instead of REAL which only uses 4 bytes for storage by default and gives 7 decimal digits precision - REAL8 gives about 17. Sorry I'm talking in an old dialect of Fortran, but I'm almost as old as Fortran itself. Regards Ian

24 Apr 2011 10:40 #8118

You appear to have only started !!

I would expect that 'no_of_equations' is the key variable for you, while total_rows and total_columns only refers to the dimension of the arrays.

If you supply the arguments to 'CroutDecomp (AA,total_rows,total_columns,no_of_equations) ', then I don't think you need it as a contains function.

You appear to be returning the result of the function as an array x. My apologies, while I think you can do that, I do not know how. I would convert it to a subroutine and have X as an argument.

My approach to the module would be to define the key arrays and variables you are using. I have modified the code to remove the compile errors. My code for crout decomposition is from memory (it's been a long time. Google to find correct code.) Hopefully it is close to what you need. the layout is close. Hopefully this is a help. If not, then at least I've demonstrated syntax that removes some compile errors.

MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 

REAL*8,DIMENSION(100,100):: AA, x 
REAL*8,DIMENSION(100):: b 

INTEGER::total_rows,total_columns,no_of_equations
 
!CONTAINS 

! FUNCTION CroutDecomp(AA,total_rows,total_columns,no_of_equations) 

!----- 
!----- 
END MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 


PROGRAM LINEAR_EQUATIONS_SOLVER 

USE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS 

!IMPLICIT NONE 

INTEGER :: i,j 

!PRINT*, 'ENTER THE TOTAL NUMBER OF ROWS AND COLUMNS' 

!READ*, 
total_rows    = size (AA, 1)
total_columns = size (AA, 2)

PRINT*, 'ENTER THE TOTAL NUMBER OF EQUATIONS (2 to 100)' 

READ*, no_of_equations 

PRINT*, 'ENTER THE A MATRIX OF Ax = b' 

ROW_LOOP:DO i=1,no_of_equations 

COLUMN_LOOP:DO j=1,no_of_equations 

    READ*,AA(i,j) 

  END DO COLUMN_LOOP 

END DO ROW_LOOP 

PRINT*, 'ENTER THE b MATRIX OF Ax = b' 

ROW_LOOP:DO i=1,no_of_equations 

 READ*,b(i) 

END DO ROW_LOOP 

call CroutDecomp (x, AA,total_rows,total_columns,no_of_equations) 


END PROGRAM LINEAR_EQUATIONS_SOLVER 

subroutine CroutDecomp (x, AA,total_rows,total_columns,no_of_equations) 
!
!  template of Crout Decomp : this needs checking for completion 
!
integer*4 total_rows,total_columns,no_of_equations
real*8, dimension(total_rows,total_columns) :: x, AA
!
integer i,j
real*8 c
!
x = aa
!
do i = 1, no_of_equations
  do j = 1,i
     x(i,j) = x(i,j) - dot_product (x(j,1:j-1), x(i,1:j-1))
  end do
  c = x(i,i)
  x(i,i) = 1
  do j = i, no_of_equations
     x(i,j) = x(i,j) / c
  end do
end do
!
end subroutine CroutDecomp   
24 Apr 2011 3:24 #8119

Thanks a lot for the reply.I'm now facing a runtime error and do not know the reason.Also, I found where is the run time error in the code below but am at no clues, why it is occuring.

Actually when j=2 and i=1, the beta(i,j) is not getting calculated- that is, the print statement for beta(i,j) is not executed when j=2 and i=1. Thouhg the program is done till j=2 and also prints i=1 but does not calculate beta(2,1) as it is not printed.

Anyone knows why?

Please help if possible!!

MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS CONTAINS

FUNCTION CroutDecomp(AA,total_rows,total_columns,no_of_equations) !This routine decomposes the 'A' matrix of Ax=b into an upper and lower triangular matrix

!It is to be noted that this function fills in only the combined matrix of 'alpha's' and 'beta's' ; where alpha is the upper triangular matrix and beta is the lower triangular matrix.

!Crout's decomposition carries out 2 steps: !1) First, for i=1,2,---,j use , beta(i,j)= a(i,j)-(summation over k=1 to i-1)[alpha(i,k)beta(k,j) !2)Second, for i=j+1,--N use, alpha(i,k)= 1/beta(j,j)((a(i,j)-summation over k=1 to j-1 [ alpha(i,k)*beta(k,j)]

INTEGERtotal_rows,total_columns ,no_of_equations REAL aa(total_rows,total_columns) INTEGER i,j,k REAL ::sum1 REAL alpha(total_rows,total_columns),beta(total_rows,total_columns),decomposed(total_rows,total_columns)

LOOP_COLUMN:DO j=1,total_columns

print*,'inside j' ,j LOOP_ROWS:DO i= 1,j print*,'inside i', i alpha(i,i)=1 sum1=0

INotEqual1:IF(i.NE.1)THEN print*,'inside prod alpha beta',i,j LOOP_PROD_ALPHA_BETA:DO k=1,i-1 sum1=sum1+(alpha(i,k)*beta(k,j)) END DO LOOP_PROD_ALPHA_BETA END IF INotEqual1

beta(i,j)=AA(i,j)-sum1 print,'printing betaqqqqqqqqqqq',beta(i,j)*

decomposed(i,j)=beta(i,j) print*,'printing decomposed',decomposed(i,j) END DO LOOP_ROWS

jLessThanNoOfEqns:IF(j.LT.no_of_equations)THEN LOOP_ROWS_1: DO i=j+1,no_of_equations sum1=0

jNotEqual1:IF(j.NE.1)THEN LOOP_PROD_ALPHA_BETA2:DO k=1,j-1 sum1=sum1+(alpha(i,k)*beta(k,j)) END DO LOOP_PROD_ALPHA_BETA2 END IF jNotEqual1

alpha(i,j)=(1/beta(j,j))*(AA(i,j)-sum1) decomposed(i,j)=alpha(i,j) END DO LOOP_ROWS_1

END IF jLessThanNoOfEqns

END DO LOOP_COLUMN print *,'in CroutDecomp'

!ROW11_LOOP:DO i=1,total_rows !COLUMN11_LOOP:DO j=1,total_columns !PRINT*,decomposed(i,j) !END DO COLUMN11_LOOP !END DO ROW11_LOOP

CroutDecomp = 20

END FUNCTION CroutDecomp

END MODULE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS

PROGRAM LINEAR_EQUATIONS_SOLVER USE DIRECT_METHODS_FOR_SOLUTION_OF_LINEAR_ALGEBRAIC_EQUATIONS !IMPLICIT NONE REAL,DIMENSION(100,100)::AA,x REAL,DIMENSION(100)b INTEGERtotal_rows,total_columns,no_of_equations,i,j PRINT*, 'ENTER THE TOTAL NUMBER OF ROWS AND COLUMNS' READ*, total_rows,total_columns PRINT*, 'ENTER THE TOTAL NUMBER OF EQUATIONS' READ*, no_of_equations PRINT*, 'ENTER THE A MATRIX OF Ax = b' ROW_LOOP:DO i=1,total_rows COLUMN_LOOP:DO j=1,total_columns READ*,AA(i,j) END DO COLUMN_LOOP END DO ROW_LOOP PRINT*, 'ENTER THE b MATRIX OF Ax = b' ROW_LOOP:DO i=1,total_rows READ*,b(i) END DO ROW_LOOP

x= CroutDecomp(AA,total_rows,total_columns,no_of_equations)

END PROGRAM LINEAR_EQUATIONS_SOLVER

24 Apr 2011 5:26 #8120

Also, I'm just giving the following inputs:

total_rows=3 total_columns=3 no_of_equations=3

And the array AA is:

1 3 8 1 4 3 1 3 4

The above are respectively: AA(1,1),AA(1,2),AA(1,3),AA(2,1),AA(2,2),AA(2,3),AA(3,1),AA(3,2),AA(3,3)

and the b matrix is: b(1)=4 b(2)=-2 b(3)=1

25 Apr 2011 10:51 #8121

The problem is silved if i declare AA, x as below:

FUNCTION CroutDecomp(AA,total_rows,total_columns,no_of_equations) !This routine decomposes the 'A' matrix of Ax=b into an upper and lower triangular matrix

!It is to be noted that this function fills in only the combined matrix of 'alpha's' and 'beta's' ; where alpha is the upper triangular matrix and beta is the lower triangular matrix.

!Crout's decomposition carries out 2 steps: !1) First, for i=1,2,---,j use , beta(i,j)= a(i,j)-(summation over k=1 to i-1)[alpha(i,k)beta(k,j) !2)Second, for i=j+1,--N use, alpha(i,k)= 1/beta(j,j)((a(i,j)-summation over k=1 to j-1 [ alpha(i,k)*beta(k,j)]

INTEGER::total_rows,total_columns ,no_of_equations

INTEGER:: i,j,k REAL ::sum1 REAL*8 alpha(total_rows,total_columns),beta(total_rows,total_columns),decomposed(total_rows,total_columns)

**REAL*8,DIMENSION(100,100)::AA,x **

Thanks a lot everyone!

Please login to reply.