[comp.lang.fortran] Dimensioning arrays at run-time, best way?

phd11@.uk.ac.keele (Zipzoid) (09/12/90)

Hi,

I think this question may have been asked many times before,
but what is the best way of dimensioning an array whose maximum
memory requirement (size) would be read in at run-time?

At the moment I am stating the maximum size that the program is ever likely
to encounter in a PARAMETER statement and using this in COMMON blocks 
duplicated throughout my source file.

As you can imagine, the memory wasted when the data file calls for a small
problem to be solved is considerable, and I am loathe to recompile the
program for varying problem sizes.

Any pointers would be gratefully received.
--
Tony McDonald (Tones)		
                                JANET:    phd11@uk.ac.kl.seq1
               ~ *              ARPANET:  phd11@seq1.kl.ac.uk
               \_/              BITNET:   phd11%uk.ac.kl.seq1@ukacrl

mroussel@alchemy.chem.utoronto.ca (Marc Roussel) (09/17/90)

In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) writes:
>I think this question may have been asked many times before,
>but what is the best way of dimensioning an array whose maximum
>memory requirement (size) would be read in at run-time?

Let your PROGRAM block be a dummy.  (I.E. don't put any code into it
that does anything but set N (the array size) and calls a subroutine
which does the real work.)  Then call your subroutine.  Most FORTRAN
compilers don't check for the right number of parameters in a subroutine
call, so the following may not be portable, but it should do the work on
most computers.

Now for the example:

      PROGRAM EXAMPLE
      read(*,*)n
      call sub1(n)
      END

      SUBROUTINE SUB1(N,X)
      real X(N)
C     Do the work in this subroutine.
C     Of course you can't use common blocks so you'll have to pass X
C      around as an argument.
      END

			        Good luck!

				Marc R. Roussel
                                mroussel@alchemy.chem.utoronto.ca

fox@DASHER.NSCL.MSU.EDU (09/18/90)

In article <1990Sep17.150155.10220@alchemy.chem.utoronto.ca>, mroussel@alchemy.chem.utoronto.ca (Marc Roussel) writes...

>In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) writes:
>>I think this question may have been asked many times before,
>>but what is the best way of dimensioning an array whose maximum
>>memory requirement (size) would be read in at run-time?
> 
>Let your PROGRAM block be a dummy.  (I.E. don't put any code into it
>that does anything but set N (the array size) and calls a subroutine
>which does the real work.)  Then call your subroutine.  Most FORTRAN
>compilers don't check for the right number of parameters in a subroutine
>call, so the following may not be portable, but it should do the work on
>most computers.
> 
>Now for the example:
> 
>      PROGRAM EXAMPLE
>      read(*,*)n
>      call sub1(n)
>      END
> 
>      SUBROUTINE SUB1(N,X)
>      real X(N)
>C     Do the work in this subroutine.
>C     Of course you can't use common blocks so you'll have to pass X
>C      around as an argument.
>      END

NO NO NO A thousand times NO!!!!!

  In most machines this will cause a very quick failure.  No storage has
actually been allocated for X.  This is because it is passed in as a dummy
parameter.  FORTRAN expects the storage to have been allocated by the caller
which is not the case.  What the caller has allocated instead is an argument 
list with a single entry.  The second entry is just garbage and referencing
it will at *best* get you garbage, and, on most memory protected machines
just cause your program to bus error or access violate depending on the O/S.
  In subroutine/functions, the dimension of a dummy parameter does *NOT*
allocate storage.  It simply is a device to tell the compilation unit how to
treat the parameter.  Storage for the parameter is expected to have been
allocated (statically or dynamically depending on the compiler) earlier in the
call tree.

		Ron

Ron Fox                     | FOX@MSUNSCL.BITNET      | Where the name 
NSCL                        | FOX@CYCVAX.NSCL.MSU.EDU | goes on before
Michigan State University   | MSUHEP::CYCVAX::FOX     | the quality
East Lansing, MI 48824-1321 |                         | goes in.
USA

khb@chiba.Eng.Sun.COM (Keith Bierman - SPD Advanced Languages) (09/19/90)

In article <1990Sep18.115704.20642@msuinfo.cl.msu.edu> fox@DASHER.NSCL.MSU.EDU writes:

   In article <1990Sep17.150155.10220@alchemy.chem.utoronto.ca>, mroussel@alchemy.chem.utoronto.ca (Marc Roussel) writes...

   > 
   >Let your PROGRAM block be a dummy.  (I.E. don't put any code into it
   >that does anything but set N (the array size) and calls a subroutine
   >which does the real work.)  Then call your subroutine.  Most FORTRAN
   >compilers don't check for the right number of parameters in a subroutine
   >call, so the following may not be portable, but it should do the work on
   >most computers.

I have often done well the "other way around" instead of

   > 
   >      PROGRAM EXAMPLE
   >      read(*,*)n
   >      call sub1(n)
   >      END
   > 
   >      SUBROUTINE SUB1(N,X)
   >      real X(N)
.....
   >      END


	program example

	print*,"how many bytes ?"
	read(*,*) nbytes
	x=malloc(nbytes)
	call realprog(x,nbytes/4)
	end
	subroutine realprog(x,n)
c
c	this is where the "real program" begins
c	
	real x(n)

c	do processing, including all calls
c
	return	
	end

The "spelling" of how to procure the memory varies, malloc works on
Sun and most unix boxes; I forget which sys$ call does the trick on
VMS, and etc. but it is usually easy to find. Only a few lines in the
formal main program need to adjusted from system to system.

--
----------------------------------------------------------------
Keith H. Bierman    kbierman@Eng.Sun.COM | khb@chiba.Eng.Sun.COM
SMI 2550 Garcia 12-33			 | (415 336 2648)   
    Mountain View, CA 94043

3003jalp@ucsbuxa.ucsb.edu (Applied Magnetics) (09/19/90)

(Mail bounced)
In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) writes:

>... what is the best way of dimensioning an array whose maximum
>memory requirement (size) would be read in at run-time?

You can't do it without violating the Fortran standard in some way.
The best alternative is to have a very simple main program read the
size, allocate the array in some machine-dependent way and pass the
array and its size to a normal Fortran subroutine that does the real
work.

If you port the code, your fallback position is to lobotomize the main
program:  declare a large static array, read the size, check that
the array is big enough, then call the subroutine.  Not so good, but
perhaps better than nothing: you can compile the subroutine and its
dependents once and for all.  To change the size, you recompile only
the main and re-link it with the rest.

My earlier post, `Fun with pointers', was prompted by my own attempts
to do better.  Using a stratagem to mimick pointer variables, I wrote a
Fortran copy of malloc() and free() from the appendix in Kernighan and
Ritchie, with an assembler assist to replace the sbrk system call.  My
code is NOT portable.  The consensus is that it would break on a
semgented memory architecture.

--P. Asselin, AMC

moler@matrix.mathworks.com (Cleve Moler) (09/19/90)

Hold it!  Keith Bierman is really lucky if his program which
uses malloc in Fortran works correctly.  His program:

> 	program example
> 
> 	print*,"how many bytes ?"
> 	read(*,*) nbytes
> 	x=malloc(nbytes)
> 	call realprog(x,nbytes/4)
> 	end
> 	subroutine realprog(x,n)
> c
> c	this is where the "real program" begins
> c	
> 	real x(n)
> 
> c	do processing, including all calls
> c
> 	return	
> 	end

There are two things wrong with this.  First, malloc returns
an integer result, but "x" is, by default, of type real, so
the assignment  x = malloc(...)  involves a conversion from
integer to floating point.  Second, and more important, the
call to the subroutine passes the address of the scalar variable
x, not the value of x which is the address of the allocated
memory.  So the subroutine uses n real locations beginning at the
location of x, not at the location of the space obtained from
malloc.

It turns out that very simple instances of "realprog" might
still appear to work because they don't clobber anything.

The key to making this sort of thing work correctly is the
VMS Fortran addressing extension %val().  This is a true extension
to the language which must be handled by the compiler.  It is
not something you can just add to a run-time library.  Fortunately,
many manufacturers, including Bierman's employer, have adopted
DEC's extension.  (The idea was around before VMS Fortran, but
everybody calls it a VMS extension today.)

Here is a program that DOES work on my Sun SPARCstation 1.
I've added a second array so something will get clobbered
if the code isn't correct.

        program example
 	integer x,y
        write(*,*) "enter n"
        read(*,*) n
        x = malloc(4*n)
        y = malloc(4*n)
        call realprog(%val(x),%val(y),n)
        end

        subroutine realprog(x,y,n)
        real x(n),y(n)
        do i = 1, n
            x(i) = i/10.
            y(i) = 10.*i
        enddo
        call wot(x,y,n)
        return 
        end

        subroutine wot(x,y,n)
        real x(n),y(n)
        write(*,*) n,x(1),x(n),y(1),y(n)
        return  
        end

Note that x and y are declared to be integer in the main
program.  More importantly, note the use of %val() in the
subroutine call.  We have to pass the values of x and y,
as obtained from malloc, down the line, rather than their
locations, as would be the case in a conventional Fortran call.
If you get rid of either the integer declaration, or the %loc()'s,
the program will fail.

(Trivia quiz: anybody know why my sub-subroutine is "wot"?)

   -- Cleve Moler
      moler@mathworks.com

fox@DASHER.NSCL.MSU.EDU (09/19/90)

In article <KHB.90Sep18101100@chiba.Eng.Sun.COM>, khb@chiba.Eng.Sun.COM (Keith Bierman - SPD Advanced Languages) writes...

> 
>In article <1990Sep18.115704.20642@msuinfo.cl.msu.edu> fox@DASHER.NSCL.MSU.EDU writes:
> 
>   In article <1990Sep17.150155.10220@alchemy.chem.utoronto.ca>, mroussel@alchemy.chem.utoronto.ca (Marc Roussel) writes...
> 
>   > 
>   >Let your PROGRAM block be a dummy.  (I.E. don't put any code into it
>   >that does anything but set N (the array size) and calls a subroutine
>   >which does the real work.)  Then call your subroutine.  Most FORTRAN
>   >compilers don't check for the right number of parameters in a subroutine
>   >call, so the following may not be portable, but it should do the work on
>   >most computers.
> 
>I have often done well the "other way around" instead of
> 
>   > 
>   >      PROGRAM EXAMPLE
>   >      read(*,*)n
>   >      call sub1(n)
>   >      END
>   > 
>   >      SUBROUTINE SUB1(N,X)
>   >      real X(N)
>......
>   >      END
> 
> 
>	program example
> 
>	print*,"how many bytes ?"
>	read(*,*) nbytes
>	x=malloc(nbytes)
>	call realprog(x,nbytes/4)
>	end
>	subroutine realprog(x,n)
>c
>c	this is where the "real program" begins
>c	
>	real x(n)
> 
>c	do processing, including all calls
>c
>	return	
>	end
> 
>The "spelling" of how to procure the memory varies, malloc works on
>Sun and most unix boxes; I forget which sys$ call does the trick on
>VMS, and etc. but it is usually easy to find. Only a few lines in the
>formal main program need to adjusted from system to system.
> 

  On the VMS boxes the call is LIB$GET_VM.  But, and here's a big but.
Most machines this should not work, for the following reasons:

1. In the call to malloc, almost all C library malloc's expect a pass
   by value for the sizeof the storage region to allocate. Many, but not all
   FORTRAN's pass constants, and scalars by reference.  So rather than malloc
   allocating the the number of bytes you want, it'll allocate the number
   of bytes corresponding to the address of the variable nbytes.  May be
   very very big, or very very small.

2. The call of realprog, assumes that passing a scaler which contains a pointer
   to a subroutine is equivalent to passing an array.  This is not usually
   true.

  Although the standard does not mandate how subroutines and functions
pass arguments between each other, most (not all) compiler pass scalars
and arrays by reference, and pass characters in some funny way to allow
the size allocated for the character string to be passed along with the
pointer to the storage.  Forgetting the character string case, in VAX/VMS
for example, The call to realprog produces the following argument list

(AP) ---> +-------------+
          |           2 |  (Number of arguments)
          +-------------+
          |ptr to x     |----> x ----> malloc'd storage
	  +-------------+
	  |Ptr to nbytes/4|---> Nbytes/4 temporary variable
	  +-------------+

  This is not atypical. This is because FORTRAN mandates that changes to 
dummy parameters made by a function/subroutine be reflected by changes to 
the actual parameters, and pointer passing seems the most efficient way
to get that job done.

  What you really want to happen in the call to malloc (using again the VMS
argument list format) is to get an argument list that looks like:

(AP)----------->+----------------+
		|               1|
		+----------------+
		|      nbytes    |
		+----------------+

 And in the call to realprog:

(AP)----------->+-------------------+
		|                2  |
		+-------------------+
		|                 x |
		+-------------------+
		|Ptr to nbytes/4    |------------> Nbytes/4 temporary
		+-------------------+

In VAX/VMS FORTRAN and in HP-UX FORTRAN, there's an extension which 
allows the programmer to specify a nonstandard call sequence inline.
To do the malloc in VAX/VMS or HP-UX you'd have to:

	x = malloc(%VAL(nbytes))

And the call to realprog should look like:

	CALL realprog(%VAL(x), nbytes/4)

  Passing x by value is the same as passing the region by reference (pointer).

 In SUN fortran there is also a %VAL exension which must be used when
passing scalar parameters to C library functions.  In addition, since
SUN FORTRAN sticks an underscore in front of function/subroutine names,
it is necessary tell the compiler that a function is C using the C pragma,
so at the top you'd need to say:

	EXTERNAL malloc !$pragman C(malloc)


  Dynamic allocation of storage is something only for the brave and 
for those well versed in parameter passing mechanisms on the implementation.
It's not something that FORTRAN readily supports.

	Ron

Ron Fox                     | FOX@MSUNSCL.BITNET      | Where the name 
NSCL                        | FOX@CYCVAX.NSCL.MSU.EDU | goes on before
Michigan State University   | MSUHEP::CYCVAX::FOX     | the quality
East Lansing, MI 48824-1321 |                         | goes in.
USA

khb@chiba.Eng.Sun.COM (Keith Bierman - SPD Advanced Languages) (09/20/90)

Cleve and others have pointed out that my code was missing a %val.
This was intentional; I should have been more explicit and stated
clearly that I was providing pseudocode, not a working bit of code.
The Sun documentation contains some examples, and one might even want
to use the Cray-oriented POINTER notation.... 

As originally stated, the exact "spelling" of the "memory allocation"
routine and how one calls it is system (machine+os) specific; and is
of course non-standard.

However, only a few lines of code in the main program are affected and
the rest of ones program may be completely standard conforming.

Dynamic memory allocation is not only for the fearless, nor does it
seriously contort ones code (unless you write very short
applications). 


--
----------------------------------------------------------------
Keith H. Bierman    kbierman@Eng.Sun.COM | khb@chiba.Eng.Sun.COM
SMI 2550 Garcia 12-33			 | (415 336 2648)   
    Mountain View, CA 94043

mroussel@alchemy.chem.utoronto.ca (Marc Roussel) (09/21/90)

In article <1990Sep18.115704.20642@msuinfo.cl.msu.edu> fox@DASHER.NSCL.MSU.EDU
writes:
>In article <1990Sep17.150155.10220@alchemy.chem.utoronto.ca>,
mroussel@alchemy.chem.utoronto.ca (Marc Roussel) writes...
>
>>In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) writes:
>>>I think this question may have been asked many times before,
>>>but what is the best way of dimensioning an array whose maximum
>>>memory requirement (size) would be read in at run-time?
>> 
>>Let your PROGRAM block be a dummy.  (I.E. don't put any code into it
>>that does anything but set N (the array size) and calls a subroutine
>>which does the real work.)  Then call your subroutine.  Most FORTRAN
>>compilers don't check for the right number of parameters in a subroutine
>>call, so the following may not be portable, but it should do the work on
>>most computers.
>> 
>>Now for the example:
>> 
>>      PROGRAM EXAMPLE
>>      read(*,*)n
>>      call sub1(n)
>>      END
>> 
>>      SUBROUTINE SUB1(N,X)
>>      real X(N)
>>C     Do the work in this subroutine.
>>C     Of course you can't use common blocks so you'll have to pass X
>>C      around as an argument.
>>      END
>
>NO NO NO A thousand times NO!!!!!
>[Lots of good reasons why this is dangerous deleted.]

In my own defence, I've used this sort of trick before without ill
effects.  It's not standard-conforming, portable or even safe to assume
that your machine will stay up after you've executed a program based on
the above model.  But on some machines with some compilers it may
work.  Maybe I should have included a disclaimer with the code. :-)

In a more serious vein, if you are working on a personal machine with a
straightforward architecture, you can compile the above code and then
hack at the generated machine language.

Another alternative would be to put an explicitly declare the size in the
main program but then to compile the main program and subroutines
separately.  You would then only have to recompile the main program (and
relink) when you wanted to change the size(s) of your array(s).  If you
do all the real work in subroutines, recompiling the main program
shouldn't generally take very long, and this should work just about
anywhere (unlike my... uhh... unique previous solution).

				Marc R. Roussel
                                mroussel@alchemy.chem.utoronto.ca

ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe) (09/21/90)

In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) asked:
> I think this question may have been asked many times before,
> but what is the best way of dimensioning an array whose maximum
> memory requirement (size) would be read in at run-time?

In article <1990Sep17.150155.10220@alchemy.chem.utoronto.ca>,
mroussel@alchemy.chem.utoronto.ca (Marc Roussel) suggested:

>       PROGRAM EXAMPLE
>       read(*,*)n
>       call sub1(n)
>       END

>       SUBROUTINE SUB1(N,X)
>       real X(N)
> C     Do the work in this subroutine.
> C     Of course you can't use common blocks so you'll have to pass X
> C      around as an argument.
>       END

> 			        Good luck!

My word we'll _need_ it!  What, precisely, is X supposed to be?  Yes,
I know that this was deliberate.  What when you arrive in SUB1, what
do you expect X to be?  On one machine here, when I use f77 X seems
to be the address 0 (which happens to "work"), while when I use f2c
followed by gcc I get a completely different address.

-- 
Heuer's Law:  Any feature is a bug unless it can be turned off.

ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe) (09/21/90)

In article <191@matrix.mathworks.com>, moler@matrix.mathworks.com (Cleve Moler) writes:
> The key to making this sort of thing work correctly is the
> VMS Fortran addressing extension %val().

The first time I saw passing-something-by-value-to-a-Fortran-subroutine
was in a program written for IBM/360 (Fortran H?).  The syntax was
	CALL SUBR(/ARG/)
Using the spelling %val(.) may be a VMS extension (it looks a lot like
Bliss) but which vendor implemented the _idea_ first?

-- 
Heuer's Law:  Any feature is a bug unless it can be turned off.

jerry@violet.berkeley.edu (Jerry Berkman) (09/23/90)

In article <614@keele.keele.ac.uk> phd11@.uk.ac.keele (Zipzoid) writes:
>what is the best way of dimensioning an array whose maximum
>memory requirement (size) would be read in at run-time?
>
On a Cray, you can use automatic arrays:

      PROGRAM EXAMPLE
      read *, n
      call sub1(n)
      END

      SUBROUTINE SUB1(N)
      real X(N)

C     Do the work in this subroutine.
C     Of course you can't use common blocks so you'll have to pass X
C      around as an argument.
      END

Since X's bounds are a dummy argument, the Cray CFT77 compiler
generates code to allocate memory for the array when the subroutine is
entered, and deallocate it when the subroutine is exited.
This is a Fortran 90 feature which is not common, but is probably
supported on some other systems.

As others have noted, VMS type Fortran systems have an extension that
allows passing values, so a similar trick can be used by calling
malloc() or something equivalent and passing the value returned as
an array.

On 4.3 BSD VAX UNIX, there is a routine called falloc(), which stands
for Fortran alloc().  This allocates the space but you must use ofsets
to a common block to refer to it, less convenient than the above methods.

For those new to this, dynamic allocation has been used with Fortran
since before I can remember.  Almost every big package such as SPSS
uses dynamic allocation.  I'm glad it will be in Fortran 90.

	- Jerry Berkman, U.C.Berkeley, (415)642-4804
	  jerry@violet.berkeley.edu

disclaimer: opinions are my own, not my employers, etc.