Index access to user type

I have a very basic user type that holds an array

    type vector
        integer :: size
        real(wp), allocatable :: data(:)
    contains    
        procedure :: write_vector
        generic :: write(formatted) => write_vector
    end type vector

with a whole bunch of interfaces and operators defined to handle the math

but to actually access an element of the vector in a profgram I have to write something like a%data(i)

Is there a way to define index accessors for user types where

a(i) =>  a%data(i)

and even better for range objects

a(1:n) =>  a%data(1:n)

Other languages allow you to define indexers to emulate array behavior for not native arrays, and I was wondering if Fortran has a similar mechanism.


My goal to make the data component private, but it seems silly to create an accessor function

    pure function vec_item(a,i) result(x)
    real(wp) :: x
    class(vector), intent(in) :: a
    integer, intent(in) :: i
        x = a%data(i)
    end function

to be used as a%item(i) . Besides I loose the ability to vectorize expressions since I cannot do a%item(:).

PS. I do have assignment (=) operations defined so i can copy data from my type(vector) :: v and an array real(wp), dimension(:,:) :: arr with just an assignment arr = v.

The best you can do is write an association of a new name (the “associating entity”, x and s in the example) to an existing entity (the “selector”, a%data and a%size in the example) and then use that new name in a block of code.

  associate (x =>a%data,s=>a%size)
     print *,x(1),x(4:1:-2),x(:), s
  end associate

Array-ness is not part of the type of a Fortran object, it is an attribute. I think there’s been a deliberate choice not to go down the route of making expressions very difficult to make sense of (even if they could be made unambiguous).

Indeed, you can’t have a generic accessor (I also hited that wall) but @themos 's suggestion is a pretty good one. The association is done at compile time, so no overhead at run time.

A second approach would be to add the target attribute to the allocatable array. Then, whenever you need to loop on it, declare a pointer to point on the whole or a section of the array.

1 Like

I’m just curious why one would want to do this? Is this part of a contest to write obscure code?

The first time I saw this concept was in early 90s, with the IBM/NAG Scratchpad/AXIOM system (strongly typed, parametrised types, efficiency prioritised, functions first-class objects). The syntax

A ( B )

, or even

A B

would have a meaning whether A was a Mapping (function) type or not. If not, then it was taken as syntactic sugar for

elt(A, B)

and a generic Array(S) type (in the Library) provided an elt function

elt : (Array S, Integer) → S

Very powerful, but in the hands of non-experts a bit of a bear-trap. It survives today in the Fricas system and the Aldor compiler. I think it is fair to say that the expectations of efficient code generation were only partially fulfilled.

1 Like

It would actually be a useful feature for simulating and smoothly using various data structures that are not part of the langage itself.

1 Like

Some immediate examples come to mind:

  • To implement jagged arrays, and hence triangular matrices with minimal storage.

  • To implement sparse vectors/ matrices

  • To associate specific code to any size array, to be part of an existing library of fixed-sized arrays (vector2, vector3) with uniform interfaces for linear algebra.

I tried that, but with the following error

mod_vectors.f90(25): error #6516: 
This attribute specification is not valid for a component definition statement.   [TARGET]

and the full type specification:

    type vector
        integer :: size
        real(wp), allocatable, target :: data(:)    !!! <=error
    contains    
        procedure :: item => vec_item, vec_items
        procedure :: write_vector
        generic :: write(formatted) => write_vector
    end type vector

You cannot add the target attribute to a (derived) type, it is an attribute of a variable:

type(vector), target :: myvector

The syntax shoud be

    type vector
        integer :: size
        real(wp), allocatable :: data(:) 
    contains    
        procedure :: item => vec_item, vec_items
        procedure :: write_vector
        generic :: write(formatted) => write_vector
    end type vector

   type(vector), target :: myvector
   real(wp), pointer :: p(:)
   !...
   !...
   p => myvector%data

data should be allocated, and the pointer should be reassigned each time data is reallocated.

I generally find the associate( p => myvector%data ) solution more elegant. Not only it doesn’t require p to be declared, but the underlying mechanism is different from the one with the pointer, despite the similarities: p is more like a dummy argument of a virtual subroutine. The restrictions are the same as with the pointer solution, though.

1 Like

Sorry about that one, @PierU 's code is the proper way to do it

Yes, this is already part of the language, and it is a nice feature. But to match with the original request, the associate variable would need to be the same name as its target:

associate( myvector => myvector%data

Within the associate block, both the associate variable myvector and the derived type myvector would be in scope. How is the compiler, or a human, supposed to know which entity is being accessed? As I said before, this looks to me to be mostly just a recipe for writing obscure source code.

Nope.The associate name has precedence in such a case, and it shadows the initial variable within the block. Meaning that myvector%data is not recognized for instance. Much like any local variable shadows any global variable with the same name.

1 Like

You are right! I thought this simply was not allowed. Nonetheless, this still seems like an efficient way to write obscure code that would confuse a human reader, even if the compiler knows how to keep it straight.

Proposed here: Overloading () · Issue #119 · j3-fortran/fortran_proposals · GitHub

2 Likes