Question

In a Fortran module, I'm trying to assign initial value to a derived data type whose component is a procedure pointer, but get an error message: unexpected pointer assignment.

In a module, how to assign initial value to a derived type containing a procedure pointer?

    module pointer_mod  

    use legendrePolynomials
    implicit none

    interface
      function func (z)
      real*8 :: func
      real*8, intent (in) :: z
      end function func
    end interface

    type proc_ptr
      procedure (func), pointer, nopass :: f_ptr
    end type proc_ptr

    type(proc_ptr), dimension(6) :: basis

    basis(1) % f_ptr => Legendre0 ! or basis(1) % f_ptr => null()

    end module pointer_mod   

where:

    function Legendre0(x) result(y)
    real, intent(in) :: x
    real :: y
    y = 1
    end function
Était-ce utile?

La solution

You get the error message, because you issue an pointer assignment outside of any subroutines, where usually only declarations should occur. Putting the assignment in a subroutine (see below) shows, that things work perfectly, provided you make sure, the Legendre0() function also use real*8 type in order to match the interface declaration (for testing purposes, I also put the Legendre function in the same module):

module pointer_mod  
  implicit none

  interface
    function func (z)
      real*8 :: func
      real*8, intent (in) :: z
    end function func
  end interface

  type proc_ptr
    procedure (func), pointer, nopass :: f_ptr
  end type proc_ptr

  type(proc_ptr), dimension(6) :: basis


contains

  subroutine test()
    basis(1)%f_ptr => Legendre0 ! or basis(1) % f_ptr => null()
  end subroutine test

  function Legendre0(x) result(y)
    real*8, intent(in) :: x
    real*8 :: y
    y = 1
  end function Legendre0

end module pointer_mod

As an additional comment: You should consider to declare your real variables like

integer, parameter :: dp = kind(1.0d0)
real(dp) :: whatever

instead of the real*8 notation, which is obsolate.

Autres conseils

Another solution would be to make the function pointer of Legendre0 the default for all variables of type(proc_ptr).

type proc_ptr
  procedure (func), pointer, nopass :: f_ptr => Legendre0
end type proc_ptr

But that's probably not what you want because you're handling an array of pointers.

Licencié sous: CC-BY-SA avec attribution
Non affilié à StackOverflow
scroll top