forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Returning an array

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Mon Apr 25, 2011 11:56 am    Post subject: Returning an array Reply with quote

I want to return an array to a function.

My program is like this:

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)]


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


!!!The program calculates a 3 x 3 array 'decomposed'CroutDecomp = decomposed

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*8,DIMENSION(100,100)::AA,x
REAL*8,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)

!!!I dont get the array calculated above retruned here.Pls can anyone help?



END PROGRAM LINEAR_EQUATIONS_SOLVER
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Mon Apr 25, 2011 1:56 pm    Post subject: Reply with quote

I shall be grateful if someone can help.Im stuck because of this!
Back to top
View user's profile Send private message
DrTip



Joined: 01 Aug 2006
Posts: 74
Location: Manchester

PostPosted: Mon Apr 25, 2011 6:12 pm    Post subject: Reply with quote

OK

thing is do you really want to have a function return an array. I mean really really really.

you can do it using but you have to have an interface defined. I use these so rarely that i can never remember the syntax. So I will leave you to look it up

someting like
Code:

functon foo (a)
interface
  real(:) foo
  real a
end interface

   foo = ....
end function



I am not going to look it up because I think thats enough of a steer for you


The reason that I hardly ever use them is that is a non standard fortran coding pattern.

usually a subroutine is used and the call code handles the array sizing etc

Code:

subroutine subs (a , b)
real a
real(:) b

b(1) = a
b(2) = a
b(3) = a

end subroutine

program main

real(3) test

call subs (4,test)

end program



[/code]
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Mon Apr 25, 2011 6:38 pm    Post subject: Reply with quote

Thanks, I was looking at the bottom-most thread in this post:

http://www.tek-tips.com/viewthread.cfm?qid=1516435

Not able to get what he does? Any help will be appreciated? There is no mennton of interface used in this.
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Tue Apr 26, 2011 5:39 am    Post subject: Reply with quote

I did try defining an interface but get a run time error:

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)]

interface

REAL*8 CroutDecomp(100,100)

end interface






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


LOOP_COLUMN:DO j=1,total_columns

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

INotEqual1:IF(i.NE.1)THEN

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
decomposed(i,j)=beta(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

CroutDecomp=decomposed(1:total_rows,1:total_columns)




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*8,DIMENSION(100,100)::AA,x
REAL*8,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)

ROW11_LOOP:DO i=1,total_rows
COLUMN11_LOOP:DO j=1,total_columns
PRINT*,'now', x(i,j)
END DO COLUMN11_LOOP
END DO ROW11_LOOP

END PROGRAM LINEAR_EQUATIONS_SOLVER
Back to top
View user's profile Send private message
christyleomin



Joined: 08 Apr 2011
Posts: 155

PostPosted: Tue Apr 26, 2011 6:37 am    Post subject: Reply with quote

Dear Dr.Tip,

Please can you guide?YEs, I need to return an array rather than using sub routine.

I want to group all functions in a module (like a C++ class) and if I use sub routine I will have to remove it from MODULE.

The return of the array will help me to great extent.
Back to top
View user's profile Send private message
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Tue Apr 26, 2011 12:20 pm    Post subject: Reply with quote

Just insert the name of the array into the function parameter list, having dimensioned it in the main program and it will be returned updated. the return value of the function can be the status:
Example:
Code:

dimension a(100,100),b(100)
isize = 100
j=1
do while(j .lt. 200)
  i=myfunction(a,isize,j,b)

  if(i.eq. 0)then
    Print *,'success for j=',j
    Print *,(b(k),k=1,isize)
  else
    Print *,'requested column outside range of input array j=',j
  endif
  j=j+50
enddo
end
integer function myfunction(aa,iisize,jj,bb)
dimension a(iisize,iisize), b(iisize)
if( jj .lt. 1 .or. jj .gt. iisize)then
! failure
  myfunction = 1
else
! success
  myfunction = 0
  do i=1,iisize
    bb(i) = aa(jj,i)
  enddo
endif
end

Note the indenting to make it readable. When you post code, press the "Code" keyword before and after the insertion of the code and indenting will be retained.
Oh, and please don't mention C++ again, it scares me something rotten!
Regards
Ian
Back to top
View user's profile Send private message Send e-mail
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group