Error: The leftmost part-ref in a data-ref cannot be a function reference

Is there any notable benefit of postfix chaining to the more classic and arguably clearer “functional” alternative?

module num_m
    implicit none
    private
    public :: NumT, root, squared
    type :: NumT
        real :: x
    end type
contains
    function squared(T)
        type(NumT), intent(in) :: T
        type(NumT) :: squared
        squared % x = (T % x)**2
    end function
    function root(T)
        type(NumT), intent(in) :: T
        type(NumT) :: root
        root % x = sqrt(T % x)
    end function
end module

program test
    use num_m
    implicit none
    print *, NumT(x=10)
    print *, root(squared(NumT(x=10)))
end program

Edit: in this example I’d be compelled to use the standard names, why force the user to learn use %squared() and %root(), when ** and sqrt are known to everyone:

module num_m
    implicit none
    private
    public :: NumT
    public :: operator(**)
    public :: sqrt
    
    type :: NumT
        real :: x
    end type
    interface operator(**)
        module procedure NumT_pow
    end interface
    interface sqrt
        module procedure NumT_sqrt
    end interface
contains
    function NumT_pow(T,p) result(Y)
        type(NumT), intent(in) :: T
        integer, intent(in) :: p 
        type(NumT) :: Y
        Y = NumT(T%x**p)
    end function
    function NumT_sqrt(T) result(Y)
        type(NumT), intent(in) :: T
        type(NumT) :: Y
        Y = NumT(sqrt(T%x))
    end function
end module

program test
    use num_m
    implicit none
    print *, sqrt(NumT(10)**2)
end program

This would be in line with C++ core guideline C.162:

C.162: Overload operations that are roughly equivalent

Having different names for logically equivalent operations on different argument types is confusing, leads to encoding type information in function names, and inhibits generic programming.

2 Likes