3

I would like to have a derived type, a, which is empty. From this derived type I would like to define further types which extend a. Suppose all of these type extensions contain some generic procedure name, value, i.e value => valuea1, value => valuea2, etc.

If I then want to pass variables of class a to some other procedure, I need to declare the relevant dummy argument of that procedure with class(a). If I do this, however, then referencing the value of the dummy argument leads to compilation failure because the class a is actually empty - only the type extensions contain the procedure.

I could presumably get around this by having some procedure called value inside the type definition of a (then overriding in the extensions). However, given that I never want to declare any object with type a, this seems messy. It it possible to get around this?

Ted Burgess
  • 83
  • 1
  • 5

2 Answers2

3

Yes, you can declare a type bound procedure even for an abstract type. It can be a real type bound procedure, or just an abstract interface.

type, abstract :: a
contains
  procedure :: valuea1, valuea2
  generic value :: value => valuea1, valuea2
end type


abstract interface
  ! the headers of valuea1, valuea2 here
  ! they should have a passed dummy argument class(a)
  ! and some other argument for the generic resolution
  ! for example:

  subroutine valua1(self, x)
    class(a), intent(in) :: self
    real, intent(inout) :: x
  end subroutine

  subroutine valua2(self, x)
    class(a), intent(in) :: self
    integer, intent(inout) :: x
  end subroutine

end interface

This way you cannot create variables of type(a), but you can make extended types which implement their own versions of value.

  • Thanks for your answer. I'm not sure that I'm following completely though... I don't actually need the generic resolution; valuea1 and valuea2 accept the same type of arguments for the problem that I have in mind, I just want to bind to valuea1 in one type extension and valuea2 in another type extension. Is the deferred attribute relevant here? – Ted Burgess Mar 11 '14 at 20:28
  • Then you just bind `value` to different procedures in the extended types. But then their interfaces must be consistent. – Vladimir F Героям слава Mar 11 '14 at 22:07
2

Similar to the answer by @VladimirF, but taking your clarification that

I don't actually need the generic resolution; valuea1 and valuea2 accept the same type of arguments for the problem that I have in mind, I just want to bind to valuea1 in one type extension and valuea2 in another type extension.

Here, then, the base (abstract) type defines a deferred type-bound procedure value() with an interface taking class(a) as the passed argument. Other arguments can be added. Each extending type defines/overrides this type-bound procedure with its own procedure.

This means than in our final subroutine call test_sub the class(a) dummy argument does have a %value().

module types

! The base type
  type, abstract :: a
   contains
     procedure(value_if), deferred :: value
  end type a

! The interface for the type-bound procedures
  abstract interface
     subroutine value_if(var)
       import a
       class(a) var
     end subroutine value_if
  end interface

! The extending types, overriding the value subroutine

  type, extends(a) :: a1
   contains
     procedure :: value => value_a1
  end type a1

  type, extends(a) :: a2
   contains
     procedure :: value => value_a2
  end type a2

contains

  subroutine value_a1(var)
    class(a1) var
    print*, "Value of a1"
  end subroutine value_a1

  subroutine value_a2(var)
    class(a2) var
    print*, "Value of a2"
  end subroutine value_a2

end module types


program test

  use types

  type(a1) x
  type(a2) y

  call x%value
  call y%value

  call test_sub(x)
  call test_sub(y)

contains

  subroutine test_sub(var)
    class(a) var
    call var%value  ! This is defined
  end subroutine test_sub

end program test

This produces output

Value of a1
Value of a2
Value of a1
Value of a2

francescalus
  • 30,576
  • 16
  • 61
  • 96
  • Thanks for the answer. So if I want value_a1 and value_a2 to have different numbers of dummy arguments, do I then need to overload the abstract interface? Apologies for my ignorance... As you can tell, I'm still very much in the early stages of learning about modern fortran. – Ted Burgess Mar 11 '14 at 21:56
  • What I would like to do is something along the lines of what Vladimir F suggested but where the generic resolution is performed according to the class of self as opposed to the dummy argument x. It seems like this isn't possible though. – Ted Burgess Mar 11 '14 at 22:20
  • This is what happens here: if you have `type(a1) self` then `self%value()` resolves to `a1_value(self)`. [To be honest, I hadn't noticed the part about the `x`s of varying types.] – francescalus Mar 11 '14 at 22:26
  • So the problem is the need for consistent interfaces. It seems that I could have some procedure called value which does nothing (and will never be called because I won't declare variables of type a) then to bind value in the extensions. I just hoped that there'd be some other way of doing but because having a redundant procedure seems very inelegant! Although, perhaps when overriding value in the extensions, I will encounter problems because of the interface inconsistency anyway? – Ted Burgess Mar 11 '14 at 22:34
  • Ignoring type-binding for now and say you have `type(a1) x` and `type(a2) y`. The advantage of the deferred type-bound `value` is that for `class(a) z` you can do `call value(z)`. If instead you want to choose (dynamic) between `call value(x, p)` and `call value(y, p, q)` for generic `value` then that advantage has gone away as you are already having to limit your `class(a)`. [Although, see http://stackoverflow.com/a/21487114/3157076.] – francescalus Mar 11 '14 at 22:48
  • And, in practical terms, there is no procedure that does nothing: what could be called `a%value` doesn't exist in the same way there there is never an object of `type(a)`. – francescalus Mar 11 '14 at 22:56