Improving `memory` with better abstractions

memalloc-io update

I have an update to the memalloc repo:

Multiple updates for increased parity with ByteArray:

  • Added (almost too much) documentation
  • Improved terminology w/ shorter, less-pedantic function names
  • Moved Memory.IO.Array to Memory.IO.Access.Array
  • Split Allocator (again) into LayoutSpace and Allocator
  • Implemented the Std allocator that uses GHC’s wrapping of the C malloc and free
  • Added notes about parameterizing Allocator in Std
  • Implemented allocRet, empty for parity (and some others)
  • Added implicit interface example with an implicit allocRet & empty

Focusing on this IO-restricted memalloc-io is yielding good progress, to the point that I have reached one of the most significant questions regarding the design of this library, and possibly have found the answer to that as well - we will discuss this at the end.

For now, let us…


Meet the Allocators!

There is quite a stack of things, so we will proceed in order from abstract to concrete.

Addresses and Address Spaces

First up, is address spaces!

An address space is anything that defines a range of addresses. This address space is not required to be dense, contiguous, or even ordered. Commonly encountered address spaces include the 64-bit flat virtual address space, or the various IP address spaces.

class AddressSpace asp where

    data family Address asp

    addrEq :: Address asp -> Address asp -> Bool

An address has the property that, if two addresses are equal, then they must point to the same location.

Thus, we can check if two addresses are equal. Note that this is not the same thing as asking whether two addresses point to the same location.

Layouts and Layout Spaces

If an address is a point, then a layout gives it volume. What a layout is, is deliberately left abstract.

class (AddressSpace alr) => LayoutSpace alr where

    data family Layout alr

    layout :: alr -> Layout alr -> IO (Address alr)
    layoutInit :: alr -> Layout alr -> (Address alr -> IO a) -> IO a

    {-# MINIMAL layout | layoutInit #-}

We can use a layout to assign an available address according to the layout, and then initialize it.

Common layout properties range from simple size and alignment to more complex layouts such as Struct-of-Arrays for ECS or GPU buffers.

Allocators and Allocations

An allocator reserves a block or region of memory for a particular use. This is in comparison to a layout space, which only allocates individual addresses and doesn’t care what you do with them.

class (LayoutSpace alr) => Allocator alr where

    data family Allocation alr

    alloc :: alr -> Layout alr -> IO (Allocation alr)
    allocInit :: alr -> Layout alr -> (Address alr -> IO ()) -> IO (Allocation alr)

    withAddress :: Allocation alr -> (Address alr -> IO a) -> IO a

    {-# MINIMAL (alloc | allocInit), withAddress #-}

With an allocator, we can allocate a new region of memory according to a given layout, optionally initializing it. The allocation wraps an address, and may contain additional data about what is stored there, eg size, alignment, type, refcount, etc.

We can also grant temporary access to the underlying address of an allocation using withAddress, but I am thinking of splitting this off to another class.

This is actually sufficient to recreate allocRet from the original memory:

allocRet
    :: (Allocator alr)
    => alr
    -> Layout alr
    -> (Address alr -> IO a)
    -> IO (a, Allocation alr)
allocRet alr lo f = do
    aln <- alloc alr lo
    a <- withAddress aln f
    pure (a, aln)

That’s pretty good - the core function for half of our main goal!

Deallocators

An allocator acquires memory, how do we release it?

There are several classes of deallocators.

First up is the standard deallocator, which can deallocate or free any individual layout.

class (Allocator alr) => Deallocator alr where

    dealloc :: alr -> Maybe (Layout alr) -> Allocation alr -> IO ()

The layout may be recoverable from either the allocator, the allocation, or else supplied manually, hence the layout may be provided as an optional hint; if this argument proves unproductive or useless, it may be removed in the future.

An arena (de-) allocator is an allocator that can free all of its allocations at once:

class (Allocator alr) => ArenaAllocator alr where

    deallocAll :: alr -> IO ()

These are pretty great for per-frame allocations in games, or per-request for webservers - really, any time you need to free a bunch of memory all at once when you are done with it.

And there are also stack (de-) allocators, which can rewind or pop the latest allocation:

class (Allocator alr) => StackAllocator alr where

    pop :: alr -> (Allocation alr -> IO a) -> IO a

I’ve made these deallocators require being an allocator, because although we could eg feasibly make an allocation that only requires itself to free, that only fits the standard deallocator, and we can construe that as an allocation that remembers its allocator (or has a manager that does) so its easier to define free ptr = dealloc (allocator ptr) None ptr (and you can see why / how I want to vanish that dealloc layout argument as well…)

Access and Allocations!

Alright, so we’ve allocated (and deallocated), now, what about the things themselves - the allocations? That is, how do we specifically access or use the memory that we have just allocated?

Well, this is where things get a little weird and nitpicky. I have done my best to split allocations up into 4 potentially-overlapping concepts, all based on what properties or access they grant.

Handles

A handle is a label for a resource, eg a file or socket etc, with very few prescribed properties. It isn’t even necessarily a reference, because it may not be dereference-able.

class Handle h where

    hdlEq :: h a -> h a -> Bool

The one property that a handle has over an address is that we can check whether two handles point to the same resource. That is, a handle has the property that, if and only if two handles are equal, then they must point to the same resource.

This is a stronger guarantee than an address, which only guarantees that equal addresses point to the same resource - a handle guarantees that if two handles point to the same resource, then they are equal.

Or, to be concise, an address can be many-to-one, a handle must be one-to-one.

Yes this difference is really nit-picky. But I felt this difference needed making.

References

A reference allows you to access or load the value stored in the reference - this is what gives most language’s variables their powers.

class Reference r where

    load :: r a -> IO a

class (Reference r) => MutableReference r where

    store :: r a -> a -> IO ()
    update :: r a -> (a -> IO a) -> IO ()

     {-# MINIMAL store | update #-}

At a low level, dereferencing means copying the value from one address to another, potentially to a different address space altogether. In most languages, this usually means copying the value to a register or the stack. In Haskell, this means yielding a lifted value.

I’ve included a mutable reference class too, it is not a very complicated concept.

Arrays

An array is just a multi-reference.

class Array arr where

    length :: arr a -> Int
    index :: arr a -> Int -> a

class (Array arr) => MutableArray arr where

    storeAt :: arr a -> Int -> a -> IO ()
    updateAt :: arr a -> Int -> (a -> IO a) -> IO ()

Look at how it is just Reference, except for the length function and the Int argument added to index neé load, store/At, and update/At!

Also, the core functions to the other half of our main goal! Not bad! I mean, we still gotta use them, but that’s coming.

Pointers

So remember when I just said that references aren’t complicated?

Well, neither are pointers. Pointers are just an address that you can perform arithmetic on. They aren’t necessarily references though, because eg they could be an array instead.

class Pointer ptr where

    nullPtr :: ptr a
    plusPtr :: ptr a -> Int -> ptr a

class (Pointer ptr) => UIntPointer ptr where

    uintPtr :: ptr a -> Word

    alignUpPtr :: ptr a -> Int -> ptr a
    diffPtr :: ptr a -> ptr a -> Int

Note that a pointer is not the same as an array, because a pointer address may have multiple successor addresses depending on the type of the pointer, and because a pointer may access multiple addresses at the same time as a single unit. A pointer can be used to efficiently implement an array, but an array can only emulate a pointer.

Also helpful are integer pointers can represent their address as an unsigned integer. This allows for the pointer to be cast to a flat address space, and for pointers to be aligned or subtracted from one another - both of which require being able to inspect the address as an integer, compared to plusPtr which only puts a number into the address space rather than getting one out of it.

Non-specific Allocation classes

These classes dont necessarily imply any particular allocation type.

I suspect that castables are required to be pointer-references, but have not constrained it as such yet:

class Castable r where

    cast :: r a -> r b

Retainables are more fun - your good ol’ reference-counted handle that disposes of itself when the count reaches zero.

class Retainable r where

    retainCount :: r a -> Int

    retain :: r a -> IO ()
    release :: r a -> IO ()

    autoreleasing :: r a -> (r a -> IO a) -> IO a

Meet the StdAllocator

Let’s try to actually put this all together with an instance for the C standard allocator!

Maybe you’ve noticed the problem we’re about to run into…


data StdAllocator = StdAllocator

-- We do a funky little dance here because the `Ptr`'s inner `Addr#` is not exposed.
ptrToStdAddress :: Ptr a -> Address StdAllocator
ptrToStdAddress ptr = StdAddress $ wordPtrWord $ ptrToWordPtr ptr where
    wordPtrWord (WordPtr wrd) = wrd

stdAddressToPtr :: Address StdAllocator -> Ptr a
stdAddressToPtr (StdAddress wrd) = wordPtrToPtr $ WordPtr wrd

instance AddressSpace StdAllocator where

    newtype instance Address StdAllocator = StdAddress
        { stdAddressWord :: Word -- Because Addr# isn't exposed, but WordPtr is
        }
        deriving newtype (Eq, Ord)

    addrEq = (==)
    addrHash = undefined -- hash

instance LayoutSpace StdAllocator where

    newtype instance Layout StdAllocator = StdLayout
        { stdLayoutSize :: Int
        }

    layout _ (StdLayout size) = ptrToStdAddress <$> mallocBytes size

instance Allocator StdAllocator where

    newtype instance Allocation StdAllocator = StdAllocation
        { stdAllocationPtr :: Ptr Void
        }

    alloc alr lo = do
        addr <- layout alr lo
        pure $ StdAllocation $ stdAddressToPtr addr

    withAddress (StdAllocation ptr) f = f (ptrToStdAddress ptr)

instance Deallocator StdAllocator where
    dealloc _ _ (StdAllocation ptr) = free ptr

Okay, so far so good!

The Next Big Question

Now, let’s make our allocation into a reference-pointer… something like…

instance Reference (Allocation StdAllocator) where
    load (StdAllocation ptr) = Ptr.peek ptr

instance Pointer (Allocation StdAllocator) where
    nullPtr = StdAllocation Ptr.nullPtr
    plusPtr (StdAllocation ptr) offset = StdAllocation $ Ptr.plusPtr ptr offset

Except… oh. We can’t. Allocation alr is of kind * but Pointer and Reference require kind * -> *. Oh dear…

This is the next big question - it needs to be parametric so we can eg allocate a ‘Ptr a’ but it needs to not be so we can eg allocate a monomorphic ‘ByteString’, which hides a ‘Ptr Word8’.

What I might need to do is make Allocator parametric, eg:

class (LayoutSpace alr) => Allocator alr a where

    data family Allocation alr :: * -> *

    alloc :: alr -> Layout alr -> IO (Allocation alr a)

Then, we could keep the original as MonoAllocator if we want, but I don’t think that it’s even necessary, because this works for any of the following:

-- Monomorphic
newtype instance Allocation VoidPtrAllocator Void
    = MkVoidPtrAllocation (Ptr Void)
-- Polymorphic
newtype instance Allocation StdPtrAllocator a
    = MkStdPtrAllocation (Ptr a)
-- Phantom
newtype instance Allocation ByteStringAllocator ByteString
    = MkByteStringAllocation ByteString

Post-editing note: This is I think badly illustrated / imprecise terminology, I will try to clarify this in the future

Why exactly do we need this? Well, references are often phantom eg data Ref a = Ref Foo, while pointers are polymorphic / castable, and arrays are monomorphic / not castable. This works to represent all three.

Crucially, it also gives us a way to produce wrapped allocations, eg a ByteString is secretly wrapping a Ptr Word8 which is secretly wrapping an Addr#.

So I’m probably going to make this change,


So that’s where I’m at, and where I stopped because publishing this update was becoming increasingly pressing :slight_smile:

Bonus: Implicit Params

You can check out how I’m looking into hiding the allocator argument using ImplicitParams to more completely recover the original memory interface in Memory.IO.Allocator.Implicit:

alloc :: (Allocator alr, ?alr :: alr) => Layout alr -> IO (Allocation alr)
alloc = Explicit.alloc ?alr

allocInit :: (Allocator alr, ?alr :: alr) => Layout alr -> (Address alr -> IO ()) -> IO (Allocation alr)
allocInit = Explicit.allocInit ?alr

allocRet :: (Allocator alr, ?alr :: alr) => Layout alr -> (Address alr -> IO a) -> IO (a, Allocation alr)
allocRet = Explicit.allocRet ?alr

empty :: (Allocator alr, EmptyLayout alr, ?alr :: alr) => Allocation alr
empty = Explicit.empty ?alr

So, yeah, that’s all for now!

7 Likes