I have problem trying to define a subroutine, whose argument contains an allocatable, optional, intent(inout) variable shown below. The code compiles fine, but get runtime error of "Segmentation fault - invalid memory reference".
Subroutine test_routine.f90
SUBROUTINE test_routine(A,B)
IMPLICIT NONE
REAL,ALLOCATABLE,INTENT(IN) :: A(:,:)
REAL,ALLOCATABLE,OPTIONAL,INTENT(INOUT) :: B(:,:)
B = A
B(:,:) = 1
END SUBROUTINE
This subroutine is packed in a module, and is called in Main.
Module test_module.f90
MODULE test_module
IMPLICIT NONE
INTERFACE test_routine
MODULE PROCEDURE test_routine
END INTERFACE
END MODULE test_module
Main test_main.f90
PROGRAM main
USE test_module
IMPLICIT NONE
REAL,ALLOCATABLE :: A(:,:),B(:,:)
ALLOCATE(A(6,6))
ALLOCATE(B(6,6))
A(:,:) = 0
CALL test_routine(A,B) ! WORKS FINE
CALL test_routine(A) ! DOESN'T WORK!
END PROGRAM main
Then I tried to assign another variable op_B, to make up for B, which doesn't actually exist if the main routine doesn't pass it in. However the following code still doesn't work.
SUBROUTINE test_routine(A,B)
IMPLICIT NONE
REAL,ALLOCATABLE,INTENT(IN) :: A(:,:)
REAL,ALLOCATABLE,OPTIONAL,INTENT(INOUT) :: B(:,:)
REAL,ALLOCATABLE :: op_B(:,:)
IF(.NOT. PRESENT(B)) THEN
ALLOCATE(op_B(SIZE(A,1),SIZE(A,2)))
B = op_B
END IF
B = A
B(:,:) = 1
END SUBROUTINE
By the way, I also tried using fixed size array, but still doesn't help. I wonder if it's impossible to do such things?