1

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
francescalus
  • 30,576
  • 16
  • 61
  • 96
fwillo
  • 77
  • 1
  • 8
  • 1
    Your subroutine `assign_pointer` isn't a module procedure. You need some mechanism to provide an explicit interface in the program. See [documentation](https://stackoverflow.com/documentation/fortran/2203/program-units-and-file-layout#t=201609201235192290047), etc. – francescalus Sep 20 '16 at 12:34
  • Yes, without an explicit interface the program assumes it is a normal procedure argument and passes the function's address, not the pointer's address. – Vladimir F Героям слава Sep 20 '16 at 12:43

2 Answers2

1

The answer by innoSPG gives the essential aspects of the solution: extend what the module includes to make an explicit interface available in the main program for the subroutine assign_pointer. I'll give a little more detail and address a difficulty suggested in a comment.

First, look at the (simplified) subroutine definition:

subroutine assign_pointer(i, func_ptr)
    use func_interface  ! func is given in here
    procedure(func), pointer, intent(inout) :: func_ptr
    integer, intent(in) :: i
end subroutine assign_pointer

The dummy argument func_ptr of this subroutine has the pointer attribute. As given elsewhere such an attribute requires an explicit interface in a scope referencing the subroutine. That other answer shows how that can be arranged (and there are many other questions and answer around that to be found).

The subroutine and functions are external procedures and do not automatically have an explicit interface available.

You then asked

Although I thought that using USE func_interface is explicitly defining the pointer.. what is the mistake in this thought?

The module func_interface contains the abstract interface func. This abstract interface is used in the declaration of the procedure pointers. However, it's the subroutine assign_pointer, as noted above, which is problematic. One can see that the dummy argument

    procedure(), pointer, intent(inout) :: func_ptr

(which has implicit interface) is wholly independent of the module, but still there is a requirement for the subroutine's interface to be explicit in a calling scope.

So, the abstract interface is only one small part of the way to get this program to work.

And even that abstract interface may be unnecessary. Depending on how f1 and f2 are to be made available we may be able to write the module as:

module full_mod
 contains
  function f1(..)
  end function f1

  function f2(..)
  end function f2

  subroutine assign_pointer(i, func_ptr)
    procedure(f1), pointer, intent(inout) :: func_ptr
    integer, intent(in) :: i
    ! f1 and f2 available from the host module
  end subroutine assign_pointer

end module

use full_mod
implicit none

procedure(f1), pointer :: func_ptr => NULL()
...
end

That is, f1 and f2 may themselves be used to give the interface of a procedure pointer, when those functions are in scope.


And a final note: the dummy argument func_ptr may not have explicit initialization. A line such as

procedure(func), pointer, intent(inout) :: func_ptr => NULL()

is trying to do exactly that. It is trying to say that func_ptr is initially disassociated. As can be seen in my code lump above the => NULL() should be removed. Either standard pointer assignment should be used

procedure(func), pointer, intent(inout) :: func_ptr
func_ptr => NULL()

or we can note that the explicit initialization in the main program

procedure(func), pointer :: func_ptr => NULL()

is allowed and as the dummy argument has the intent(inout) attribute it retains that not-associated status on entry to the subroutine.

Graham
  • 7,431
  • 18
  • 59
  • 84
francescalus
  • 30,576
  • 16
  • 61
  • 96
  • Wow! Thank you very much francescalus! This was one detailed answer, I have to read some stuff to fully understand it, but I appreciate the effort very much! One last thing I'm wondering about, because I can't find a satisfying answer in tutorials : I noticed that the program is running even if I'd leave out the CONTAINS in MODULE. So what exactly is the purpose.. is it kind of protecting the functions so they only can be run inside the MODULE,SUBROUNTINE,PROGRAM etc. and can not be called directly outside of the scope? – fwillo Sep 20 '16 at 20:33
  • Without the `contains` statement in the module the thing shouldn't compile. It is required to be able to define subroutines and functions _contained_ in (internal to) the module. You can see this [here](http://stackoverflow.com/documentation/fortran/1139/usage-of-modules/3671/module-syntax#t=201609202046415669996). If you mean that your program still works when the procedures aren't in the module then (except for the pointer dummy mentioned previously) that is possible: much of the information shared in a module is repeated in other declarations (such as the function return types). – francescalus Sep 20 '16 at 20:51
  • I'm stupid. I didn't save my source code after I removed CONTAINS. Sorry, for that. It's not compiling as you said. Thanks again for the detailed answer regarding this minor topic! – fwillo Sep 20 '16 at 21:40
0

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
innoSPG
  • 4,588
  • 1
  • 29
  • 42
  • 1
    It is also worth noting that dummy arguments (such as `func_ptr` in `assign_pointer`) may not be explicitly initialized. – francescalus Sep 20 '16 at 13:19
  • Absolutely, the default case is not processed, so it will happen in a real life situation when the input are computed. – innoSPG Sep 20 '16 at 13:29
  • 3
    I can't really take credit for spotting the non-associated pointer: I meant that `procedure(func),pointer, intent(inout) :: func_ptr => NULL()` isn't allowed. That's attempting explicit initialization (as initially disassociated) on a dummy argument. – francescalus Sep 20 '16 at 13:56
  • 1
    Now it's working! Thank you very much. Also thanks to everybody who contributed here! I never really used this 'CONTAINS' stuff, didn't quite got the point of it. Maybe that's because I'm more used to a C++ type of code. I guess I'll take a closer look at MODULE and CONTAINS and stuff. Although I thought that using 'USE func_interface is explicitly defining the pointer.. what is the mistake in this thought? – fwillo Sep 20 '16 at 17:42