Enhancements to allocatable arrays

Following some recent discussions ( REALLOCATABLE attribute, Is allocate a function or subroutine? - #6 by RonShepard ), some enhancements to the allocatable arrays could be proposed. The needs are (from simpler to more complex):

  • Allocating an array regardless its current allocation status. The current content would be lost. It would just be a shortcut to
    if (allocated(a)) deallocate(a)
    allocate(a(n))
  • Modifying the bounds without modifying the sizes; the content would be kept
  • Having something similar to C++ vectors, i.e. resizeable arrays while keeping the content, with an internal allocation strategy that reduces the needs of allocating new memory and copying the content

Briefly, how do C++ vectors work:

  • they are basically 1D arrays
  • there is a decoupling between the size and the capacity. The size is the usual concept, and the capacity is the amount of memory effectively allocated under the hood: capacity >= size. It allows some overprovisioning of memory, such that the size can grow without necessarily having to reallocate some memory.
  • a vector can be declared with or without an initial size.
  • v.resize(n) sets the size to n. If the capacity was less than n, then it is raised to n.
  • v.reserve(n) sets the capacity to max(n,v.size())

Note that no implicit overprovisioning happens at this point, just an explicit one with the reserve()method. Implicit overprovisioning happens with the methods that append or insert elements to/in the vector. for instance:

  • v.push_back(x) appends a scalar x to the vector:
    • the size is incremented by 1.
    • if the new size is <= the current capacity then the new element is just written in memory
    • if the new size is > the current capacity, then
      • the compiler allocates memory with twice the capacity
      • the content of the vector is copied to the new memory area
      • the new element is written in memory
      • the old memory area is deallocated

The capacity can be reduced only explicitly (with the reserve() or shrink_to_fit()methods), it is never implicitly reduced, even when downsizing the vector or when using methods that remove elements (e.g. pop_back())

(You can now directly jump to the post with the updated version of the proposal)

Reallocation regardless the allocated status

This could be achieved with a new realloc specifier. The content would be lost.

real, allocatable :: a(:)
...
allocate( a(n) )
...
allocate( a(m), realloc=.true.)

Or it could be the new standard behavior (it would not break the backward compatibilty; just, illegal code would be now legal)

Modifying the bounds

The sizes are not changed and the content is kept. No specifier at all is needed, one just have to specify one of the new bounds:

allocate( a(n) )
allocate( a(lb:) ) ! the new shape is lb:lb+n-1
allocate( a(:ub) ) ! the new shape is ub-n+1:ub

For rank > 1 arrays, using just : would mean no change for this dimension

allocate( a(n,m) )
allocate( a(:,lb:) ) ! the new shape is (1:n,lb:lb+n-1)

Resizeable arrays

Option 1

No new attribute is created, meaning that all allocatable arrays can potentially be resizable. Some new specifiers in allocate are needed to tackle all possibilities: resize=<logical>, capacity=<integer>, and cap=<character(*)>

allocate( a(n), resize=.true., [capacity=c | cap=cc])

  • if a was not allocated, performs a normal allocation, otherwise the array is resized while keeping the content (or a part of the content if the new size is smaller than the previous size)
  • the capacity and cap specifiers are mutually exclusive
  • cap=cc
    • cc=‘grow’ (default):
      • if (n <= current_capacity) then no reallocation occurs
      • if (n > current_capacity) then the new capacity is set to max(2*current_capacity,n)
    • cc=‘auto’: same than ‘grow’, with an additional rule:
      • if (2n < current_capacity) then the new capacity is set to min(2n,current_capacity/2)
    • cc=‘fit’: the new capacity is set to n. The following syntax is possible when one doesn’t want to change the size:
      `allocate( a(:), resize=.true., cap=‘fit’)
  • capacity=c
    • forces the capacity to max(c,n).
  • if the capacity changes, a reallocation+copy can occur; if the capacity does not change, no reallocation must occur.

Assignments:

  • the capacity of the rhs is transfered to the lhs if and only if allocation on assignment occurs
  • otherwise the lhs keeps its previous capacity

A typical use case of resizable arrays is when appending elements to an existing array:
a = [a, b] (b being a scalar or a rank 1 array)
However, an array constructor has no overprovisioned capacity according to the above rules, and consequently a has no overprovisioned capacity either after the assignement. Another specifier is actually needed if one wants some overprovisioning:
allocate( a(size(a)+size(b)), resize=.true., fill=b )
But a new statement/routine would actually be desirable:
append(a,b)
And similarly drop(a,k) as a shortcut to:
allocate( a(max(size(a)-k),0), resize=.true. )

allocate( a, resize=.true., mold=b )

  • a inherits the capacity from b, unless specified otherwise with capacity= or cap=

allocate( a, resize=.true., source=b )

  • does not make a lot of sense, as the whole purpose of resizable arrays is to keep the content. These two specifiers should be mutually exclusive, OR it should behave like a = b

Notes:

  • resize=.true. could be omitted is either capacity or cap are specified (or, resize could not be needed at all, and cap or capacity would trigger the resizable behavior).
  • instead of resize=.true. one may have a more general specifier mode=[''|'realloc'|'resize'], which would replace also the realloc=.true. specifier described above

Option 2

Resizabilty would be an essential property of the array, with a specific attribute:
real, resizable :: a(:)

Everything would work pretty much the same, except that the resize specifier is not needed at all (it is always implied).

Assignements:

  • the capacity is never transfered from the rhs to the lhs, as it is an essential property of an array, i.e.
    a = [a, b] is equivalent to allocate( a(size(a)+size(b)), fill=b ) (with cap='grow' as the default)

allocate( a, mold=b )

  • a does NOT inherit the capacity from b

allocate( a, source=b )

  • does not make a lot of sense, as the whole purpose of resizable arrays is to keep the content. This specifier should not be allowed for resizable arrays, OR it should behave like a = b

rank > 1 arrays

Everything would work pretty much the same, except that only the last dimension could be resized (except that all dimensions can be resized if the initial size is 0).

The capacity would refer to the size of the last dimension, not to the size of the whole array, e.g.:
allocate( a(n,m), resize=.true., capacity=m+2)
means that 2 columns are overprovisioned

fill specifier:

! a(:,:) is already allocated
m = size(a,2)
allocate( a(:,m+5), resize=.true., fill=b )
  • b can be a scalar or an array of the same TKR than a

append(a,b)

  • if r=rank(a), then the rank of b can be (r-1) or (r)

Are resizeable arrays needed?

Good question. Indeed, they can be simulated with a user-defined class (could be in the standard library). The coming generics feature may even makes this simpler. However this approach has (and will still have) some obvious limitations. Arrays are really 1st class objects in Fortran, so any enhancement to them looks desirable to me, as long as it doesn’t bloat the language (and I don’t think the above proposal bloats it).

6 Likes

I would add that this proposal makes Fortran even more interesting :grin:.

I’d say this is true, as long as the effort is kept on not needing this

It would make the whole proposal difficult to adopt for already running large code-bases.

You are already elucidating quite well how to make Option 1 workable and robust :slight_smile:

The second line looks like a very good design and as you mention in the previous line, it would make the resize option unnecessary. The rest of the mechanism can be worked out from the options.

1 Like

I would disagree somewhat with this narrow scope. The main purpose of resizable arrays is to avoid the overhead associated with actual memory allocation requests to the operating system. This can be (and is) done now when the programmer overallocates his work arrays, keeps track of the effective dimensions, and then always references those arrays as a(1:m), b(1:m,1:n), and so on where m and n are within the actual allocation bounds. In this kind of application, the array dimensions are decreased as often as they are increased. The important feature is to avoid the expensive actual memory allocation step.

Of course, it remains to be seen which type of application would be in most demand, but at least in my own programming, the above is what I do most of the time. If the compiler could help keep track of the currently active dimensions, and allow simple whole array operations on the leading subblocks, then it would make programming both easier and less error prone. The fact that the leading subblock remains intact when the dimensions are changed is simply a side effect, not the “whole purpose” of the feature. Many times, the user does not need to preserve the contents, he just needs the effective dimension to change, with as little computational overhead effort as possible.

1 Like

You’re right, I was too much focused on the “keep the content” feature and I missed that. I have to revise the whole stuff :smiley: !!

Edit: it can probably fit quite well in the realloc=.true. case (or mode='realloc')… Let me think about it.

New attempt to take into account @RonShepard objections. Actually it can make the whole thing more consistent. I am also retaining the option 1 only.


The needs:

  • Allocating an array regardless its current allocation status. The current content would be lost.
  • Modifying the bounds without modifying the sizes; the content would be kept
  • Having something similar to C++ vectors, i.e. resizeable arrays with or without keeping the content (note that in the C++ vector case, the content is always kept), with an internal allocation strategy that reduces the needs of allocating new memory and copying the content.

(just go back to the initial post for a short description of how C++ vectors work)

A few new specifiers in allocate could handle all these cases:

mode=<character(*)>
capacity=<integer>
cap=<character(*)>)

Reallocation

In short: one can reallocate an already allocated array (but this works also with an unallocated array). But under the hood the compiler allocates a new memory area only if needed (i.e. if the new requested size exceeds the current capacity), otherwise it simply recycles the already allocated memory and just updates the array metadata.

There’s no guarantee to retrieve the initial content after the reallocation.

In the rules below, an effective reallocation may occur each time the capacity changes (i.e. a pointer to the array may become undefined), and no effective reallocation must occur if the capacity doesn’t change (i.e. a pointer to the array remains defined)

allocate( a(n), mode='realloc', [capacity=c | cap=cc])

  • the capacity and cap specifiers are mutually exclusive
  • cap=cc
    • cc=‘grow’ (default):
      • if (n <= current_capacity) the capacity doesn’t change
      • if (n > current_capacity) then the new capacity is set to max(2*current_capacity,n)
    • cc=‘auto’: same as ‘grow’, with an additional rule:
      • if (2*n < current_capacity) then the new capacity is set to min(2*n,current_capacity/2)
    • cc=‘fit’: the new capacity is set to n.
  • capacity=c
    • forces the capacity to max(c,n).
  • The following syntax is possible when one doesn’t want to change the size but only to update the capacity:
    allocate( a(:), mode='realloc', [capacity=c | cap='fit'])

Assignment lhs = rhs:

  • the capacity of the rhs is transfered to the lhs if and only if allocation on assignment occurs
  • otherwise the lhs keeps its previous capacity

allocate( a, mode='realloc', [mold|source]=b )

  • a inherits the capacity from b, unless specified otherwise with capacity= or cap=

simply updating the bounds

n = size(a)
allocate( a(lb:), realloc=.true.) ! the new shape is (lb:lb+n-1)
allocate( a(:ub), realloc=.true.) ! the new shape is (ub-n+1:ub)

rank > 1 arrays

The above description can be extended to any rank without any restriction. The sizes of all the dimensions can be changed

allocate( a(lb:,n,:), mode=realloc )

  • the bounds are updated on the first dimension without changing the size
  • the new size of the second dimension is set to n
  • no change on the third dimension

Important change compared to the previous proposal:
The capacity is expressed in number of elements, regardless the rank and shape of the array : a capacity of 100 can host an rank-1 array up to 100 elements, a rank-2 array of 5x20 elements, but not a rank-2 array of 10x20 elements.

Resizing

The overall principle is the same than for the reallocation case, but the content is kept (or a part of the content if the new size is smaller)

allocate( a(n), mode='resize', [capacity=c | cap=cc])

Because the content is kept, comme restrictions apply:

allocate( a, mode='resize', source=b )

  • does not make sense, as the objective here is to keep the initial content. The source specifier should not be allowed
  • however, one may want to initialize the new elements of the array when increasing its size; a new extend= specifier would be needed

allocate( a(m), resize=.true., extend=s)

  • s is a scalar
  • equivalent to
    n = size(a)
    allocate( a(m), resize=.true. )
    a(n+1:m) = s

allocate( a, resize=.true., extend=b)

  • b is a rank 1 array
  • equivalent to
    n = size(a)
    allocate( a(n+size(b)), resize=.true. )
    a(n+1:m) = b

A typical use case of resizable arrays is when appending elements to an existing array:
a = [a, b] (b being a scalar or a rank 1 array)
However, an array constructor has no overprovisioned capacity according to the above rules, and consequently a has no overprovisioned capacity either after the assignement. The extend= specifier can be used:
allocate( a, resize=.true., extend=[b] ) or
allocate( a, resize=.true., extend=b )

But a new statement/routine could actually be desirable:
append(a,b)
And similarly drop(a,k) as a shortcut to:
allocate( a(max(size(a)-k),0), resize=.true. )

rank > 1 arrays

This is where the main restriction would apply compared to the mode='realloc' case: only the last dimension could be resized. For, resizing the other dimensions would force moving the existing content in all cases. Exceptions:

  • the array is not allocated
  • the size of the array is 0
  • the new size is 0
allocate( a(n1,n2,n3) ) ! all dimensions with a size > 0
...
allocate( a(:,:,n3+1), resize=.true. ) ! ok
allocate( a(n1+1,:,n3+1), resize=.true. ) ! illegal

In the extend=b specifier, b should be a scalar or an array of the same TKR than the array that is resized.

As mentioned earlier, the moving of existing content would only be required if the result must be contiguous. If the result is not required to be contiguous, then resizing a multidimensional array could leave the leading subbblock untouched and it would not require a memory copy. This is exactly how I now handle this resizing case in my own codes (where I manually overallocate, and keep track of the current working dimension).

Here is some pseudocode to demonstrate the diffference. Suppose the overallocated workspace looks like WORK(maxsize). Then for a 2D array the contiguous option would work like

real, pointer :: a(:,:)
...
sizea = max( 0, (ub1-lb1+1)*(ub2-lb2+1) )
a(lb1:ub1,lb2:ub2) => WORK(1:sizea)

I’m leaving out all of the size and extent checks, and just focusing on the memory layout. Of course, the pointer would need to be obscure, the programmer certainly would not want to introduce a new wild pointer to screw up optimization when this feature is used. With this convention, the result would always be contiguous, but leading 2D subblocks would need to be copied to remain intact, unless of course if the leading extents happen to be the same.

In contrast, the subblock approach would be implemented, using WORK(1:max1,1:max2), as

real, pointer :: a(:,:)
...
a(lb1:ub1,lb2:ub2) => WORK(1:ub1-lb1+1,1:ub2-lb2+1)

This result array is not contiguous, in the usual case, but the leading subblock is always untouched.

Thus there are two conventions that are incompatible with each other, 1) the result array is contiguous, or 2) the leading subblock of the result is always untouched. I think this should not be a compiler implementation option, it needs to be specified so that all compilers do the same thing. Maybe a new keyword would allow a compiler to provide both options to the programmer?

The most important feature for efficient reallocation is to avoid the malloc()/free() calls to the operating system. This can consume a huge number of machine cycles, especially if garbage collection is invoked during the call. Then the next most important feature is to avoid memory copies to retain the existing data (more important for large arrays then small arrays). This is a given for 1D arrays, and for multidimensional arrays, then can be done with the leading subblock convention. The importance of the other feature, contiguous multidimensional arrays, depends on the application. Sometimes it is critical for efficiency, sometimes it is irrelevant, and sometimes it is somewhere in between.

Allocatable arrays are efficient because they are contigous in memory. Any notion of discontiguity in them would break the whole purpose and it would become a re-invention of lists. If the compilers can find a way to allocate the next chunk of memory next to the existing one without any data transfer that would be the grail, but I don’t see how it could be done in the general case. So just one copy would be needed internally. From current array to a temp having the new sizes, then move_alloc( from=temp , to=array)

I stop you there :smiley: … I understand your point, but in the current standard allocatable arrays are required to be contiguous. And I’m not sure it would be a good idea to change that. So, a different attribute would be needed:
real, resizeable :: a(:,:)
But it could not be an actual argument for an allocatable dummy argument, and vice-versa.

In just one paragraph you already revealed the conflict!

That’s the source of the inefficiency in your description. The temp array that you require for the copy violates the most important efficiency feature.

You are proposing a one-size-fits-all solution to the reallocation problem. I’m proposing an alternative that, at least for a large number of applications, perhaps even the majority, might be more efficient because it avoids the malloc()/free() step.

Yes, I agree there are numerous other considerations, such as how these new reallocatable arrays can be used as dummy arguments and so on. Also we don’t want to end up with a parametrized data type kind of feature, that looks very good on paper but is so difficult to implement in compilers that it remains unusable even after several decades. But if one is concerned about efficiency, then I think the various alternatives that focus on efficiency should be considered.

Both of these conventions can be tested now. They are both simply ways to implement, in simpler, safer, and more convenient ways, things that can be done now with existing allocations, move_alloc(), and with array stride addressing. So maybe we should set up some test cases, implement both conventions, and see what are the tradeoffs!

I am proposing something that also avoids the malloc/free steps (not always, but as much as possible), but within the constraints of what allocatable objects are. And the contiguity constraint is critical: thinking a bit around it, I think it can not be relaxed without major issues (either breaking the backward compatibilty, or making the compilers unable to determine at compile time if an allocatable actual argument is contiguous or not).

So, if integrated in the language, your approach would require a new attribute and new rules to determine how “resizable” arrays interact with other arrayswhen used as arguments.

The elimination of malloc()/free() would also be critical to efficiency for this reallocatable proposal. I suggest putting together some test cases that actually measure now important each of these features are.

As for compile time and run time tests for contiguity, I think the tests themselves (which only involves a few integer comparisons of the metatdata) are cheap compared to everything else being discussed (malloc()/free(), temporary copies, etc.). Most array operations, either with array syntax or with intrinsics such as matmul(), sum(), etc. do not currently require contiguous arguments. Contiguous arguments are mostly required for C interop (due to limitations of the C language compared to fortran) or with legacy codes (f77 style assumed-size and explicit-shape dummy arguments, etc.). While those are important in a practical sense (and we must already deal with those situations now), should the features of future fortran be held captive for these reasons?

This reallocation feature is going to be a major change. Just look at the complications already in the proposal in this discussion thread. Is there really a need to make a half-baked change, when, with just a little more effort and forethought, the programmer could control which features the allocatable arrays can possess based on the application needs at hand.

I would say that more than a conflict it is a matter of choice:

  • Do I need a structure that guarantees contiguity for the sake of everything I’ll do afterwards with it? allocatable arrays are the choice

  • Do I need a structure that enables flexible resizing for the current processing? Something like a linked list would be the choice

There is always a tradeoff to pay.

Regarding this discussion I’m more concerned about the first point and giving allocatable arrays a push forward for dynamic memory management.

In this regard, the malloc()/free() internal steps would be the price to pay, but they are way overpaid by everything that is gained afterwards. The kind of arrays I’m describing here have the purpose of existing during long scopes, usually the scope of the whole program execution, and not the scope of a single procedure.

Since avoiding the malloc()/free() steps are paramount for the second kind of use cases, then yes, a new attribute would be required, I would suggest something like

real, list :: x(:) 
!> or as proposed previously
real, resizable :: x(:) !> the first one seems more explicit in the sense that it is a new entity

But in this regard, it would be a completely new kind of entity, not guaranteeing contiguity.

@RonShepard

You are missing the main point, which is the fact that the standard currently requires contiguity for the allocacatable arrays. So the compiler knows for instance that such a call never requires a copy-in/copy-out:

real, allocatable :: a(:,:)
<some code>
call foo(a)
...
subroutine foo(x)
   real, contiguous :: x(:,:)

So, if the conguitity enforcement is removed for allocatables it will have negative consequences. Actually it will even break the backward compatibility:

implicit none
real, allocatable, target :: a(:,:)
real, pointer :: p(:)
allocate( a(100,100) )
p(1:200) => a
end

The above code is valid because a is guaranteed to be contiguous. If the contiguity constraint was removed, this code would become invalid.

So, your wishes requires something else than allocatable, such as a resizable attribute. Why not, but you have to make it clear.

Ok, so here is a small test code that compares timings for the two conventions.

program compare
   ! compare subblock operation with contiguous reallocation.
   implicit none
   integer, parameter :: wp = selected_real_kind(14), n=2000
   character(*), parameter :: cfmt='(a,es9.3,a)'
   real(wp) :: cpu0, cpu1
   call cpu_time(cpu0)
   call subblock()
   call cpu_time(cpu1)
   write(*,cfmt) 'subblock time = ', cpu1-cpu0,' seconds'
   call cpu_time(cpu0)
   call contiguous()
   call cpu_time(cpu1)
   write(*,cfmt) 'contiguous time = ', cpu1-cpu0,' seconds'
contains
   subroutine subblock()
      ! allocate arrays to the max size and work with subblocks.
      real(wp), allocatable :: a(:,:), b(:,:), c(:,:)
      integer :: k
      allocate( a(n,n), b(n,n), c(n,n) )
      call random_number( a )
      call random_number( b )
      do k = n, 1, -1
         c(1:k,1:k) = a(1:k,1:k) + b(1:k,1:k)
      enddo
      return
   end subroutine subblock
   subroutine contiguous()
      ! reallocate contiguous arrays while keeping the leading subblock.
      real(wp), allocatable :: a(:,:), b(:,:), c(:,:)
      integer :: k
      allocate( a(n,n), b(n,n), c(n,n) )
      call random_number( a )
      call random_number( b )
      do k = n, 1, -1
         call reallocate( a, k )
         call reallocate( b, k )
         call reallocate( c, k )
         c = a + b
      enddo
      return
   end subroutine contiguous
   subroutine reallocate( x, n )
      ! conditional reallocation, save the leading subblock.
      real(wp), intent(inout), allocatable :: x(:,:) ! array to be reallocated.
      integer, intent(in) :: n  ! new dimension.
      real(wp), allocatable :: tmp(:,:)
      if ( size(x,dim=1) == n ) return   ! quick return.
      tmp = x(1:n,1:n)                   ! save the leading subblock.
      call move_alloc( from=tmp, to=x )  ! shallow copy.
      return
   end subroutine reallocate
end program compare

$ nagfor -O compare.f90 && a.out
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7114
[NAG Fortran Compiler normal termination]
subblock time = 1.468E+00 seconds
contiguous time = 1.174E+01 seconds

This shows that the subblock convention is about 6x faster than the contiguous convention for these compiler options and for this value of n. Smaller values of n show smaller differences, and larger values show larger differences. I picked a value that resulted in timings between 1 and 10 seconds so that timing noise would be small.

I do agree that linked lists and other data structures are often the best choice when resizing is required. However, a linked list would not be appropriate for the type of array operations that occur in the above code, which is typical for the way we write programs now (i.e. with overallocation and array stride syntax).

Yes, there would be cases where copy-in/copy-out is required, just as there are now. I mentioned some of these cases previously (e.g. explicit shape and assumed size dummy arguments). However, there would be no backward compatibility issues because all code that now uses contiguous allocatable arrays will continue to be contiguous. These new proposals would be for the new allocatable arrays that have been overallocated and/or reallocated with the noncontiguous option. Of course, if they are reallocated with the contiguous option, then there would be no backwards compatibility problems. Also, if the reallocation only changes the extent of the last dimension, then the new array would remain contiguous. I am not proposing that the subblock convention is the only one provided by the compiler, I think it would be best if the programmer can choose. For example, if the programmer knows that the array would trigger copy-in/copy-out with some routine that requires contiguous arrays, then he might as well use the contiguous convention (pay me now, or pay me multiple times later). But if he is only going to associate the array with assumed shape dummy arguments (which do accommodate noncontiguous arguments), then he can choose the subblock option and his code will run 6x faster. If the programmer only needs to change the array extents, and he does need to save the previous data (which is a common situation), then the contiguous convention could be used with no malloc()/free() overhead.

I think this is what you want to do:

real(wp), allocatable, target :: a(:,:), b(:,:), c(:,:)
real(wp), pointer :: pa(:,:), pb(:,:), pc(:,:)
integer :: k
allocate( a(n,n), b(n,n), c(n,n) )
call random_number( a )
call random_number( b )
do k = n, 1, -1
  pa => a(1:k,1:k); pb => b(1:k,1:k); pc => c(1:k,1:k)
  pc = pa + pb
enddo
return

Not only “just as they are now”, but also “more often than now”. This is maybe acceptable, but it should not be ignored.

That’s not true: I’ve shown a code snippet that would break.

…and above all, for this code. You are performing only a single and quite simple operation on the arrays, interleaved with repeated reallocations, so this benchmark is not surprising.

But I think there is a misunderstanding from the start. From what you have posted overall, I actually understand that you want to fully get rid of the malloc/free, apart from an initial one. You want to overallocate a big array, then work on varying size subarrays in this big array. Am I correct ? If yes, I fairly think that no new feature is really needed in the language, as working on array slices is already straightforward.

My proposal rather addresses the cases where one doesn’t know in advance the maximum size that is needed, and/or where one doesn’t want to overallocate too much memory for the whole program execution. Additional malloc/free are not completely avoided, but their occurrences can be dramatically reduced with an appropriate strategy.

This is a different way of doing the noncontiguous subblock addressing. These pointer arrays are not contiguous.

This is correct, but this is the tradeoff that we are discussing, right? Noncontiguous subblock vs. contiguous arrays with reallocation.

It is correct that if you expend more effort working with the arrays for each allocation, then the allocation costs are amortized, but the underlying difference in the two approaches remain the same.

Yes, this was the point of my posts. You were looking only at that one narrow use case, while I think the proposal should consider also these other more common situations that involve frequent reallocations.

So far, what I have understood, and seems like @PierU understood the same thing as well, is that you want to have some extra syntactic sugar to handle in a compact manner sub-slices of memory as if they were a compact array… pointers give you exactly what you need, you can also call a procedure on a slice of the array, and from within handle it as whole memory region. It wont be contigous but you would have constant strides to help with the performance of memory acces…

The whole point of this proposal/thread is not about memory acces… is about resizing/reshaping the actual physical memory space allocated for the current data structure. This discussion is striving for an efficient management of memory allocation/reallocation … not about how to view_as the same region differently.

Yes and no. It is granted that my proposal is pointless in the cases where a reallocation is needed each time the apparent size changes. In such cases, working directly on array slices (possibly via some pointers) is clearly the way to go IMO.

The situation you are describing is indeed beyond the scope of my proposal, which closely remains within the framework of what allocatable objects are (in particular no new attribute is needed).

But feel free to propose something (based on my proposal or not) that would fit your needs.