Search code examples
functionpointersfortranaliassubroutine

Receiving Memory Access Error when changing a pointer inside a subroutine


I'm using Fortran and gfortran 4.7.2. I'm pretty new to Fortran and searched intensively for a solution to my problem. The program I want to use has many functions, which should be aliased based on the given conditions correctly. For that I want to use pointer.

The main program creates pointer based on the interface in the module func_interface. Based on which function I want to alias, I wrote a subroutine which should change the pointer to desired function. Nevertheless I receive a 'Memory Access Error' when trying to run the program - obviously because I didn't understand the pointers in Fortran or how to pass them to a subroutine in order to change them inside the subroutine correctly.

Has somebody an idea how to change the program in order to use it this way? The program is as below.

MODULE func_interface
    ABSTRACT INTERFACE
        FUNCTION func(z)
            DOUBLE PRECISION func
            DOUBLE PRECISION, INTENT (IN) :: z
        END FUNCTION func
    END INTERFACE
END MODULE func_interface

SUBROUTINE assign_pointer(i, func_ptr)
    USE         func_interface
    IMPLICIT    NONE

    PROCEDURE (func), POINTER, INTENT(INOUT) ::     func_ptr => NULL ()

    INTEGER, INTENT (IN) :: i

    DOUBLE PRECISION        f1, f2
    EXTERNAL                f1, f2

    SELECT CASE ( i )
        CASE ( 1 )
            func_ptr => f1
            RETURN
        CASE ( 2 )
            func_ptr => f2
            RETURN
    END SELECT
END SUBROUTINE assign_pointer

DOUBLE PRECISION FUNCTION f1(x)
    IMPLICIT            NONE
    DOUBLE PRECISION, INTENT(IN) :: x

    f1 = 2*x
END FUNCTION f1

DOUBLE PRECISION FUNCTION f2(x)
    IMPLICIT            NONE
    DOUBLE PRECISION, INTENT(IN) :: x

    f2 = 4*x
END FUNCTION f2

PROGRAM pointer_test
    USE         func_interface
    IMPLICIT    NONE

    DOUBLE PRECISION    f1, f2
    EXTERNAL            f1, f2

    PROCEDURE (func), POINTER :: func_ptr => NULL ()

    CALL                    assign_pointer( 1, func_ptr )
    WRITE(*, '(1PE12.4)')   func_ptr(5.2D1)

END PROGRAM pointer_test

Error Message :

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7F32AFB92667
#1  0x7F32AFB92C34
#2  0x7F32AF14F19F
#3  0x4007CE in assign_pointer_
#4  0x40085B in MAIN__ at pointer_test.f90:0
Speicherzugriffsfehler

Solution

  • The comments from francescalus and Vladimir are what you need. Below I suggest a simple reorganization of your code where I put all the functions in the existing module. I also commented the external statements because they become useless with functions in a module. You will find the following comment on many fortran question on S.O. but it is worth putting it here again. When starting new project, you should stick to modern programming techniques. It is better to put procedures in module instead of using the external. That will automatically build the interface for you and do some checking at compile time.

    Now if you are going to use some functions that exist already and you are not modifying them, you need to supply explicit interface.


    Thank to francescalus comment, I modify the call to the selected function in the main program, to call only if it is initialized. To avoid that, the default case can be processed in the procedure assign_pointer.


    MODULE func_interface
        ABSTRACT INTERFACE
            FUNCTION func(z)
                DOUBLE PRECISION func
                DOUBLE PRECISION, INTENT (IN) :: z
            END FUNCTION func
        END INTERFACE
    CONTAINS
    
        SUBROUTINE assign_pointer(i, func_ptr)
        ! USE         func_interface
            IMPLICIT    NONE
    
            PROCEDURE (func), POINTER, INTENT(INOUT) ::     func_ptr => NULL ()
    
            INTEGER, INTENT (IN) :: i
    
            !DOUBLE PRECISION        f1, f2
            !EXTERNAL                f1, f2
    
            SELECT CASE ( i )
                CASE ( 1 )
                    func_ptr => f1
                    RETURN
                CASE ( 2 )
                    func_ptr => f2
                    RETURN
            END SELECT
        END SUBROUTINE assign_pointer
    
        DOUBLE PRECISION FUNCTION f1(x)
            IMPLICIT            NONE
            DOUBLE PRECISION, INTENT(IN) :: x
    
            f1 = 2*x
        END FUNCTION f1
    
        DOUBLE PRECISION FUNCTION f2(x)
            IMPLICIT            NONE
            DOUBLE PRECISION, INTENT(IN) :: x
    
            f2 = 4*x
        END FUNCTION f2
    END MODULE func_interface
    
    
    PROGRAM pointer_test
        USE         func_interface
        IMPLICIT    NONE
    
        !DOUBLE PRECISION    f1, f2
        !EXTERNAL            f1, f2
    
        PROCEDURE (func), POINTER :: func_ptr => NULL ()
    
        CALL                    assign_pointer( 1, func_ptr )
        IF(associated(func_ptr))then
            WRITE(*, '(1PE12.4)')   func_ptr(5.2D1)
        ELSE
            ! manage the cas
        END IF
    END PROGRAM pointer_test