Allow TYPE IS to select multiple types

I suggest that a type is statement be allowed to select multiple types, so that the commented lines below are valid.

subroutine twice(p)
class(*), intent(in out) :: p
select type (p)
   type is (integer)
      p = 2*p
   type is (real)
      p = 2*p
   type is (real(kind=dp))
      p = 2*p
!   would like to replace above with
!   type is (integer, real, real(kind=dp))
!      p = 2*dp
   type is (character (len=*))
      p = trim(p) // trim(p)
end select
end subroutine twice

I skimmed the titles of the issues at GitHub - j3-fortran/generics – I don’t know if that has been proposed. It does not seem hard for users to understand or compiler writers to implement, and it would save some cutting and pasting.

Edit: there is a similar issue More flexible SELECT TYPE at GitHub j3-fortran/fortran_proposals

4 Likes

It makes sense to me to keep dynamic dispatch in an organized way, like the current use of type is that is tied to inheritance. I prefer leave the general type selection to static dispatch (metaprogramming like trait, template, etc).

1 Like

The commented code would have to “expand” to the uncommented version when compiled. because of the select type construct, those lines require different instructions. I.e.

  • integer * integer
  • 2 promoted to real → real * real
  • 2 promoted to real(kind=dp) → real(kind=dp) * real(kind=dp)

I agree that it would occasionally be syntactically convenient, but semantically I think the use cases are probably pretty limited. How often in real projects will you really have duplicated lines in a select case construct?

1 Like

Currently, the “declared type” of p inside the type is block is what was specified. The language would have to be contorted and twisted to say that the declared type can be any of the types named. This doesn’t add anything you can’t already do - “syntactic sugar” - and would be a nightmare to describe.

1 Like

All the time! Usually when calling a generic procedure. Here’s two random snippets from two very different projects:

     select type(value)
     class is (AbstractValue)
        call this%insert(trim(name),value)
     type is (integer)
        call this%insert(trim(name),newValue(value))
     type is ( logical )
        call this%insert(trim(name),newValue(value))
     type is ( real(KIND=DP))
        call this%insert(trim(name),newValue(value))
     type is (character(len=*))
        call this%insert(trim(name),newValue(value))
     class default
        print*, "wrong attribute type insertAttribute0"
     end select
...
    select type (values)
    type is (integer(int8))
      status = nf90_get_var(ncid, varid, values)
    type is (integer(int16))
      status = nf90_get_var(ncid, varid, values)
    type is (integer(int32))
      status = nf90_get_var(ncid, varid, values)
    type is (real(real32))
      status = nf90_get_var(ncid, varid, values)
    type is (real(real64))
      status = nf90_get_var(ncid, varid, values)
    type is (character(len=*))
      status = nf90_get_var(ncid, varid, values)
    class default
      status = NF90_EBADTYPE
    end select

Mixing unlimited polymorphic types and generic procedures is currently quite painful, and almost always involves a lot of copy-pasting.

Could it not be something along the lines of “when there are multiple types in the argument of type is, the subsequent block is expanded as if it had been written once for each type”. So that the compiler rewrites

select type(variable)
type is (type1[, type2, type3, ...])
   <expression>
end select type

literally as

select type (variable)
type is (type1)
   <expression>
type is (type2)
   <expression>
type is (type3)
   <expression>
...
end select type

This sort of rewriting is also being proposed in C++, in the proposed template for as part of the reflection proposal.

This syntactic sugar would probably also go a long way to enabling lots of generic programming without needing to add new syntax, although really one would want compile-time generic programming. A massive downside to the above is that type errors can only be caught at runtime.

2 Likes

Out of 69 uses I found 57 were pure duplicates, only 5 did not have duplicates. Several others were essentially duplicates except a type was involved like “iand(a,2_int8)” in one and “iand(a,2_int16)” where if there was a way to specify a “type that matches the case” they would be duplicates. In quite a few cases I am not counting it looks like the select case is being used in lieu of templating by promoting all integer types or real types to a “larger” type. Looking at all of it the proposal seems to cover the most common case; but it also looks like good templating would be a superior solution, as I see some pretty complicated issues when there are multiple arguments that are class(*). So this does seem to not only be a common usage but the dominant one.

An issue it does not solve is that I see quite a bit of compiler-dependent pre-processor directives saying to only do certain types with certain compilers which this does not solve unless there is a way to say “all real types supported” instead of an explicit list, like real(kind=*) or something, but that seems risky. The most common case is skipping large REAL types for the Nvidia compiler. That raises the thought about TYPE statements for kinds not supported being skipped during compilation instead of causing an error as something to think about.

So my first impression is that good templating would solve the problem more generically, but it would simplify current usage of SELECT CASE in the vast majority of cases, but that a lot of SELECT CASE usage looks (at least at first glance) as a kludge for not having templating.

4 Likes

I see. I usually try harder to redesign things to avoid these kinds of constructs, because they often turn out to be very obnoxious for future maintenance. The generics facility slated for the standard after next is intended to solve these issues, it will just be a while before it is usable.

This screams for a trait construction, something like

interface has_foo
   subroutine foo()
     ! default impl
   end subroutine
end interface

type :: type1(has_foo)
!...
end type

type :: type2(has_foo)
!...
end type
!...
type :: type10(has_foo)
contains
   module procedure :: foo  ! non-default impl
end type

Obviously there needs to be a suite of type-related apparatus to make this work.

3 Likes

Yes, All the time. Just because this construct creates so much code duplication, I always avoid it altogether. This capability is not simply syntactic sugar. The committee can either fix the problem and name it whatever they want, traits, templates, enhancements, or leave the users again with their creativity to develop all sorts of ugly external hacks and preprocessing to achieve their goals.

3 Likes

I thought of a downside to my proposal. It does not seem difficult for a a compiler to expand

type is (integer, real, real(kind=real64), logical)
   x = 2*x

into separate blocks for each type, and then compile or reject the expanded code, but then reporting errors becomes more complicated, since an error in the expanded code must be reported as an error in the original code. Maybe error messages such as

x = 2*x not allowed for x logical

would be needed. There could be nested type is statements with multiple types, further complicating matters. It is important that Fortran compiler error messages stay comprehensible.

A long time ago when I tried to use templates in C++ I found that syntax errors resulted in very long and unreadable error messages. Is that still a problem with modern C++ compilers? I guess the people working to add generics in Fortran want to avoid such pitfalls.

At j3-fortran/fortran_proposals one of those people, Tom Clune, wrote

The compiler developers were adamant that “the way compilers work” does not allow such seemingly simple code transformations as to replicate code for multiple cases in this manner. (For both SELECT RANK and SELECT TYPE. I don’t recall the TYPE IS case being discussed, but possibly the same reason exists. But it would seem to be even simpler as there is no dependent code to compile and execute in this case.

I will say that the “frequent need” for SELECT TYPE does diminish considerably in many cases with careful design. The primary ones that do not involve intrinsic types. E.g., a common case that two objects must have the same type appears as a doubly nested mess of SELECT TYPE statements. However the Visitor (also called Bridge) design pattern provides a way to implement double dispatch in a single dispatch language. Whether the extra complexity is better than the tangle of SELECT TYPE depends on the use case and the eye of the developer.

And of course, next generation Generics features in the language will also reduce the need for such nested SELECT TYPE’s in the future. But that’s a ways off.

A preprocessor could be developed to expand the type is line above to standard Fortran.

No. Compilers nowadays are much improved on type errors.

I still believe type is should only be used as a syntactic sugar on top of dynamic polymorphism. It encourages mixing interface and implementation, and further expansion in that direction just motivates more bad design and ugly code. I hope fortran steers away from it and spend more time on static polymorphism.

Fypp does that already, but of course, it looks somewhat uglier than native code only:

#:set TYPES = ['integer', 'real', 'real(kind=real64)', 'logical']
#:for TYPE in TYPES
type is (${TYPE}$)
  x = 2*x
#:endfor

But, let’s hope, that at some point (in 10-15 years?) we don’t need such constructs any more (and can dispose fypp) thanks to the generics offered by the Fortran language …

5 Likes