j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
178 stars 15 forks source link

Overloading () #119

Open jacobwilliams opened 4 years ago

jacobwilliams commented 4 years ago

I haven't fully thought this through yet, but what if we had the ability to overload () for a derived type in various contexts? That could be used for some interesting things.

Such as dictionaries:

type(dict) :: d
d('key') = 1
d(1995) = 'string'

or a string class:

type(string) :: s
s = 'hello world'
write(*,*) s(1:5)   ! this writes 'hello'
nncarlson commented 4 years ago

I'm not so sure about such expressions as the lhs of an assignment (and actually I'm not sure what "1:5" would mean as an argument), but I've often wished for this to improve readability/expressiveness. For example, I currently have stuff similar to this

type, abstract :: func
contains
  procedure(eval) , deferred :: eval
end type
abstract interface
  real function eval(this, x)
    import func
    real, intent(in) :: x
  end function
end interface
class(func) :: f
a =  f%eval(0.0)

It would be much clearer imo to be able to write f(0.0). This just syntactic sugar I think, so I wouldn't expect it to be difficult to implement.

gronki commented 4 years ago

Unless a strong use case is presented, I would personally oppose. Fortran is not C++. It already has arrays. If someone wants to build an object wrapper around an array, or implement string as a derived type (as opposed to intrinsic implementation) I suggest using C++ as a better suited language.

Dictionaries, strings and arrays should be built into language.

pt., 20 gru 2019 o 16:30 Neil Carlson notifications@github.com napisał(a):

I'm not so sure about such expressions as the lhs of an assignment (and actually I'm not sure what "1:5" would mean as an argument), but I've often wished for this to improve readability/expressiveness. For example, I currently have stuff similar to this

type, abstract :: funccontains procedure(eval) , deferred :: eval end type abstract interface real function eval(this, x) import func real, intent(in) :: x end function end interface class(func) :: f a = f%eval(0.0)

It would be much clearer imo to be able to write f(0.0). This just syntactic sugar I think, so I wouldn't expect it to be difficult to implement.

— 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/119?email_source=notifications&email_token=AC4NA3I5DFQSTWWBXYILQK3QZTQI5A5CNFSM4J5X4262YY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEHNHFFA#issuecomment-567964308, or unsubscribe https://github.com/notifications/unsubscribe-auth/AC4NA3MP2DRZ245AULZYMW3QZTQI5ANCNFSM4J5X426Q .

cmacmackin commented 4 years ago

I think this could be useful, but we would need to separate function calls from indexing. Function calls would be trivial enough to define. Something like the following:

module example
type :: callable
contains
    procedure :: called_proc
    generic :: operator(()) => called_proc
end type callable

contains

real function called_proc(self, arg1, arg2, arg3)
    class(callable), intent(in) :: self
    integer, intent(in) :: arg1, arg2
    real, intent(in) :: arg3
    called_proc = arg3 ** (arg1 + arg2)
end function called_proc

end module example

The procedure that is called could be any function or subroutine which is valid as a type-bound procedure.

Indexing could be implemented in a similar manner, but would need some way to distinguish itself. Leaving that issue aside for the moment, we could do the following:

module example2
type :: indexed
contains
    procedure :: index_proc
    generic :: operator(()) => index_proc
end type indexed

contains

real function index_proc(self, arg1, arg2, arg3)
    class(indexed), intent(in) :: self
    integer, intent(in) :: arg1, arg2, arg3
    called_proc = arg3 ** (arg1 + arg2)
end function index_proc

end module example2

The functionn called for indexing would need to accept scalar integer arguments of intent(in) and return a scalar result. The compiler could then handle "array-slicing" as though the function were elemental (perhaps require it to be declared as such?) and were passed an array of integers corresponding to the slices.

The issue becomes how to distinguish between these two distinct use cases. Some different approaches:

Personally, I think the first of these makes the most sense.

cmacmackin commented 4 years ago

Unless a strong use case is presented, I would personally oppose. Fortran is not C++. It already has arrays. If someone wants to build an object wrapper around an array, or implement string as a derived type (as opposed to intrinsic implementation) I suggest using C++ as a better suited language. Dictionaries, strings and arrays should be built into language.

Well, the fact of the matter is that these aren't built in and I can see this operator being accepted more quickly than such a standard template library being approved and implemented.

A use-case I could potentially see for overloaded indexing would be for handling non-rectangular or periodic grids. Potentially unstructured meshes too, maybe?

A use case for overloading procedure-calling would be to allow functors and something closer to closures or lambda functions (although I'd also be quite happy to see the latter properly implemented within the language).

klausler commented 4 years ago

This is just syntactic sugar for a type-bound function that could return a pointer, yes?

jacobwilliams commented 4 years ago

@klausler For the LHS case, maybe ... or maybe some additional kind of assignment operator?

@gronki @cmacmackin Right, we don't have strings, and I'm not that optimistic that we will ever have them. So, give us this, and we can write our own string class in the proposed standard library. No matter how amazing a string class we can write now, it will always be clunky since to use the slice notation, we have to expose the underling character string:

This would be amazing:

type(string) :: s1, s2, s3
...
s3 = s1(1:2) // s(10:20)

This is not amazing:

type(string) :: s1, s2, s3
...
s3 = s1%str(1:2) // s%str(10:20)
cmacmackin commented 4 years ago

@klausler the issue with returning pointers is it requires that whatever is being pointed to is a valid target. Currently derived type components can not have the target attribute, meaning they'd have to be pointers with all the associated hassle of memory management. Hopefully that restriction can be removed (see #28 ).

ivan-pi commented 4 years ago

I have wished to have this several times. An equivalent feature of Python is the ability to overload the __call__ method.

I like the idea of @cmacmackin to have attributes for callable and indexable. A quadratic function could be built then as:

module quadratic_mod
type, public :: quadratic
   real :: a, b, c 
contains
    procedure, callable :: eval
    generic :: operator(()) => eval
end type 
contains
real function eval(this,x)
class(quadratic),intent(in) :: this
real,intent(in) :: x
eval = this%a+x*(this%b+x*this%c)
end function
end module

program main
use quadratic_mod
type(quadratic) :: f = quadratic(1.0,2.0,3.0) ! 1 + 2*x + 3*x**2
real :: y
y = f(x)
end program

What I wonder is, whether such a functors could then be passed on to some other routine, e.g. a numerical integration routine with a fixed interface such as:

abstract interface
   real function f(x)
       real, intent(in) :: x
   end function
end interface
function integrate(a,b,f)
real, intent(in) :: a, b
procedure(func) :: f
...
end funcion

without having to rely upon an adaptor class/module.

pbrady commented 4 years ago

I believe this is the same as #44 (and maybe #45). I'll close those since there's no discussion there

certik commented 4 years ago

Thanks @pbrady I thought you already opened some issues for this, but I couldn't find it.

septcolor commented 4 years ago

@nncarlson It's interesting that I use the same pattern for creating potential energy functions, i.e. a function object (derived from an abstract one) that is given system-specific data + potential routines. An appealing point of this approach (to me) is that each function object has its own data internally.

One use case might be to pass such a function object (with an overloaded ()) to generics that can accept both procedures and functors. For example, "callablle(func) :: f" instead of "procedure(func) :: f"...?

(But I also feel that this kind of thing could make the learning cost of Fortran higher, so care may be necessary to keep the syntax relatively straightforward...)

veryreverie commented 3 years ago

I think that there are two independent proposals here, which I would separate as:

  1. Function objects, i.e. types which overload the () operator, probably using operator(()) syntax. Ideally these objects would also be useable in procedure(func) contexts.
  2. Overloadable array slice syntax. i.e. allowing user-defined procedures to take a:b:c slices as arguments. This could possibly be done by definining an intrinsic type slice with components %first, %last and %stride

I think both proposals would make the language more intuitive, but I think the two should be evaluated separately, on their own merits. If both were implemented, I see no reason to limit the slice syntax to only be useable with the function object syntax.

perazz commented 2 years ago

I'm bringing back this discussion following what's been under discussion here.

I think having an accessor operator would be a very useful way to enable derived types/classes to be treated like arrays. The points for having it should be that all functions operating on arrays should also have validity on derived types with the accessor operator.

Here's one simple example I have in mind:

type :: symmetric_matrix
   integer, len :: n
   real :: data((n**2+n)/2)

   contains

   ! This should be pure and elemental OR pointer
   procedure, private, pass(this) :: sym_access

   ! The accessor needs something to define its dimensions
   generic :: accessor(:,:) => sym_access

end type symmetric_matrix

contains

! Point to symmetric data
elemental integer function sym_ptr(this,i,j) result(ptr)
   class(symmetric_matrix), intent(in) :: this
   integer, intent(in) :: i,j

   integer :: row,col,ptr

   row = merge(i,j,i>=j)
   col = merge(j,i,i>=j)

   ! Get pointer to data
   ptr = this%n*(col-1)-((col-1)*(col-2))/2 + (row-col+1)

end function sym_ptr

elemental real function sym_access(this,i,j) result(aij)
   class(symmetric_matrix), intent(in) :: this
   integer, intent(in) :: i,j

   integer :: ptr

   ptr = sym_ptr(this,i,j)
   aij = this%data(ptr) 
end function sym_access

! pointer version
function sym_access(this,i,j) result(aij)
   class(symmetric_matrix), intent(in) :: this
   integer, intent(in) :: i,j
   real, pointer :: aij
   integer :: ptr

  if (i>=1 .and. j>=1) then 
    ptr = sym_ptr(this,i,j)
    aij => this%data(ptr) 
  else
    nullify(aij)
 endif
end function sym_access

I haven't thought about all the implications on sliced array indexing/ stride/etc. but if there's an elemental way to compute that, maybe it's straightforward.

Actually, a compiler may like more the pointer version for its' ability to return null and hence catch out-of-bounds access, or maybe not.

My two cents, Federico

perazz commented 2 years ago

On the usage standpoint, imagine all array-based syntax to be enabled by that, like:

forall(i=1:N,j=1:N,j<=i) sym_mat(i,j) = blabla

! array-like dimensions to work on are specified by the accessor interface
sum(sym_mat,2)
sum(sym_mat,1)

etc.

ivan-pi commented 1 year ago

@perazz, you should be able to get a nice symmetric matrix syntax with the new features in C++23 such as the multidimensional operator[] and the mdspan container view. The LayoutPolicy and AccesorPolicy can be used to implement a symmetric matrix. More in the article mdspan in C++.