Drawback of type-bound procedures (vs. interfaces)?

Context

Suppose we have several modules of the general form:

module abc_m
  ⋮
  type abc_t
    integer :: int1
    real :: real1
    ⋮
  end type abc_t

  contains

  subroutine abc_sub1_i(this, a, …)
    ⋮
  end subroutine abc_sub1_i

  subroutine abc_sub1_r(this, a, …)
    ⋮
  end subroutine abc_sub1_r

  subroutine abc_sub2(this, a, …)
    ⋮
  end subroutine abc_sub2

    ⋮

end module abc_m

Some of the procedures are similar for different types, e.g. create, destroy, print.

One option to streamline the usage would be to add interfaces to each module:

  interface init
    module procedure :: abc_init
  end interface init

  interface sub1
    module procedure :: abc_sub1_i
    module procedure :: abc_sub1_r
  end interface sub1

  ⋮

(I was a bit surprised that you can define interfaces with the same name at different locations.)

Alternatively one could use type-bound procedures:

  type abc_t
    ⋮
    contains
    procedure :: init => abc_init
    procedure :: sub1 => abc_sub1_i, abc_sub1_r
    ⋮
  end type abc_t

I like the type-bound approach as you only have to import the type and get all the procedures without cluttering the namespace.

Questions

  1. Are there drawbacks to type-bound procedures or changing type(abc_t) to class(abc_t) in the procedures?
  2. I suppose the type-bound approach would be called object-oriented (even if we ignore interitance and polymorphism here), is there a name for the interface approach?
  3. Do you have any thoughts on this topic?
2 Likes
  1. Using class(abs_t) will slow down the running speed. The specific procedure is dynamically dispatched during execution, that is polymorphism.
  2. I think they are just called function overloading.

Apologies for reviving an old thread but I have similar questions. Background: I’m revisiting fortran after using F90/95 > 10 years ago. I never really used the interface stuff tho, kept it pretty basic.

As part of this I was reading the really nice book ‘Modern Fortran’ by Milan Curcic. I was enjoying chapter 9 on generic procedures which covers the interface approach. Then I get to chapter 10 on overloading operators for derived types and I figured we could just use interfaces again — cool! All of a sudden tho we’re using type bound procedures which seem to require a different mechanism and the whole ‘generic :: =>’ approach.

After some searching I realised that you can still use the interface approach if (??) you don’t use type bound procedures but rather keep them outside the type definition. See also the post above!

So, I’m curious about the pros and cons of each and whether there is a ‘recommended’ approach for overloading operators for derived types? The OP indicates that they prefer the type bound approach due to module importing behaviour, which makes sense, but aesthetically I think I prefer the ‘generic function’ approach a bit more. Is this frowned upon in post 90/95 fortran?

Obviously the type bound approach is more similar to traditional OO, but I think you could make a case that the generic function approach is similar to what some R folk call ‘functional object oriented programming’ eg (from Introduction | Advanced R)

There are two main paradigms of object-oriented programming which differ in how methods and classes are related. In this book, we’ll borrow the terminology of Extending R and call these paradigms encapsulated and functional:

  • In encapsulated OOP, methods belong to objects or classes, and method calls typically look like object.method(arg1, arg2) . This is called encapsulated because the object encapsulates both data (with fields) and behaviour (with methods), and is the paradigm found in most popular languages.
  • In functional OOP, methods belong to generic functions, and method calls look like ordinary function calls: generic(object, arg2, arg3) . This is called functional because from the outside it looks like a regular function call, and internally the components are also functions.

With this terminology in hand, we can now talk precisely about the different OO systems available in R.

5 Likes

Welcome @omacl.

I don’t think it’s frowned upon – IMO they’re both good approaches.

3 Likes

There is one minor but irritating drawback to type bound procedures: editor tooling does not normally recognise them, so you cannot ctrl/Q or equivalent to jump to the definition, this will improve but I do not have the skills (yet?) to help

1 Like

Hi @omacl and thank you for the nice words. Mostly answered across the posts in this thread, but here to summarize the key differences:

  • In the type-bound approach the call resolution is done at run-time (because input argument is class–polymorphic), which adds some overhead. In the basic interface approach the call resolution is done at compile time.
  • In the type-bound approach your operators come bundled with the type, so you only need to import the type from the module. In the basic interface approach, you need to import operators explicitly, e.g. `use m, only: mytype, operator(+), operator(*), …
  • In the type-bound approach the operators will work with types that extend the parent type, whereas in the basic interface approach you’d need to define separate interfaces for the extending type.

Both approaches are fine. I think of them as two different styles, each with minor pros and cons.

6 Likes

Fantastic, thanks all for the replies!

A last quick naive question, slightly ill-formed. My understanding is that interfaces and operator overloading essentially act to ‘append’ to any existing overloading. So when doing

use m, only: mytype, operator(+), operator(*)

the operator(+) doesn’t overwrite/replace existing definitions but ‘appends’ the implementation for mytype to the list of implementations for other types.

Is this roughly correct? And presumably means I could write an interface block with the same name multiple times, say in the same module, and each time it ‘adds’ to the list of specific implementations for that generic function? Is this ‘appending’ or ‘additive’ behaviour of the generic interface names explicitly discussed somewhere (eg in a book or other documentation)?

Yes, overloading appends and does not replace, the ‘gotcha’ is that the interfaces have to be public of course (I may be the only person ever to have forgotten this)

It is common to have multiple overloads in a single module to cover, for instance, arguments of different kinds.

Bon voyage

1 Like

With one possible exception of overloading the derived type assignment which in fact does replace the intrinsic assignment,

1 Like

Just as a note for the record, re: where the concatenation behaviour is documented, I found this in the most recent ‘Modern Fortran Explained’ (including 2018) in ‘Section 8.14 The use statement‘:

A name clash is also permissible for a generic name that is required. Here, all generic interfaces accessed by the name are treated as a single concatenated interface block. This is true too for defined operators, and also for defined assignment (for which no renaming facility is available). In all these cases, any two procedures having the same generic identifier must differ as explained in Section 5.18. We imagine that this will usually be exactly what is needed. For example, we might access modules for interval arithmetic and matrix arithmetic, both needing the functions sqrt, sin, etc., the operators +, -, etc., and assignment, but for different types.