gm2
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

Re: Dynamic mutidimensional arrays


From: Gaius Mulley
Subject: Re: Dynamic mutidimensional arrays
Date: Wed, 05 Apr 2023 15:13:05 +0100
User-agent: Gnus/5.13 (Gnus v5.13) Emacs/27.1 (gnu/linux)

Michael Riedl <udo-michael.riedl@t-online.de> writes:

> Gaius,
>
> in a lot of cases within linear algebra routines one has a need to have 
> intermediate multidimensional arrays (mostly 2-dimensional, but I
> also had more dimensions) which would only be needed within the scope of the 
> procedure.
>
> A simple sample might be that we need to multiply two matrices and, in the 
> end, one is only interrested in some special aspects of this
> result (e.g. the lowest eigenvalues).
>
> How would you handle such a case ?
>
> As said, in Oberon it would work as suggested, but also in modern Fortran 
> that is not implement too different (sample code below),
> gfortran can compile the code without issues.
>
> But I just wanted to see if that would be of principal interrest - if it 
> would reqite too much work, I can live with static allocation for
> the moment. 
>
> Mainly it would be a chance to make code more readable and to avoide wasting 
> too much memory in the case you define the maximun size of a
> problem the code can handle with static declarations.
>
> Michael
>
> PROGRAM DynArray
>       USE ISO_FORTRAN_ENV, only : dp => REAL64, stdin => input_unit
> !     Next line requires a fortran module "LinAlg.f90" which implement 
> MultMatVec ...
>       USE LinAlg, only : MultMatVec
>       IMPLICIT NONE
>       INTEGER :: M,N
>       REAL(dp),allocatable :: A(:,:)
>       REAL(dp),allocatable :: B(:),C(:)
> !     ... some more stuff ...
>
>       READ(stdin,*) M
>       READ(stdin,*) N
>
>       ALLOCATE(A(M,N))
>       ALLOCATE(B(N))
>       ALLOCATE(C(M))
>
> !     some code to initialize A,B ...
>
>       CALL MultMatVec(M,N,A,B,C)
>
> !     Some code to output the result C ...
>
>       DEALLOCATE(A)
>       DEALLOCATE(B)
>       DEALLOCATE(C)
> END PROGRAM DynArray
> ~                     
>

Hi,

an interesting discussion, I hear the wise warnings about painting
myself into a corner etc (especially when ISO generics, OO and M2R10 are
implemented).

Here is an exploratory idea, would the following code suit/have merit?
This time the open array dynamic variables are only allowed in local
procedure variables.


MODULE DynArray ;


PROCEDURE Transform (in: ARRAY OF ARRAY OF REAL; VAR out: ARRAY OF ARRAY OF 
REAL) ;
VAR
   (* tempMat and tempVec are created at runtime via alloca and are
      internally implemented in the same way as procedure
      parameters.  *)
   (* The array elements 0..HIGH (in), 0..HIGH (in[0]) are all accessible.  *)  
    
   tempMat: ARRAY <HIGH (in)> OF ARRAY <HIGH (in[0])> OF REAL ;
   (* The array elements 0..HIGH (in) are all accessible.  *)
   tempVec: ARRAY <HIGH (in)> OF REAL ;
   i, j   : CARDINAL ;
BEGIN
   FOR i := 0 TO HIGH (in) DO  (* some code to initialize tempMat ... *)
       FOR j:= 0 TO HIGH (in[0]) DO
          IF in[i, j] < 0.0
          THEN
             tempMat[i, j] := 0.0
          ELSE
             tempMat[i, j] := 1.0
          END
       END
   END ;
   FOR i:=0 TO HIGH (in) DO  (* some code to initialize tempVec ... *)
      tempVecp[i] := FLOAT (i)
   END ;
   (* Some code to create the result in out using in, tempMat and tempVec.  *)
END Transform ;


PROCEDURE Init (M, N: CARDINAL) ;
VAR
   (* Create local variables which are handled in the same way as a non var
      parameter open array.  The array elements 0..N are all accessible.
      The M N below must be assignment type compatible with CARDINAL.
      The open array variables in and out could be treated in the same
      way as non var open array parameters.  *)
   in, out: ARRAY <M> OF ARRAY <N> OF REAL ;
BEGIN
   (* read data into in[i, j] ... *)
   Transform (in, out) ;
   Display (out)
END Init ;


VAR
   M, N: CARDINAL ;
BEGIN
   M := ReadCard () ;
   N := ReadCard () ;
   Init (M, N)
END DynArray.


regards,
Gaius



reply via email to

[Prev in Thread] Current Thread [Next in Thread]