Fortran save procedure as property in derived type
Asked Answered
I

1

1

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)

Immotile answered 8/12, 2015 at 22:28 Comment(3)
You need procedure() or procedure(interface) for a procedure pointer component of a derived type.Playsuit
Hmm, okay. I tried that, but I get new compilation errors: 1) FUNCTION attribute conflicts with SUBROUTINE attribute in 'operator'. and 2) Can't convert UNKNOWN to INTEGER(4)Immotile
Forget external and never use it again (at least I do not). You need a proper interface block. And show your full code which generates the error. You must use interfaces compatible with add.Pitcher
P
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/

Playsuit answered 8/12, 2015 at 23:21 Comment(8)
Excellent, thank you! I left out the implicit none's from this question because I was just trying to reduce the number of lines...Immotile
Also, thank you for commenting about needing integer in "integer, external :: operator". This clears some other things up too. Thanks again!Immotile
Yeah, it was. If instead this were a subroutine, how would needing integer in "integer, external :: operator" change?Immotile
With a subroutine one still has to decide: implicit or explicit interface. external says implicit, and explicit comes from specifying the interface (somehow). [With external, then integer, external, would be wrong for a subroutine as that is a function declaration.]Playsuit
I'm realizing now that I won't be able to apply this to my code since I use subroutines in my code... =[Immotile
Ahh, I see. For subroutine you basically cannot prescribe the type since multiple parameters can be passed.. Is there any other way to make subroutines explicit without specifying the specific procedure?Immotile
Subroutines don't have types - the type for a function is that of its result. So, the declaration is unrelated to the arguments (and subroutines don't have results). It's possible to use an abstract interface to give an explicit interface or even any other subroutine. Saying a procedure has an interface matching a given subroutine doesn't mean that the procedure is exactly that subroutine (just "looks" the same) - but I think that's a different question, really.Playsuit
Right, I know there's no result type for subroutines. I wasn't sure if I would have had the same error or not. Awesome, I got it working, thanks again!Immotile

© 2022 - 2024 — McMap. All rights reserved.