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 strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Question on passing arrays/ array indexes to subroutines 1

Status
Not open for further replies.

Sleort

Technical User
Mar 28, 2011
4
NO
Hi,

I'm using (and at the same time trying to master) Fortran 95...

Okay, suppose that I have an array,
Code:
INTEGER, DIMENSION(-5:5) :: arr

and I want to pass this to a subroutine WHILE keeping the "non-default" indexing (because the indexing contains important information). The ususal assumed-shape array passing doesn't seem to work the way I want;
Code:
SUBROUTINE ASSUMED(a)
  INTEGER, DIMENSION(:) :: a
  WRITE(*,*) lbound(a), ubound(a)
END SUBROUTINE

CALL ASSUMED(arr)
writes
Code:
1   11
... So the subroutine seems to forget about it's initial lower and upper indexes and automatically uses the default lower index 1. Okay, I could use an explicit-shape approach like this:
Code:
SUBROUTINE EXPLICIT(a, l, u)
  INTEGER :: l, u
  INTEGER, DIMENSION(l:u) :: a
  WRITE(*,*) lbound(a), ubound(a)
END SUBROUTINE

CALL EXPLICIT(arr, -5, 5)
which gives the desired result
Code:
-5   5
but at the cost of having to explicitly pass more parameters (which can be quite cumbersome when one have to pass several arrays to a subroutine).

I have discovered that if the ASSUMED subroutine is modified to arrays declared ALLOCATABLE I do get the desired result:
Code:
INTEGER, DIMENSION(:), ALLOCATABLE :: arr2
ALLOCATE(arr2(-5:5)

SUBROUTINE ASSUMED2(a)
  INTEGER, DIMENSION(:), ALLOCATABLE :: a
  WRITE(*,*) lbound(a), ubound(a)
END SUBROUTINE

CALL ASSUMED2(arr2)
gives
Code:
-5   5
My questions are then:
* Are there some "assumed-array way" of passing the indexes to the subroutine without using allocatable arrays?
* Why does it work with allocatable arrays and not ordinary ones?
* Is there some (performance or otherwise) penalty when using allocatable arrays instead of ordinary ones?

I would be grateful if anyone could help me out here;-)
 
Sorry but I don't understand the result of your test with the subroutine "assumed2" : the normal result is "1 11" and not "-5 5". The ALLOCATABLE attribute has no effect on that result because upper and lower bounds are never passed ! Only the array dimension is passed when the dimension :)) is used in the argument definition.

Notice also that you may pass only the lower bound :
Code:
SUBROUTINE EXPLICIT(a,l)
  INTEGER :: l
  INTEGER, DIMENSION(-l:) :: a
  WRITE(*,*) lbound(a), ubound(a)
END SUBROUTINE

CALL explicit(a,size(a)/2)

My own test case :
Code:
program test
  implicit none
  real :: a(-5:5)
  real,allocatable :: b(:)
  allocate(b(-5:5))
  call s1(a)
  call s1(b)
  call s2(b)
  call s3(a,size(a)/2)
  contains
  subroutine s1(a)
    real :: a(:)
    write(*,*) lbound(a),ubound(a)
  end subroutine
  subroutine s2(b)
    real,allocatable :: b(:)
    write(*,*) lbound(b),ubound(b)
  end subroutine
  subroutine s3(a,l)
    real :: a(-l:)
    integer :: l
    write(*,*) lbound(a),ubound(a)
  end subroutine
end program

And the results obtained with INTEL and GCC compilers :

Code:
           1          11
           1          11
          -5           5
          -5           5



François Jacq
 
Oups ! I correct myself : you are right !

So the ALLOCATABLE attribute influences the behavior of dummy arguments. I have to read again carefully the F2003 reference manual about that attribute.

I was so sure that I posted too quickly...

Finally you deserve a star because I learnt something about FORTRAN today !

François Jacq
 
Glad to be "of help":p

... And please let me know if you find out anything. That might (maybe) answer some of my questions...
 
After examining a little bit more deeply your example, the upper and lower bounds are passed when the dummy array argument has either the POINTER or ALLOCATABLE attribute.

Like you I was a little bit disappointed when I observed, a long time ago (middle of nineties), that theses bounds were not passed for "normal" array argument. I never tried with the allocatable attribute because this one was not authorized in FORTRAN-90. Even the FORTRAN-95 does not accept it for dummy arguments. This generalization of the use of allocatable was the subject of a specific technical recommendation in 1997. But I think now that the POINTER attribute would have given the expected result.

Compared to ALLOCATABLE, POINTER is here a little bit more flexible because it is always possible to point to an existing array (allocatable, pointer, automatic or static) without allocating additional memory :

Code:
program test
  implicit none
  real,target :: a(-5:5)
  real,pointer :: c(:)
  c => a
  call  s3(c)
  contains
  subroutine s3(c)
    real,pointer :: c(:)
    write(*,*) lbound(c),ubound(c)
  end subroutine
end program



François Jacq
 
So, to summarize: One can "cheat" and use either ALLOCATABLE or POINTER arrays to pass indexing information to the subroutine, but at the "cost" of having to explicitly specify (both in subroutine and main program) that the array is ALLOCATABLE/POINTER? (Making the subroutine less flexible)

But then, why not declare all arrays either ALLOCATABLE or POINTER? (Or am I missing some important fact about these attributes?)

And one (or two) last question(s): You write
Compared to ALLOCATABLE, POINTER is here a little bit more flexible because it is always possible to point to an existing array (allocatable, pointer, automatic or static) (...)
But then you have to state this explicitly (with TARGET and POINTER), making the code less flexible..?
(...) without allocating additional memory :
Hmm... I thought that the arguments of a subroutine were dummy arguments, i.e. no (additional) memory is allocated for them..?

Thanks a lot for helping me out!
 
But then you have to state this explicitly (with TARGET and POINTER), making the code less flexible..?

Hmm... I thought that the arguments of a subroutine were dummy arguments, i.e. no (additional) memory is allocated for them..?

If the array you want to pass to the subroutine is defined somewhere else and is not a pointer, then it is always possible to define a pointer pointing to it and to pass that pointer to the subroutine (in using the "pointer" version of that subroutine of course).

On the contrary, with the "allocatable" version of the subroutine, if the array you want to pass is not allocatable, then you need to create a copy of that array (which is an allocatable of course) and to pass that copy to the subroutine. This is why I wrote that the pointer solution is less memory consuming.

Anyway, I prefer to avoid the attributes allocatable and pointer to dummy arguments except if they are needed because one really wants to allocate of to point to in the subroutine.

For passing dimensions which are often constant during a run, I often use a specific module containing these constant values (either parameters of variables defined only once) :

Code:
module constant
  integer :: n
end module

program test
  use constant
  implicit none
  real :: a(-5:5)
  n=size(a)/2 ! n defined only once
  call  s(a)
  contains
  subroutine s(a)
    real :: a(-n:n)
    write(*,*) lbound(a),ubound(a)
  end subroutine
end program

François Jacq
 
Okay, I think I'm about to get a grip of the situation.

Smart module solution, by the way, but not really useful in my situation (unless it's possible to make kind of an "object module"... hmm... I could maybe make a new datatype containing both the array and the index information, although I'm not sure it's worth it...)

A little nit-picking(?) :
If the array you want to pass to the subroutine is defined somewhere else and is not a pointer, [highlight]then it is always possible to define a pointer pointing to it[/highlight] and to pass that pointer to the subroutine
Well, not unless you have declared the array you want to point to TARGET in advance... and then you have to know in advance that you are going to point to the array, right? (And then it's not that flexible anymore...)
 
Well, not unless you have declared the array you want to point to TARGET in advance... and then you have to know in advance that you are going to point to the array, right? (And then it's not that flexible anymore...)

Right. But declaring TARGET an array has no particular consequence in term of memory or CPU (it could perhaps prevent too aggressive compiler optimizations).

In your case, it is also possible to defined derived type variables containing allocatable members :

Code:
module m
  implicit none
  type my_type
    real,allocatable :: a(:)
    real,allocatable :: b(:)
  end type
  contains
  subroutine s(c)
    type(my_type) :: c
    write(*,*) lbound(c%a),ubound(c%a)
    write(*,*) lbound(c%b),ubound(c%b)
  end subroutine
end module

program test
  use m
  implicit none
  type(my_type) :: v
  allocate(v%a(-5:5),v%b(4:10))
  call s(v)
end program

Result :

Code:
          -5           5
           4          10

This is still simpler because, as demonstrated, you may group together several arrays.





François Jacq
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top