j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
173 stars 14 forks source link

Traits For Types #125

Open everythingfunctional opened 4 years ago

everythingfunctional commented 4 years ago

Java calls them interfaces, Haskell calls them type classes, and Rust calls them traits. But the basic gist is that you can define the procedures that a type must have in order to implement a trait. A type can then be marked as implementing that trait, and procedures and types can specify traits instead of just types or classes.

The additional syntax would be as follows.

A new block structure, similar to interface, that defines a trait. I.e.

trait some_trait
    function someFunc(self, other)
        trait(some_trait), intent(in) :: self
        integer, intent(in) :: other
        real :: someFunc
    end function someFunc

    subroutine someRoutine(input, output)
        integer, intent(in) :: input
        integer, intent(out) :: output
    end subroutine someRoutine
end trait some_trait

A new statement only valid in a type definition. I.e.

type, public :: someType
    implements some_trait
contains
    procedure :: someFunc => someTypeSomeFunc
    procedure, nopass :: someRoutine => someTypeSomeRoutine
end type someType

And a new keyword for variable declarations. I.e. the following would all be valid

subroutine doSomething(some_input)
    trait(some_trait), intent(in) :: some_input
    ...
end subroutine doSomething
type, public :: someOtherType
    trait(some_trait), allocatable :: something
end type someOtherType
program hello
    ...
    trait(some_trait), allocatable :: something
   ...
    allocate(someType :: something)
   ...
end program hello

The compiler must simply confirm that a type implements the procedures in the trait with the correct interfaces, and any type used where trait(some_trait) is specified must simply be checked to have implemented that trait. The run time implications are basically just an extension of the dynamic capabilities that class(someClass) already offers.

I think that this would enable techniques and patterns that would otherwise require parameterized types, multiple inheritance, or templates, or all 3, without requiring a hugely significant change to the inner workings of the language or the syntax.

certik commented 4 years ago

Yes!

This is precisely how we concluded templates should be implemented at the last J3 meeting. I think it's also called strong concepts in C++.

The advantage of the approach you described is that the compiler can provide good error messages and relatively quick compile times compared to the traditional C++ templates.

So I think this proposal should be pursued.

On Sat, Dec 28, 2019, at 8:58 PM, Brad Richardson wrote:

Java calls them interfaces, Haskell calls them type classes, and Rust calls them traits. But the basic gist is that you can define the procedures that a type must have in order to implement a trait. A type can then be marked as implementing that trait, and procedures and types can specify traits instead of just types or classes.

The additional syntax would be as follows.

A new block structure, similar to interface, that defines a trait. I.e.

`trait some_trait function someFunc(self, other) trait(some_trait), intent(in) :: self integer, intent(in) :: other real :: someFunc end function someFunc

subroutine someRoutine(input, output)
    integer, intent(in) :: input
    integer, intent(out) :: output
end subroutine someRoutine

end trait some_trait ` A new statement only valid in a type definition. I.e.

type, public :: someType implements some_trait contains procedure :: someFunc => someTypeSomeFunc procedure, nopass :: someRoutine => someTypeSomeRoutine end type someType And a new keyword for variable declarations. I.e. the following would all be valid

subroutine doSomething(some_input) trait(some_trait), intent(in) :: some_input ... end subroutine doSomething type, public :: someOtherType trait(some_trait), allocatable :: something end type someOtherType program hello ... trait(some_trait), allocatable :: something ... allocate(someType :: something) ... end program hello The compiler must simply confirm that a type implements the procedures in the trait with the correct interfaces, and any type used where trait(some_trait) is specified must simply be checked to have implemented that trait. The run time implications are basically just an extension of the dynamic capabilities that class(someClass) already offers.

I think that this would enable techniques and patterns that would otherwise require parameterized types, multiple inheritance, or templates, or all 3, without requiring a hugely significant change to the inner workings of the language or the syntax.

— You are receiving this because you are subscribed to this thread. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/125?email_source=notifications&email_token=AAAFAWHOCMNP5YU57XM3TNLQ3AN47A5CNFSM4KAWLA7KYY3PNVWWK3TUL52HS4DFUVEXG43VMWVGG33NNVSW45C7NFSM4IDCJZEQ, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWE6RSGUVWH33HLIUSDQ3AN47ANCNFSM4KAWLA7A.

everythingfunctional commented 4 years ago

Actually, I think implements should not be a statement, but an attribute of the type. Similar to extends. I.e.

type, public, implements(some_trait) :: someType
contains
    procedure :: someFunc => someTypeSomeFunc
    procedure, nopass :: someRoutine => someTypeSomeRoutine
end type someType
everythingfunctional commented 4 years ago

It would also be desirable if more than one trait could be specified. I.e. a type could implement multiple traits, and an argument or variable could be required to implement multiple traits.

cmacmackin commented 4 years ago

While I agree that this would be a useful feature, I'd question whether it should be taken as the sole means by which to implement generic programming (as @certik seems to suggest). This issue is that it does not allow generic code to be written for the intrinsic types (e.g., an algorithm which could work with both reals and integers). While this could be overcome by wrapping the intrinsic types, that would be a rather tedious and inelegant workaround.

Furthermore, how would one declare derived-type components by a trait. Would they be treated in much the same way as polymorphic variables? The downside of this as a way to create generic containers is that it would not allow for compile-type type-checking.

Where these traits could be useful, however, would be as a means of constraining type-parameters such as those discussed in #4.

certik commented 4 years ago

It does allow to write generic code that works for both reals and integers. One specifies a trait (we called it an interface) that requires the arithmetic operations that you need, and if both real and integers satisfy it, then you can use both.

On Sun, Dec 29, 2019, at 9:09 PM, Chris MacMackin wrote:

While I agree that this would be a useful feature, I'd question whether it should be taken as the sole means by which to implement generic programming (as @certik https://github.com/certik seems to suggest). This issue is that it does not allow generic code to be written for the intrinsic types (e.g., an algorithm which could work with both reals and integers). While this could be overcome by wrapping the intrinsic types, that would be a rather tedious and inelegant workaround.

Furthermore, how would one declare derived-type components by a trait. Would they be treated in much the same way as polymorphic variables? The downside of this as a way to create generic containers is that it would not allow for compile-type type-checking.

Where these traits could be useful, however, would be as a means of constraining type-parameters such as those discussed in #4 https://github.com/j3-fortran/fortran_proposals/issues/4.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/125?email_source=notifications&email_token=AAAFAWGTGACHZXH57LN52ZTQ3FYA7A5CNFSM4KAWLA7KYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEHZQ53Y#issuecomment-569577199, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWHYZDXRR4UY37T6KWLQ3FYA7ANCNFSM4KAWLA7A.

cmacmackin commented 4 years ago

It does allow to write generic code that works for both reals and integers. One specifies a trait (we called it an interface) that requires the arithmetic operations that you need, and if both real and integers satisfy it, then you can use both.

Given that the proposal required derived types to have an implements statement or attribute for them to match a trait, it's not clear to me that this is the case.

certik commented 4 years ago

Well, the details have to be figured out, but that should be the goal.

On Mon, Dec 30, 2019, at 4:14 AM, Chris MacMackin wrote:

It does allow to write generic code that works for both reals and integers. One specifies a trait (we called it an interface) that requires the arithmetic operations that you need, and if both real and integers satisfy it, then you can use both.

Given that the proposal required derived types to have an implements statement or attribute for them to match a trait, it's not clear to me that this is the case.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/125?email_source=notifications&email_token=AAAFAWAUYLMUOWNME5HYO63Q3HJ27A5CNFSM4KAWLA7KYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEH2CU5I#issuecomment-569649781, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWCK3YPTQW2QB26VY5DQ3HJ27ANCNFSM4KAWLA7A.

everythingfunctional commented 4 years ago

@cmacmackin , if there are some built-in traits that real, integer, etc. do implement, then you could write generic code that works for both reals and integers. While I agree that traits do not enable every kind of generic programming, I think it does take you farther than any other single feature would.

As for derived-type components, yes, they would be treated like polymorphic variables. Correct, you wouldn't get as much compile-time type-checking, but you won't be able to get full compile-time type-checking without a full unification and constraint solver like you would find in Haskell.

jacobwilliams commented 4 years ago

@certik Is there any write up of what was decided about this at the J3 meeting?

I also like the type, public, implements(some_trait) :: someType syntax. Multiple traits would also be key in order to be really useful (e.g., you've got some object you want to use with two different libraries, each of which require some different traits).

klausler commented 4 years ago

What distinguishes a "trait" from an ABSTRACT derived type (7.5.2) plus multiple inheritance?

everythingfunctional commented 4 years ago

@klausler With inheritance, you also get other components and type bound procedures that you might not want. You could in theory use multiple inheritance like traits, but multiple inheritance involves dealing with a lot more problems.

klausler commented 4 years ago

@klausler With inheritance, you also get other components and type bound procedures that you might not want. You could in theory use multiple inheritance like traits, but multiple inheritance involves dealing with a lot more problems.

Well, thanks for the reply, but I'm still not seeing what a "trait" does that an ABSTRACT type can't do.

everythingfunctional commented 4 years ago

That's actually kind of the point. It doesn't do everything that abstract types can do. Which makes it easier to implement, and easier to understand how it's supposed to be used.

Sometimes a feature with the right constraints is actually better than a feature that can do everything.

klausler commented 4 years ago

That's actually kind of the point. It doesn't do everything that abstract types can do. Which makes it easier to implement, and easier to understand how it's supposed to be used.

Sometimes a feature with the right constraints is actually better than a feature that can do everything.

Thanks for the confirmation.

jacobwilliams commented 4 years ago

Also, abstract types can't handle the intrinsic types. If you require a user to extend an abstract type to use a sorting library, then they aren't going to be able to use real, integer, variables. We don't want to have to wrap these into a custom type just to use a library, and then have to add all the operators that are already present for intrinsic types. That's one of the major problems we have now that this would solve if implemented well.

klausler commented 4 years ago

Also, abstract types can't handle the intrinsic types. If you require a user to extend an abstract type to use a sorting library, then they aren't going to be able to use real, integer, variables. We don't want to have to wrap these into a custom type just to use a library, and then have to add all the operators that are already present for intrinsic types. That's one of the major problems we have now that this would solve if implemented well.

But the intrinsic types could be predefined to have procedures, such as the OPERATOR(<=) needed by a sorting routine, yes?

certik commented 4 years ago

The abstract type approach requires a type A to subclass it in order for the user to use A in the generic subroutine, correct?

The advantage of the "interface" approach as we discussed at J3 meeting (I'll try to write up what we discussed soon) is that user types, such as A above, do not need to subclass anything. Thus the approach works like one would expect from templates.

On Mon, Dec 30, 2019, at 12:04 PM, Peter Klausler wrote:

Also, abstract types can't handle the intrinsic types. If you require a user to extend an abstract type to use a sorting library, then they aren't going to be able to use real, integer, variables. We don't want to have to wrap these into a custom type just to use a library, and then have to add all the operators that are already present for intrinsic types. That's one of the major problems we have now that this would solve if implemented well.

But the intrinsic types could be predefined to have procedures, such as the OPERATOR(<=) needed by a sorting routine, yes?

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/125?email_source=notifications&email_token=AAAFAWEQBOXDYZNOXZTQP5DQ3JA2PA5CNFSM4KAWLA7KYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEH267UY#issuecomment-569765843, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWEMANENJ2VM7EZ5FP3Q3JA2PANCNFSM4KAWLA7A.

klausler commented 4 years ago

The abstract type approach requires a type A to subclass it in order for the user to use A in the generic subroutine, correct? The advantage of the "interface" approach as we discussed at J3 meeting (I'll try to write up what we discussed soon) is that user types, such as A above, do not need to subclass anything. Thus the approach works like one would expect from templates. On Mon, Dec 30, 2019, at 12:04 PM, Peter Klausler wrote: > > Also, abstract types can't handle the intrinsic types. If you require a user to extend an abstract type to use a sorting library, then they aren't going to be able to use real, integer, variables. We don't want to have to wrap these into a custom type just to use a library, and then have to add all the operators that are already present for intrinsic types. That's one of the major problems we have now that this would solve if implemented well. But the intrinsic types could be predefined to have procedures, such as the OPERATOR(<=) needed by a sorting routine, yes? — You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub <#125?email_source=notifications&email_token=AAAFAWEQBOXDYZNOXZTQP5DQ3JA2PA5CNFSM4KAWLA7KYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEH267UY#issuecomment-569765843>, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWEMANENJ2VM7EZ5FP3Q3JA2PANCNFSM4KAWLA7A.

ABSTRACT types today must contain only procedures that are DEFERRED, and those cannot be referenced until they are overridden in an extended type. yes.

certik commented 4 years ago

Let's discuss the various approaches on a simple example from #46. The syntax is just preliminary (I don't even like it myself, but that's not the point here):

    <T> function f(x)
    <T>, intent(in) :: x
    f = x + 1
    end function

This is just the old fashioned C++ style templates. What we discussed at the J3 meeting is that this causes slow compile times and very long unreadable error messages. The solution to both is to provide some kind of an interface (I just wrote this up, there might be some slight mistakes):

  type, requirements :: T
  contains
    generic :: operator(+) => plus
  end type

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs, rhs
      type(T) :: plus
    end function
  end interface

    type(T) function f(x)
    type(T), intent(in) :: x
    f = x + 1
    end function

Then when you use this, you can just call it with any type that satisfies the type, requirements :: T above, and you do not subclass it. As an example both of these should just work:

integer :: a, b
b = 1
a = f(b) # a will be equal to 2

and

real :: a, b
b = 1
a = f(b) # a will be equal to 2

as well as any user defined type that defines operator(+) with the above signature:

type(user_type) :: a, b
b = ...
a = f(b) # "a" will be equal to "b" + 1

The way this would work is that the compiler would check that user_type or integer or real (from the above three examples) satisfies the type, requirements :: T "interface". If it does, then it compiles and works. If it does not, then it emits a nice error message why the user type does not satisfy the interface. Finally, while compiling the generic function "f(x)" above (typically in some library), the compiler will check that the body of the function only uses operations are declared in the "interface requirements" T. If the function "f" uses an operation that was not defined, the compiler will emit an error right away (as opposed to at instantiation time, as in current C++). The compile times will be shorter also, because the compiler only needs to compile "f" once (and check that it conforms to the type "T"). After that, at instantiation time, the compiler only has to check the user type against the interface "T", it does not have to go through the whole subroutine ensuring that everything is used correctly for the given case. This roughly corresponds to "strong concepts" from C++ (proposed for C++11, but did not get in).

The current C++ has so called "weak concepts", where the compiler checks user code at instantiation time against the interface. But it does not check the code of "f" against T. So there can still be long error messages.

So this is roughly what we discussed at the last J3 meeting. See here for more info: https://github.com/j3-fortran/fortran_proposals/issues/4#issuecomment-552139256.

klausler commented 4 years ago

This idea defers type resolution to runtime for the function f, rather than instantiating f at compilation time separately for each necessary combination of argument types, correct?

everythingfunctional commented 4 years ago

@klausler , you could probably do both. In some instances it would be possible to specialize and inline a generic function, in others it might not be possible, (i.e. you're variable is class(something) and so you still need the vtable lookup at run time), or you might be concerned about bloating the size of your binary.

By specifying the trait on both the type definition and the variable declarations, you don't actually have to recheck whether the type satisfies the trait at every use.

certik commented 4 years ago

@klausler the idea is fully compile time, there is no runtime resolution. To be specific and clear, let's have a module A.f90:

module A
implicit none
private
public :: T, f

  type, requirements :: T
  contains
    generic :: operator(+) => plus
  end type

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs, rhs
      type(T) :: plus
    end function
  end interface

contains

    type(T) function f(x)
    type(T), intent(in) :: x
    f = x + 1
    end function

end module

When you compile it, the compiler will check that f conforms to the interface T and report any errors. Internally it will store the generic (un-instantiated) version of f in the A.mod file. Then let's have a B.f90 file with:

program B
use A, only: f
implicit none
integer :: a, b
b = 1
a = f(b) # a will be equal to 2
end

When compiling B.f90, the compiler will check that the type of b (which is integer) conforms with the interface T in the module A. If it conforms, then we know that f can be instantiated, without checking f again (thus this check is quick). So it will instantiate f at the compile time of B.

klausler commented 4 years ago

Thanks for the clarification.

Can f be defined as a separate module procedure?

(Additional question) And how is the availability of a conversion from default INTEGER (for 1) to T indicated?

certik commented 4 years ago

Can f be defined as a separate module procedure?

Like this?

module A
implicit none
private
public :: T

  type, requirements :: T
  contains
    generic :: operator(+) => plus
  end type

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs, rhs
      type(T) :: plus
    end function
  end interface

end module A

module A2
use A, only: T
implicit none
private
public :: f

contains

    type(T) function f(x)
    type(T), intent(in) :: x
    f = x + 1
    end function

end module A2

I think so.

(Additional question) And how is the availability of a conversion from default INTEGER (for 1) to T indicated?

This is something we discussed at the J3 meeting, and there are several ideas, but I don't think we figured out how to best do this yet. @tclune do you remember about this particular point?

FortranFan commented 4 years ago

@certik wrote:

..

(Additional question) And how is the availability of a conversion from default INTEGER (for 1) to T indicated?

This is something we discussed at the J3 meeting, and there are several ideas, but I don't think we figured out how to best do this yet. ..

Why won't this be per the usual language rules? That, when the processor "will instantiate f at the compile time of B" for type REAL say, will it not simply create an instantiated f like so

   real function instantiated_f(x)
      real, intent(in) :: x
      instantiated_f = x + 1
   end function

and in which case, the standard stipulations toward the above mixed-mode arithmetic will apply?

certik commented 4 years ago

Why won't this be per the usual language rules? That, when the processor "will instantiate f at the compile time of B" for type REAL say, will it not simply create an instantiated f like so

   real function instantiated_f(x)
      real, intent(in) :: x
      instantiated_f = x + 1
   end function

and in which case, the standard stipulations toward the above mixed-mode arithmetic will apply?

This is the natural thing to do. But the problem is that if this approach can cause the code to be in error at instantiation? If so, then this is not going to work, as that would be equivalent to the "weak concepts" from C++. Instead, we want the "strong concepts", because we want to catch all errors in f at the compile time of the module A, not B. So the T declaration must possibly be extended with the exact operations that are needed, such as implicit conversions.

These are the details that we have to iron out.

everythingfunctional commented 4 years ago

I have an example which would demonstrate why a function may not be able to be fully "instantiated" at compile time. It's a bit convoluted though. Have a trait T defined, and an abstract type A that implements T. Then have a type B that extends from A. Now, have a procedure that takes as input something that implements trait T. Declare an allocatable variable of class(A), and pass that as input to the procedure. At this point, you can't actually fully instantiate the procedure with a concrete type, because you don't know which concrete type will actually be used. And especially if that procedure calls another procedure that takes a trait, it definitely won't know at compile time what actual type will be passed. You have to use the same method that class variables use (vtables) to look up the actual procedure at run time.

module traitT

    trait T
        function traitFunction(input)
            trait(T), intent(in) :: input
            integer :: traitFunction
        end function
    end trait
end module traitT

module abstractA
    use traitT, only: T

    type, abstract, implements(T) :: A
    contains
        procedure :: traitFunction => ATraitFunction
    end type A
contains
    function ATraitFunction(input)
        class(A), intent(in) :: input
        integer :: ATraitFunction

       ATraitFunction = 1
    end function ATraitFunction
end module abstractA

module typeB
    use abstractA, only: A

    type, extends(A) :: B
    contains
        procedure :: traitFunction => overideTraitFunction
    end type B
contains
    function overideTraitFunction(input)
        class(B), intent(in) :: input
        integer :: overideTraitFunction

        overideTraitFunction = 2
    end function overideTraitFunction
end module typeB

module routines
    use traitT, only: T
contains
    subroutine f(input)
        trait(T), intent(in) :: input

        call g(input)
    end subroutine f

    subroutine g(input)
        trait(T), intent(in) :: input

        print *, input%traitFunction()
    end subroutine g
end module routines

program orchestrate
    use traitT, only: T
    use abstractA, only: A
    use typeB, only: B
    use routines, only: f

    class(A), allocatable :: x

    allocate(B :: x)
    call f(x)
end program orchestrate

I'm pretty sure the above is perfectly valid except for the trait part, but you could substitute that with another abstract type that A extends from instead and it would actually be valid. This is a contrived example, but you can kind of see my point. You would expect this program to print 2, but if it tried to actually "instantiate" at compile time, it'd probably end up printing 1 because it would instantiate the routines as taking type A and end up calling ATraitFunction instead of overideTraitFunction.

certik commented 4 years ago

@everythingfunctional seems the only difference between your proposal and what I described above is that in your proposal, user types such as A in your previous comment has to specify which trait it implements (type, abstract, implements(T) :: A). Is that necessary? That would prevent intrinsic types like integer / real to be used, and also it prevents the type A to be used with other traits. What is your opinion on that? Are there any other differences between what you proposed and what I tried to describe above about what we discussed at the last J3 committee meeting? If they are the same, then we can use this issue. If they are different, then I am going to create a separate issue for the J3 proposal. I initially thought they are the same, but after seeing more examples and carefully reading what you wrote, it seems maybe they are not the same. If you could help clarify that, I would really appreciate it.

Regarding your last comment about runtime instantiation: I think that is no different to using templates in C++ with virtual functions ---- they will resolve to the base class function, known at compile time, not the overloaded function known at runtime. So the above example in C++ would return 1.

If you want it to resolve to the "overloaded" function (and return 2), you have to use the CRTP pattern where you explicitly type the base class to a subclass at compile time, and then the template resolves to the overloaded function, at compile time.

I would think the above design (everything at compile time) would make the most sense, as there will be no runtime overhead.

everythingfunctional commented 4 years ago

Syntactically, I think that is the only difference. But, my proposal would be that you could provide a list of traits that are satisfied there. Also, I would propose you be able to specify a list of traits for procedure arguments and allocatable variables. That way you could say this procedure needs something that is Addable and Showable (i.e. has operator(+) and procedure toString defined).

Rust has some traits that are built in to the language. I would propose some be added to the Fortran standard as well. That way intrinsic types could be used for at least some traits. It would also beneficial if there was some way to add traits, or even type bound procedures, to intrinsic types. I don't know if that's too much to ask, but Rust has it. Or perhaps your idea of not specifying which traits a type implements would be sufficient.

I was unclear on that behavior of C++. What does Fortran currently do in this situation? I haven't tested it. I like the idea of no runtime overhead, but sometimes you can't get away from it. In my example, of f calling g, would the whole call chain have to be instantiated at call f(x)? Seems like that would add a lot of overhead to compilation times.

certik commented 4 years ago

Ok, let's keep just this issue for now to discuss the details, it seems it's quite similar, and we have not moved beyond what I described above either at the J3 committee.

Regarding your last paragraph, indeed, the whole chain f and g are "templated" / "generic", and so the whole chain has to be instantiated (at compile time).

klausler commented 4 years ago

Can f be defined as a separate module procedure?

Like this?

No. Separate module procedures (15.6.2.5) are defined with MODULE PROCEDURE, possibly in a submodule.

jacobwilliams commented 4 years ago

I was thinking... would it be useful if some traits were optional, and a procedure could query if an input had a certain trait and then do something with that information?

I was thinking of the automatic differentiation application (see #95). You could write a function that had an optional derivative calculation, but only if you gave it a class where you needed that (if you passed in a real, it wouldn't do that part).

FortranFan commented 4 years ago

@certik wrote:

FortranFan wrote: Why won't this be per the usual language rules? That, when the processor "will instantiate f at the compile time of B" for type REAL say, will it not simply create an instantiated f like so

   real function instantiated_f(x)
      real, intent(in) :: x
      instantiated_f = x + 1
   end function

and in which case, the standard stipulations toward the above mixed-mode arithmetic will apply?

.. Instead, we want the "strong concepts", because we want to catch all errors in f at the compile time of the module A, not B. So the T declaration must possibly be extended with the exact operations that are needed, such as implicit conversions. ..

With respect to your comment in https://github.com/j3-fortran/fortran_proposals/issues/125#issuecomment-569834089 , I assume you meant to catch errors at compile-time of module A2?

Assuming yes and keeping in mind the J3 discussion on "requirements" was in the context of generics toward a possible Fortran 202Y design, can the "strong concept" mean a "strong" requirement is enforced on all instructions?

Meaning, in your generic procedure f that employs the requirements of the abstract interface given with plus, an instruction such as z = x + y where x, y, and z are all type(T) can be permitted because it can be seen by a processor as clearly matching up with the interface in plus?

Whereas an instruction such as x = x + 1 can be considered a weak match with possible mixed-mode arithmetic and thus be disallowed?

certik commented 4 years ago

With respect to your comment in #125 (comment) , I assume you meant to catch errors at compile-time of module A2?

Yes.

My understanding of the strong concept is that A2 is fully checked at its compile time, and it will not fail at instantiation. While weak concept is that user type is still checked against the "requirement", but the function f can fail to instantiate if is uses features that are not part of the "requirement". If my understanding is incorrect, let me know.

certik commented 4 years ago

@tclune I tried to summarize our latest status on templates from the last J3 meeting in this issue. Would you have time to make some progress on this before our next meeting? It would be nice to have some draft of a proposal, even if very preliminary. If we wait until we meet at the J3 meeting, it will be too late.

difference-scheme commented 4 years ago

Yes, this is absolutely essential, and it is incomprehensible why this is still not part of the language!

I was about to open an Issue for this myself, but I will simply comment here, instead, on what I believe would be the best way to proceed.

I think that in order to get this feature rapidly into the language it is essential to focus on run-time polymorphism (i.e. OOP) first. One should leave a potential use of some similar feature for compile-time polymorphism (i.e. generics) to some later revision, that will deal with such complications separately.

A 'trait' as it was called above is, in Fortran speak, nothing but an abstract type, with the important restriction that it is prohibited to contain any fields (i.e. variables) or non-deferred methods, i.e. any implementation code. Like an abstract type it may contain deferred procedures, and like an abstract type it cannot be instantiated.

I prefer the name 'interface type' instead of 'trait' because the syntax for the aforementioned semantics most compatible with present-day Fortran is something like the following

type, abstract, interface :: InterfaceType1
contains
  procedure(proc), deferred :: method1
end type InterfaceType1

abstract interface
  subroutine proc()
  end subroutine proc
end interface

(notice the nice double occurrence of "abstract" and "interface" for consistency). So the only new thing required above is the new type-qualifier "interface" in the type declaration. Thus the compiler will know that the insertion of anything above the contains statement is forbidden, and that any procedure declared below the contains statement must be deferred.

To use the feature one will simply code the following

type, implements(InterfaceType1) :: ConcreteType
contains
  procedure :: method1
end type ConcreteType

and provide an implementation of method1. Notice that it is this mechanism (i.e. "implements" inheritance) which will allow polymorphism, e.g. if InterfaceType1 is used in another type, like so

type :: SomeOtherType
  class(InterfaceType1), allocatable :: obj
end type SomeOtherType

I think that no completely new syntax should be necessary here. We should still be able to use the "class" statement, since InterfaceType1 is nothing but a (special) form of an abstract type, and "implements" inheritance is a (special) form of inheritance. But I'd like to hear other views on this.

If we need to conform to two InterfaceTypes we would have, e.g., something like the following:

type, implements(InterfaceType1,InterfaceType2) :: ConcreteType
contains
  procedure :: method1
  procedure :: method2
end type ConcreteType

This could then be combined also with implementation inheritance to, e.g., inherit variables and concrete versions of method1/method2 from some ConcreteBaseType

type, extends(ConcreteBaseType), implements(InterfaceType1,InterfaceType2) :: ConcreteType
contains
  procedure :: method1
  procedure :: method2
end type ConcreteType

So, one would obtain a two-tiered inheritance capability, one to enable polymorphism, and one to inherit implementations (if one so desires), the same way it works in Java. It is the lack of such a feature which is responsible for most of the "select type" downcasting non-sense that we currently have to contend with.

certik commented 4 years ago

@difference-scheme thanks for the feedback. We need your help:

it is incomprehensible why this is still not part of the language!

The reason it's not part of the language already is that nobody has put enough work to get it in. In order to get this done, we need to brainstorm and figure out a way to do this that will work and that we can agree upon, then write proposals for it, then discuss at the Committee and convince everybody, and several times (at several meetings) etc. Would you be interested in helping us with this?

The hardest part right now is to collect all the various proposals above, and figure out a proposal that we would all agree upon, and to drive the discussion and try to reach an agreement. To that aim, I think we have to have document where we discuss the pros and cons of all the proposals above, so that we can move the discussion forward. Your particular proposal in your comment seems to be a variation of several of the above proposals. So I think it's time we start to work on just one document and keep improving the various aspects of it.

difference-scheme commented 4 years ago

@certik Yes, I am willing to help with this, though I am only just a user and not an expert on languages. In case you've already started to write up some draft for a proposal, feel free to use anything that I've written up in my comment. I could then try to come up with some examples on how typical tasks have to be coded now, vs. how they would be coded with the feature in place, to illustrate the advantages.

I believe the main point to agree on first is whether we want such a feature to cover only run-time polymorphism for now, or both run-time and compile-time polymorphism. The former would make adoption much quicker and simpler, as there is very little risk involved, given that the same feature already works in other languages (Java, C#, etc.).

certik commented 4 years ago

Thanks. @tclune is leading the effort here, he might have some document already. Otherwise maybe somebody will find time to write it up. I want to write proposals for some other features first, before I get to this.

I believe the main point to agree on first is whether we want such a feature to cover only run-time polymorphism for now, or both run-time and compile-time polymorphism.

The proposal I had above would be only compile time polymorphism -- although as we discussed above, maybe it's both. Doing only runtime polymorphism with interfaces would be new, but one can "sort of" do it already with abstract classes, so there is a workaround. But Fortran currently does not have a compile time template / polymorphism.

everythingfunctional commented 4 years ago

I finally got around to testing it, and Fortran does do run time look up of functions for polymorphic variables. A procedure which accepts a class(Parent) and calls one of its procedures will call the child types procedure if it is passed as the actual argument. Even if it is passed as an allocatable variable of the parent type. So long as the actual value is of the child type, any calls to it's procedures will be to the child types procedures, even if they are made through a variable of the parent class.

I.e. given

module Poly_m
    use iso_varying_string, only: VARYING_STRING, assignment(=)

    implicit none
    private

    type, public :: Base_t
    contains
        private
        procedure, public, nopass :: greet => baseGreet
    end type Base_t

    type, public, extends(Base_t) :: Extended_t
    contains
        private
        procedure, public, nopass :: greet => extendedGreet
    end type Extended_t

    public :: fromGreeter
contains
    pure function baseGreet() result(greeting)
        type(VARYING_STRING) :: greeting

        greeting = "Hello"
    end function baseGreet

    pure function extendedGreet() result(greeting)
        type(VARYING_STRING) :: greeting

        greeting = "Howdy"
    end function extendedGreet

    pure function fromGreeter(greeter) result(greeting)
        class(Base_t), intent(in) :: greeter
        type(VARYING_STRING) :: greeting

        greeting = greeter%greet()
    end function fromGreeter
end module Poly_m

The following will print "Howdy"

class(Base_t), allocatable :: greeter
allocate(Extended_t :: greeter)
call put_line(fromGreeter(greeter))

This is why I think traits should be implemented as run time polymorphism. It doesn't stray far from the already existing concepts and underlying machinery of abstract and extends for inheritance, making it easier to implement, and easier for users to understand.

certik commented 4 years ago

@everythingfunctional ok, in that case I think this proposal is different to what we discussed at the Committee so far, as my understanding was that we were discussing compile time polymorphism / templates. I will try to create a separate issue for that, and we can use this issue for your original proposal, which is runtime polymorphism with traits.

difference-scheme commented 4 years ago

@everythingfunctional, @certik Great! I have started to write up a draft for a proposal along these lines (the preliminary title is: "Improved run-time polymorphism for Fortran"). EDIT: @certik Sorry, I think I misunderstood you. I presume now that you want to move your own (compile-time polymorphism) proposal into another Issue. So where can I put my proposal draft in case you want to contribute to the write-up or give feedback?

certik commented 4 years ago

@difference-scheme just create a PR with the proposal. Once we have the proposals written and we can see the differences between them, if two of them should be merged, then we can do it. Otherwise we'll have several different proposals and we can then discuss the pros and cons of each approach, which will move the discussion forward.

wclodius2 commented 3 years ago

FWIW in the example

module A
implicit none
private
public :: T

  type, requirements :: T
  contains
    generic :: operator(+) => plus
  end type

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs, rhs
      type(T) :: plus
    end function
  end interface

end module A

module A2
use A, only: T
implicit none
private
public :: f

contains

    type(T) function f(x)
    type(T), intent(in) :: x
    f = x + 1
    end function

end module A2

The interface should be:

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs
      integer, intent(in) :: rhs
      type(T) :: plus
    end function
  end interface

The type probably also needs an assignment interface for the "strong concepts" to be enforced, and would benefit from having an example instantiation, so a full example should probably be

module A
implicit none
private
public :: T

  type, requirements :: T
  contains
    generic :: operator(+) => plus
    generic :: assignment(=) => assign
  end type

  abstract interface
    function plus(lhs,rhs)
      type(T), intent(in) :: lhs
      integer, intent(in) :: rhs
      type(T) :: plus
    end function plus
  end interface

  abstract interface
    function assgn(lhs,rhs)
      type(T), intent(out) :: lhs
      type(T), intent(in) :: rhs
    end function assign
  end interface

end module A

module A2
use A, only: T
implicit none
private
public :: f

contains

    type(T) function f(x)
    type(T), intent(in) :: x
    f = x + 1
    end function

end module A2

program example
use A2
implicit none
real :: two
two = f(1.0)
end program example
brandongc commented 3 years ago

(Let me know if you think should be a different linked issue vs a comment on this one)

It would be great if the intrinsics such as matmul and dot_product would also take advantage of this and work with types provided the appropriate operators (*,+,=) and traits (e.g. "associative") are defined.

This would be particularly useful for working with a broad range of algebraic structures.