Improving `memory` with better abstractions

I’ve long been of the mind that memory needs to be improved. Due to concern about the library itself, it may be an opportune time to examine this library, and consider what we can do to improve it. Haskell has done a great job of pollenating other languages with concepts, and I have spent some time recently doing a lot of C, with some dabbling in Rust and Zig, all with a focus on memory management, allocators, alignment, and other dark arts that often left to the compiler in functional languages.

I think it is actively harmful to the community and to the language to consider such things as ‘beneath us’, since these things are usually considered an implementation detail that should never be visible. But think of what could be done with explicit control over allocators - what if we had a HasAllocator like we have HasCallstack? What if we could actually run a given function with a different allocator, and could guarantee immediate memory cleanup when it was done? Zig passes allocators explicitly, we have many options to hide them away as implicit arguments or behind monads. I think there is something to be learned, and brought back to Haskell - doubly so the rise of alternative compilers such as MicroHs, and the desire to compile efficiently for more architectures like embedded systems and WebAssembly.

To that end I have extracted the public API of memory for assessment and it consists of some 170-ish functions, classes, data types, and constructors. Not a small surface, to be sure, but not an insurmountable foe. Of course, this does not include the implementation code, which is another beast altogether - so we should take the time to seek to understand why certain things were implemented so. Also, some time ago I did a reverse dependency search to see how memory is actually being used (its here in some thread somewhere) and it turned out that a majority of use cases were limited to the same code - the ByteArray/Access class, the typely-sized variant ByteArrayN/SizedByteArray, and base encoding functions.

Anyway, lets get started.

The first thing worth considering is that the main class hierarchy - the ByteArrayAccess and ByteArray classes - are badly named, and do not properly separate their concerns anway. ByteArrayAccess is an unwieldy name and is implicitly mutable, and ByteArray is actually concerned with allocations. One could argue that ByteArrayAccess is about accessing the length and pointer of an array of bytes, but then we should just call it ByteArray and change the other class to Allocator. But ByteArray/Access doesn’t allocate / give you access to a byte array, it gives you an arbitrarily typed pointer of least length bytes in size - but a pointer and an array are not the same thing, nor is the implicit presumption of a byte-addressable architecture necessarily a good one to make. It is also troublesome that one can allocate a ‘byte array’ using a Ptr Word64 but still have to describe its size in bytes. This just screams potential for unchecked exceptions and alignment problems, it again mixes or refuses to differentiate pointers vs arrays, and ignores the size information that the pointer’s type provides.

I could go on; about the only thing going for it is that these classes are then used to implement a generic ByteString-like interface for all instances ByteArray - yippee! That is actually very nice, (and explains the stupid naming convention), except we’ve voluntarily loaded a footgun by conflating pointers with arrays while simultaneously measuring in bytes instead of element count. In short, memory made literally the exact same mistakes that C’s stdlib made (no surprise since that was deliberate mirroring), and it makes a pale comparison to Rust and Zig’s more modern memory and allocation tooling, let alone attempting to describe allocating a striped GPU vertex attribute buffer, or a non-traditional computing basis such as analog values and qubits. It is precisely these shortcomings that I wish to fix.

I have the violent opinion that one should only allocate memory in bytes when one is allocating an array of bytes (because it has that many bytes) OR as a void pointer (but only for a byte-addressable system). If we are allocating a pointer for a known type, we should use its size. I am also of the opinion that we should separate singular allocations from arrays and allocate using element count. The presumption of a byte-addressable architecture is also a problem - what of bit-addressable or word-addressible architectures? For a package that is supposedly about memory, it does a terrible job of it - for one, a memory package that doesn’t provide any allocators?

Enough ranting, can we do better? I think the first thing to do is re-work these core typeclasses - the rest of the library is actually mostly a grab-bag of low-level tools, so we can worry about that later.

Here is what I am throwing around as an alternative interface:

class (Monad m) => Allocator m alloc where

    -- The memory type being allocated
    type Memory alloc
    -- The memory layout, such as element count and alignment, or even GPU vertex attribute layout
    type Layout alloc

    allocate :: alloc -> Layout alloc -> m (Memory alloc)
    reallocate :: alloc -> Memory alloc -> Maybe (Layout alloc) -> Layout alloc -> m (Memory alloc)
    deallocate :: alloc -> Memory alloc -> Maybe (Layout alloc) -> m ()

class (Allocator m alloc) => MonadAllocator m alloc where
    getAllocator :: m alloc

NOTE: memory restricts its operations to IO, probably to limit implementation complexity as well as the number of dependencies. It might be worth lifting this restriction. We can otherwise also consider an IOAllocator class that is fixed / specialized to IO.

This allows for shenanigans to hide the allocator, such as:

allocateM
    :: forall m alloc . (MonadAllocator m alloc)
    => Layout alloc -> m (Memory alloc)
allocateM layout = do
    alloc <- getAllocator @m @alloc
    allocate alloc layout

And we can implement an allocator for base:Data.Array.Byte.ByteArray

data ByteArrayAllocator = ByteArrayAllocator

instance Allocator IO ByteArrayAllocator where

    type Memory ByteArrayAllocator = ByteArray.MutableByteArray RealWorld

    type Layout ByteArrayAllocator = ByteArrayLayout
        { layoutSize :: Size
        , layoutAlign :: Align
        }
    -- NOTE: Null layout is 0,1 not 0,0
    -- It contains the additive identity (size) and multiplicative identity (align)
    -- This might be better described as the identity layout?
    -- > A memory layout (for a pointer) consists of a size and an alignment, which
    -- > presents the question: what is the identity / null layout?
    -- > If we actually consider this, the natural answer is 0,1 where 0 is the
    -- > additive identity (0 size) and 1 is the multiplicative identity (1 align
    -- > aka any alignment) - in other words, the layout identity is the product of
    -- > the additive and multiplicative identity
    
    allocate _ layout = ByteArray.newAlignedPinnedByteArray (layoutSize layout) (layoutAlign layout)

    reallocate _ ptr _ layout =  ByteArray.resizeMutableByteArray ptr (layoutSize layout)

    -- | Deallocating a ByteArray is a no-op since we rely on lazy gc >:(
    deallocate _ _ _ = return ()

instance MonadAllocator IO ByteArrayAllocator where
    getAllocator = return ByteArrayAllocator

And we could do the same for a C stdlib allocator, but I’ve run out of time. We’ll pick this up later - until then, thoughts?

13 Likes

I like the general idea, but this specific type class seems overly generic in a bad way. The alloc function now basically has the signature a -> b -> m c which says almost nothing.

To define a good interface, I think we need some meaningful properties that these memory, layout, and allocator types follow. Or we could consider the denotation directly. For example, is Memory alloc equivalent to a function Layout alloc -> Byte (probably not but this is just to give some direction)?

If you reject that pointers and arrays are the same thing, then you should also reject that pointers can have a size.

Then surely the element type needs to be mentioned in the signatures of the class methods. For example, I would expect something more like: allocate :: alloc -> Layout alloc a -> m (Memory alloc a).

This allows for shenanigans to hide the allocator, such as:

But that requires using AllowAmbiguousTypes in (I think) a bad way; in the sense that you will need to use type applications whenever you want to use this function. Do we really need to pass the allocator explicitly? My intuition would be to hide it by default as part of the monad (e.g. as ReaderT alloc m).

2 Likes

I have no particular opinion on how control over allocators should look like — but I would like to mention that control over memory allocation is a design choice, not a value judgment. It’s a trade-off: I can spend my time thinking about how memory is laid out, and perhaps gain some performance improvements out of that, or I can spend my time focusing on functionality and algorithm complexity at a modest performance penalty. In all but exceptional circumstances, I prefer the latter.

Also, there is a substantial body of work on memory management in lazy functional languages like Haskell, consider for example weak pointers or compact regions.

2 Likes

It’s not necessarily a trade off. It’s possible you can improve memory’s API. You only have to trade off when you’re at some sort of peak. It’s possible that there’s ways to improve control of allocation without forcing it on the algorithm-writer.

Sometimes you can just do better rather than trade off!

1 Like

I dont have time yet for full replies but they will be coming along with another post to elucidate things so I will be brief

I don’t disagree - consider this as a very vague template for other classes. ‘memory’ is a very nebulous / generic concept until you start pinning those pieces down. For the most part, we can usually assume 8-bit byte-addressable architectures running in IO that return a standard Ptr wrapped in some data or newtype - for the most part. I am hoping that we can add some constraints though - hence the desire for conversation.

This is a common belief, due to array decay in C, but pointers are not arrays, and I will stand on tat point - though they are somewhat duals.

Pointers are addresses that support pointer arithmetic that can be used to implement arrays, but pointers are about contiguous memory / addresses and offset, while arrays are indexed and are about constant-time access - very similar, but the devil is in the details. Pointers may be null, arrays must not. Pointers are relative and deal with alignment, packing, word size, addressing mode, etc, arrays are absolute and have simple indices.

I am not speaking of just the bog-standard standard C stdlib malloc, but also of things like kernel-level allocators that make such bog-standard simplicity possible :slight_smile:

I do prefer the monad approach myself, and I think with more concrete properties, eg an allocator of specific specific type will inform the other variables, even though under the hood eventually there is the host allocator. Like, an object pool still deals with bytes but they mask that with a better interface even though it must support the more low-level. Keep the perspective of dealing with very primitive# things.

I will respond to more later.

1 Like

I have a practical question. The package name memory is lost to the Haskell community while its current maintainer chooses not to develop the package further but also to not ‘hand the keys’ to any alternative maintainer. My question is, what is the best way forward:

A: fork memory under a different name and then ‘build on those foundations’; or

B: ‘start from scratch’ with a package that has a different name?

2 Likes

Addendum to pointers are not arrays:

An array and a pointer are the same, up to a point - up to the array element type being the pointer’s type when it is also the addressable type (usually Byte addressable, but sometimes Bit or Word). Eg a pointer to bytes in a byte-addressable system is equivalent to a byte array - but only precisely then.

However this fails the moment you need to access multiple contiguous buckets - a pointer can implicitly simultaneously address some number of buckets starting at an arbitrary position as a single unit, an array must index into each slot individually to re-assemble the complete datum

Consider the implementation of a struct, and pointers to its member fields of various types. A pointer just needs an offset to access a field member, but to simulate struct fields an array must pretend multiple slots of the same type make up data of a different type and then cast to it - but casting arrays is generally a Very Bad Idea.

So pointers allow you to cast, but not all handle types (eg reference, array) allow casting.

It helps to remember that, a pointer to an array, is a pointer and not an array, and it is not the same as an array of pointers.

I would keep the original if I could, but I do not mind forking under a new name. ‘memalloc’ is my current thought, the other thought is to break it up into multiple smaller libraries with distinct intents - eg memory-allocators, memory-pointers, memory-encoding, etc

If I implemented my memoria idea I would be (a) a ‘avoid bitrot’-type maintainer (b) definitely in the market for more skilled co-maintainers and (c) at least, a person who could be contacted and could ‘reach out to the community’ if something arose that needed action beyond my own capabilities.

Given the feedback on that idea, I was also thinking that memoria could become less ‘monolithic’ as a package by spinning parts out into other packages on which it then depended.

2 Likes