Fortran save procedure as property in derived type

别说谁变了你拦得住时间么 提交于 2019-12-08 08:26:31

问题


Is it possible to store a procedure as a property of a derived type? I was thinking of something along the lines of:

  module funcs_mod
  public :: add
  contains
  function add(y,z) result (x)
    integer,intent(in) :: y,z
    integer :: x
    x = y + z
  end function
  end module

  module type_A_mod
  use funcs_mod
  public :: type_A,set_operator
  type type_A
    procedure(),pointer,nopass :: operator
  end type
  contains
  subroutine set_operator(A,operator)
    external :: operator
    type(type_A),intent(inout) :: A
    A%operator => operator
  end subroutine
  function operate(A,y,z) result(x)
    type(type_A),intent(in) :: A
    integer,intent(in) :: y,z
    integer :: x
    x = A%operator(y,z)
  end function
  end module

  program test
  use type_A_mod
  use funcs_mod
  type(type_A) :: A
  call set_operator(A,add)
  write(*,*) operate(A,1,2)
  end program

But this doesn't successfully compile. Several errors are displayed including:

1) Syntax error in procedure pointer component

and

2) 'operator' at (1) is not a member of the 'type_a' structure

As well as some unsuccessful use statements. Is there a way to do this correctly? Any help is greatly appreciated.

UPDATE:

I've modified procedure,pointer to procedure(),pointer and now the errors are

1) FUNCTION attribute conflicts with SUBROUTINE attribute in 'operator'

and

2) Can't convert UNKNOWN to INTEGER(4)

Both refer to the line x = A%operator(y,z)


回答1:


As you have discovered, the syntax for declaring a procedure pointer declaration requires procedure([interface]), pointer [, ...] :: .... You chose procedure(), pointer, nopass :: operator.

The consequence of procedure() is that you are not declaring whether operator is a function or a subroutine. There is nothing untoward in this, but more work then remains in convincing the compiler that you are using the references consistently. Your compiler appears to not believe you.

Rather than go into detail of what the compiler thinks you mean, I'll take a different approach.

You reference A%operator for a structure A of type with that component as the result of the function operate. You say clearly in declaring this latter function that its result is an integer.

Now, assuming that you don't want to do exciting things with type/kind conversion to get to that integer result, we'll take that you always intend for A%operator to be a function with integer result. That means you can declare that procedure pointer component to be a function with integer result.

This still leaves you with choices:

type type_A
  procedure(integer),pointer,nopass :: operator
end type

being a function with integer result and implicit interface, and

type type_A
  procedure(add),pointer,nopass :: operator
end type

being a function with explicit interface matching the function add.

Your ongoing design choices inform your final decision.

As a final note, you aren't using implicit none. This is important when we consider your line

external :: operator

If operator is a function then (by implicit typing rules) it has a (default) real result. So, you want to change to one of the following

integer, external :: operator

or

procedure(integer) :: operator

or

procedure(add) :: operator

To conclude, and echo the comment by Vladimir F, think very carefully about your design. You currently have constraints from the reference of operate (in the function result and its arguments) that look like you really do know that the component will have a specific interface. If you are sure of that, then please do use procedure(add) as the declaration/



来源:https://stackoverflow.com/questions/34167276/fortran-save-procedure-as-property-in-derived-type

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!