Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Chriss Miller on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Array-Valued Function

Status
Not open for further replies.

toasterrowster

Programmer
Jan 14, 2003
5
CA
Hi,

I have written a function that returns a two dimensional array. For some reason my compiler keeps telling me that my routine has been "called with different number and/or type of actual arguments in earlier call..."
I have double checked and I have made sure that the number and types are the same in my call to the function.

Do I have to give a dimension to the array that im assigning the function to? I tried this and the compiler doesnt seem to like it.

The only way I could get it to work would be to add a extra arguement in my call to the function that had the same name as the function? does this make sense? It gets the program to compile, but when I run it, I get an array out of bounds error. I have even copied examples of array valued functions from text books into my program and my compiler still complains about the number or type of arguements. Is it a compiler setting?

Any help would be great....Thanks alot.

Rowan
 

Post a small sample program which illustrates the problem. CaKiwi
 
Ok here is where i call it...

Code:
specarray = specinarray(component, state, spherical, h2so4, hno3, temp, interpolate)

here is a portion of the function...

Code:
!**********************************************
! specinarray
!**********************************************
FUNCTION specinarray(component, state, spherical, h2so4, hno3, temp, interpolate)
REAL*8, DIMENSION(24,5000) :: specinarray
INTEGER, PARAMETER :: MAX_INTERP_SIZE=4
INTEGER :: compnum, temp, radius_id, ir, i, j, k
INTEGER :: h2so4wts(MAX_INTERP_SIZE)
INTEGER :: hno3wts(MAX_INTERP_SIZE)
INTEGER :: interpCount
INTEGER :: errorcode
INTEGER :: spectrumAddresses(MAX_INTERP_SIZE,MAX_INTERP_SIZE)
INTEGER :: freqs
INTEGER :: spectraPointer
REAL*8 :: h2so4, hno3 
REAL*8 :: radius
REAL*8 :: ya(MAX_INTERP_SIZE,MAX_INTERP_SIZE)
REAL*8 :: interpolatedResult, ddy  
REAL*8 :: Spectraa(10,5000)
REAL*8, EXTERNAL :: dereferenceSpectraValue
REAL*4 :: freqStart, freqInc, freqEnd
REAL*8, ALLOCATABLE :: spectrum(:)
CHARACTER*5 :: state, spherical 
CHARACTER*8 :: component
LOGICAL :: interpolate
.
.
.
.

specinarray(1,1) = 8

.
.
.
end function


the parts left out are not important as they do not affect the array.

Thanks in advance

Rowan
 
I have never tried to write a function which returned an array and to the best of my knowledge it is not allowed. I suggest that you create another argument and use that to pass back the data to the calling routine.

SUBROUTINE specinarray(component,specout)
REAL*8, DIMENSION(4,4) :: specout
character*8 component

specout(1,1) = 8

end subroutine

program spec

REAL*8, DIMENSION(4,4) :: sp
character*8 comp

call specinarray(comp,sp)
print *,sp(1,1)

end program spec CaKiwi
 
CaKiwi,

I have written it as a subroutine as well and it works fine. My boss would like it in a the form of a function though because he wants to just be able to assign the returned array to an array, as you can see in my example.

From what I have read in "Fortran 90 Programming" by Ellis, Phillips, Lahey, there is no problem returning an array with a function. I followed their formatting and the formatting I have seen on the web, but it doesnt seem to work.

If you know something that I dont, that it is definatly impossible, then tell me because then I can tell my boss, and keep it as a subroutine.

thank you,

Rowan
 

I have never seen it documented one way our the other. Does your book give an example that you can try? CaKiwi
 
Yes it does, and even when I try those I get the same argument type/amount error. It almost seems like there is something wrong with my compiler settings or something


Rowan
 
Here is an example off a web site,

Code:
Functions can return arrays, for example, 


   PROGRAM Maian 
    IMPLICIT NONE
     INTEGER, PARAMETER      :: m = 6
     INTEGER, DIMENSION(M,M) :: im1, im2
      ...
     IM2 = funnie(IM1,1) ! invoke
   CONTAINS
    FUNCTION funnie(ima,scal)
     INTEGER, INTENT(IN) :: ima(:,:)
     INTEGER, INTENT(IN) :: scal
     INTEGER, DIMENSION(SIZE(ima,1),SIZE(ima,2)) &
                         :: funnie
     funnie(:,:) = ima(:,:)*scal
    END FUNCTION funnie
   END PROGRAM
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top