Concerns regarding limitations in the current generics proposal

@FortranFan thanks, good catch, I fixed it.

1 Like

That works for me. Feel free to send me a calendar invite, or let me know if you want me to send one.

1 Like

Yes, there absolutely is!! Please re-read the following quote from my previous post:

2 Likes

Perfect, thanks!

I don’t see an example of this in your examples. Can you give a Fortran code example (using your syntax) that shows a “type T generic over a type U should be able to have a type bound procedure that is generic over a type E which is independent of the type declaration” ?

From post #1:

module result_mod
    implicit none
    private
    public :: result_t

    type :: result_t<T, E>
        requirement
            type :: T; end type
            type :: E; end type
        end requirement

        type(T), allocatable :: value
        type(E), allocatable :: error
    contains
        procedure :: is_error
        procedure :: and_then
    end type

contains


    logical pure function is_error(this)
        class(result_t<T, E>), intent(in) :: this

        is_error = allocated(this%error)
    end function


    pure function and_then<U>(this, func) result(res)
        requirement
            type :: U; end type
        end requirement

        abstract interface
            type(U) pure function func_i(value)
                type(T), intent(in) :: value
            end function
        end interface

        class(result_t), intent(in) :: this
        procedure(func_i) :: func
        type(result_t<U, E>) :: res

        if (this%is_value()) then
            res%value = func(this%value)
        else
            res%error = this%error
        end if
    end function
end module

Refer back to the original post for my attempt at implementing this with the current proposal.

1 Like

Ah I see, thanks. At this point I think I would need you to walk me through it over a video. I understand the use case (I think we want it), but I would need to understand at the semantic level what exactly has to be changed (if anything). Obviously some syntactic changes are needed, but let’s not worry about the syntax at this initial point.

Great, let’s do that! It might be a good idea if @everythingfunctional joins us as well instead of having two meetings on this. Does 21. Nov 14:30 US Eastern work for you as well? I’ll message you both a link for a meeting, but we can change the time if necessary. If anyone else is interested in joining just let me know and I’ll message the link.

Thursday 17. Nov 14:30 US Eastern is one alternative option that works for me.

1 Like

That should work. Send us a calendar invite and we’ll go from there. If we can’t make it, we can move it.

1 Like

@plevold did you meet with the generics subgroup to discuss this? What is the current status? (I don’t recall receiving a calendar invite, if you sent it and I missed it, I apologize!)