Search code examples
fortransubroutine

How to declare an array with size modification in a subroutine?


I did a subroutine MatPath to append an array but I don't understand how I should declare this array in the subroutine where I call MatPath :

!********************************************************************** 
SUBROUTINE MatPath(Path, Start) 
INTEGER(2),PARAMETER::Ximax = 5, Yimax = 5, Zimax = 1
INTEGER(4)::W,B
REAL(8), DIMENSION(:,:), ALLOCATABLE::Path
REAL(8), DIMENSION(:,:), ALLOCATABLE::Temp_Array
REAL(8), DIMENSION(:), ALLOCATABLE::Start
W=SIZE(Path,DIM=2)
ALLOCATE(Temp_Array(3,W))
DEALLOCATE(Path)
ALLOCATE(Path(3,W+1))
Path(:,1:W)=Temp_Array(:,1:W)
Path(:,W+1)=Start(:)
DEALLOCATE(Temp_Array)

RETURN
END SUBROUTINE MatPath
!************************************************
SUBROUTINE FINDPATH(Array, St)
IMPLICIT NONE
INTEGER(4), DIMENSION(3,3)::Array
REAL(8), DIMENSION(3)::St
REAL(8), DIMENSION(3, :)::Path !PROBLEM HERE

CALL MatPath(Path, St)

END SUBROUTINE FINDPATH

It's still unclear how I can declare an array which the size would be modify in a subroutine ... If someone can explain how it work, Thanks !

EDIT

To be more clear here a simplification of my problem how can I get modification of the size of my array A and pass it between the main program end the subroutine ? :

program teste10

REAL(8),DIMENSION(:,:),ALLOCATABLE::A

ALLOCATE(A(2,2))
A=1
WRITE(*,*), "Initial A : ", A

CALL TESTE1(A)

WRITE(*,*) "new A : ", A 

DEALLOCATE(A)
STOP
end program teste10
!**********************************************
SUBROUTINE TESTE1(A)

REAL(8),DIMENSION(:,:),INTENT(INOUT), ALLOCATABLE::A
REAL(8), DIMENSION(:,:), ALLOCATABLE::Temp
INTEGER(4)::X, Y

X=SIZE(A, DIM=1)
Y=SIZE(A, DIM=2)
ALLOCATE(Temp(X,Y))
DEALLOCATE(A)
ALLOCATE(A(X+2,Y+3))
A(1:X, 1:Y)=Temp(1:X,1:Y)
A(X+1:X+2, Y+1:Y+3)=0
DEALLOCATE(Temp)

RETURN
END SUBROUTINE TESTE1

When I try to do that it give me a "SIGSEV, segmentation fault occured" or just run forever without any message....


Solution

  • First, there was certainly some error message from the compiler. Please show your error messages in our questions.

    In the called subroutine, you declare the dummy arguments allocatable. That is correct.

    In the calling subroutine, you didn't declared the arrays allocatable. That is not correct. If you pass any variable into an allocatable dummy argument, the variable must itself be allocatable.

    So both Path and St have to be allocatable inside FINDPATH.

    You probably can remove the allocatable attribute from Start and then St will not have to be allocatable either.

    So (not tested):

    !********************************************************************** 
    SUBROUTINE MatPath(Path, Start) 
      INTEGER  ::  W
      REAL(something_better), DIMENSION(:,:), ALLOCATABLE :: Path
      REAL(something_better), DIMENSION(:,:), ALLOCATABLE :: Temp_Array
      REAL(something_better), DIMENSION(:),               :: Start
    
      W=SIZE(Path,DIM=2)
      ALLOCATE(Temp_Array(3,W))
      DEALLOCATE(Path)
      ALLOCATE(Path(3,W+1))
      Path(:,1:W)=Temp_Array(:,1:W)
      Path(:,W+1)=Start(:)
      DEALLOCATE(Temp_Array)
    END SUBROUTINE MatPath
    !************************************************
    
    
    SUBROUTINE FINDPATH(Array, St)
      INTEGER, DIMENSION(3,3) :: Array
      REAL(something_better), DIMENSION(3) :: St
      REAL(something_better), DIMENSION(3, :), allocatable :: Path 
    
      CALL MatPath(Path, St)
    
      !here do something with Path and Array?
      !it is not clear what does Path and what does Array
    END SUBROUTINE FINDPATH
    

    Moreover, the presence of IMPLICIT NONE in the calling subroutine is leading me to suspicion that your subroutines are not in a module. They have to be in a module or the explicit interface must be established by some other means because allocatable arguments require explicit interface.


    The second version (also not tested):

    module Subroutines
      implicit none
      integer, parameter :: dp = kind(1.d0)
    
    contains
    
        SUBROUTINE TESTE1(A)
          REAL(dp), DIMENSION(:,:), INTENT(INOUT), ALLOCATABLE :: A
          REAL(dp), DIMENSION(:,:), ALLOCATABLE :: Temp
          INTEGER :: X, Y
    
          X=SIZE(A, DIM=1)
          Y=SIZE(A, DIM=2)
          ALLOCATE(Temp(X,Y))
          DEALLOCATE(A)
          ALLOCATE(A(X+2,Y+3))
          A(1:X, 1:Y) = Temp(1:X,1:Y)
          A(X+1:X+2, Y+1:Y+3) = 0
          DEALLOCATE(Temp)
        END SUBROUTINE TESTE1
    
    end module
    
    
    program teste10
      use Subroutines
    
      implicit none
    
      REAL(dp), DIMENSION(:,:), ALLOCATABLE :: A
    
      ALLOCATE(A(2,2))
      A=1
      WRITE(*,*), "Initial A : ", A
    
      CALL TESTE1(A)
    
      WRITE(*,*) "new A : ", A 
    
      DEALLOCATE(A)
    end program teste10
    

    Here insert my usual rant about ugliness and non-portability of integer(4) and real(8).

    I can't imagine why you might want

    INTEGER(2),PARAMETER::Ximax = 5, Yimax = 5, Zimax = 1
    

    instead of just

    INTEGER, PARAMETER :: Ximax = 5, Yimax = 5, Zimax = 1
    

    There is simply no reason why the former might be better unless you pass it as an argument somewhere where kind 2 is required.