Improving `memory` with better abstractions

I have managed to cobble together a good set of simplified, IO-restricted typeclasses out of the greater writing- and comment-strewn experiment, as to get that out of the way so I can finish writing about it.

You can find the memalloc repo here if you want to look. If you squint, hopefully you’ll see how we can use this to recover the original ByteArray/Access classes. Otherwise you’ll have to wait for documentation and an explanation which are forthcoming.

4 Likes

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

This is a really cool update, and I’m looking forward to seeing this all become usable. I have a few comments, which might just be due to my misunderstanding the design:

  1. Many classes have class-specific fooEq functions: AddressSpace has addressEq, Handle has hdlEq. Would it be better to have class Eq (Address asp) => AddressSpace asp, class (Eq (h a), Eq1 h) => Handle h, etc?
  2. Are your fooInit functions (layoutInit, allocInit, etc) meant to be safe bracket-style functions? Would it make sense to shoehorn a with into those names? Or are these reserve-and-initialise? I think it might be the latter; would naming the functions like layoutAndInit be clearer here?
  3. At the moment, layoutInit reads to me like it initialises a layout, but actually it seems like it takes a tag indicating the LayoutSpace as well as the layout and returns an Address. Am I correctly reading that that an instance of LayoutSpace is not meant to be a singleton (e.g., you could have layout spaces for individual memory segments if you were in a strange memory model)?
    • Nit: Should the type variable in LayoutSpace be lsp instead of alr or something?
  4. The distinction between a LayoutSpace and an Allocator is still unclear to me, despite your clarification that “this is in comparison to a layout space, which only allocates individual addresses and doesn’t care what you do with them”. In particular, I struggle to imagine what I am able to do with a LayoutSpace and I don’t know what operations would be safe to pass to the callback in layoutInit. Could you please provide a code snippet explaining how to use this machinery both for simple malloc()/free() style memory usage, as well as for some more exotic layout like SoA?
  5. Is there a reason layoutInit takes a polymorphic callback while allocInit takes a monomorphic one?
  6. Are the class names in your deallocator hierarchy too tightly coupled to specific allocation strategies? That is, is it possible to have a deallocator that can “drop all” that isn’t an arena allocator? (StackAllocator seems fine, since it’s a name of an abstract data type as well as a machine stack.)
  7. What is the function parameter to pop used for?
  8. Have you considered using the StateVar library? It seems like its class HasGetter is your class Reference, and its classes HasSetter and HasUpdate are your class MutableReference. It also allows write-only and write/update vars, in case that split is useful to you (e.g. for things which act like output registers).
  9. If a “pointer is just an address that”, should you have class Array ptr => Pointer ptr?
  10. Is it true that the Int is a right group action on a ptr? This might be a useful law to note.
  11. Are there any pointer schemes which lack a null pointer? It could potentially be very useful to do arithmetic on non-null pointers only.
  12. Is it universally true that uintPtr nullPtr == 0? If so, this might be worth writing as a law; if not, there might be some work here to ensure that nullPtr doesn’t compare equal to a zero pointer.
  13. Is it true that for UIntPointers p and q plusPtr p (diffPtr p q) == q? Another potential law.
  14. Should the pointer hierarchy have an Eq ptr constraint?
  15. I think I agree with you that there should be some kind of constraint on class Castable because otherwise that’s a pretty scary type. Maybe there needs to also be some kind of constraint that a and b are “castable to each other” in some kind of meaningful sense that depends on something elsewhere in your layout/address/pointer hierarchy?
4 Likes

Memory Functors

This isn’t quite ready for publishing yet, mostly because I am still mulling things over, but I think I have had broken through the sticky wicket with something I hope you’ll like. A few things, actually.

Bits Proposal

First, I have been working on an extended Bits hierarchy. I have an actual proposal draft with more detail, but I’ll give you the cliffs notes because it is still in progress. The code is still shaking loose but I am pleased with the fundamental breakdown so far.

Why? Because Haskell’s bitwise tooling is so poor that it is mentioned in wikipedia:

“Haskell likewise currently lacks standard support for bitwise operations, but both GHC and Hugs provide a Data.Bits module with assorted bitwise functions and operators, including shift and rotate operations and an “unboxed” array over Boolean values may be used to model a Bit array, although this lacks support from the former module.” - Wikipedia, Bit Array, Language Support

I’d really like to fix that. So what are the problems?

The current Data.Bits is extremely monolithic, and conflates several distinct concepts and responsibilities, making it difficult to implement lawful instances.

Particular issues include:

  • Bits is huge - it has 22 different functions to implement
    • It is large enough that many implementations are partial
    • Eg they implement xor or testBit while more complex functions such as rotate are left unimplemented.
  • It does not distinguish between logical and arithmetic shifts
  • FiniteBits is actually about fixed-width precision, which excludes arbitrary precision units (eg finite but dynamic)
    • bitSize, bitSizeMaybe, and finiteBitSize have historical issues
    • None of the size functions actually check the value argument, which is necessary for arbitrary precision units
  • .&. and .|. are super awkward* but then we have xor instead of .^. probably because ^ is used for exponentiation in Haskell instead.

* I’d love to actually steal (&&) and (||) from Data.Bool and recast them as (&&), (||) :: (Boolean a) => a -> a -> a which is backwards-compatible with Bool

If we break the Bits (and FiniteBits) class down and group the functions by use, several distinct categories become apparent:

  • Boolean algebra
    • complement, .&., .|., xor
  • Multi-bit operations / shifts
    • shift, rotate, shiftL, unsafeShiftL, shiftR, unsafeShiftR, rotateL, rotateR
  • Per-bit access
    • bit, setBit, clearBit, complementBit, testBit
  • Size introspection
    • bitSizeMaybe, bitSize, finiteBitSize
  • Population statistics
    • popCount, countLeadingZeros, countTrailingZeros
  • Miscellaneous / representational
    • zeroBits,isSigned

A fair spread of concepts - one might say that the functions in the Bits class are more united by an implicit or unstated assumption regarding therir expected performance, than by any single concept.

The proposal is to replace the singular Data.Bits class with a hierarchy of three core classes - Boolean, Bitwise, and Bits to fix multiple deficiences, distinguish between finite / arbitrary precision and fixed width / precision (eg Integer vs WordN 128), and to maybe also integrate Bytes neé ByteArray more closely into that hierarchy.

This restructuring will provide a clearer separation of concerns, better type safety, more lawful instances, and help provide a more extensible foundation for low-level programming in Haskell. If done carefully, it could be almost backwards-compatible; a FromDataBits wrapper for deriving via would serve to make the transition easier.

There are actually more classes to the hierarchy with respect to bit formats (eg, TwosComplement) which I am still working on, as well as integrating concepts like Endianness, but they are not so pressing at present.

I am especially keeping in mind certain disciplines:

  • Cryptography
  • Game Development
  • 3D modeling
  • Graphical processing

Believe it or not, one of my current goals and major reasons for learning Haskell was to build a (distributed) game engine - something I used to be quite good at, something that needs good low-level memory management to run quickly, and cryptography to make it run safely and securely in a distributed environment.

I have always had this as a concrete, long term goal, and a not insignificant amount of this recent memory work is aided by my looking back on and translating some of my older (decades old by now) C projects and tech demos.

Units

Bit and Byte are now a thing, and have very specific meaning (smallest unit, and smallest addressable unit); the distinction between them and eg Bool or Word8 is that Bit and Byte do not have a value interpretation attached.

I would like to do the same for Word, however, I have run into the issue that Haskell obviously already uses the nomenclature Word instead of UInt, when I need it to mean ‘largest addressable unit’ which is the more widely-accepted meaning for Word - which it does already mean, it just also has a value-judgement attached to it that I want to separate off. I might just have to deal with newtyping Memory.Word over Data.Word so they can be separate concepts.

Why care about this? Proper handling of units makes more things possible, like being able to declare sizes with IEC or SI prefixes eg newtype Bank 64 Kibi Byte = Bank (Ptr Word8), or being able to declare other base unit types in the future, such as Qubit.

Functors

The main thing that I have been working on, are memory functors.

You see (and this is the thing that I’ve been stuck on), Haskell is all about functors, and the problem is, memory can’t be a functor (or even a monofunctor):

  • Memory can’t be passed by value, only by reference
  • Memory can only contain primitive / unlifted / storable things
  • Memory operations require a destination to put the result
  • Memory operations require a length to be supplied
  • Memory operations run in IO

This has several knock-on effects:

  • You can’t really copy memory, only the contents
    • Memory is where the values live, after all
  • You need to either supply an existing destination, allocate a new one, or mutate the source
    • Each of these affects functions differently
    • They are not mutually exclusive, either
  • Mutable memory is further constricted to act like a monofunctor
    • This is because the contents are not lifted, and are of fixed size

Despite not actually being functors (not in the usual sense, anyway), I have managed to characterize the behavior in such a way that they are similar enough, and produce a set of typeclasses:

-- Takes a destination as an additional argument
class MemCopyFunctor mem where

    memCopyMap :: (a -> b) -> mem a -> mem b -> Int -> IO ()

-- Allocates a destination and returns it
class MemAllocateFunctor mem where

    memAllocateMap :: (a -> b) -> mem a -> Int -> IO (mem b)

-- Mutates the source in-place
class MemMutateFunctor mem where

    memMutateMap :: (a -> a) -> mem a -> Int -> IO ()

-- Memory folds
-- NOTE: The IO may be unnecessary
class MemFoldable mem where
    memFoldl :: (b -> a -> b) -> b -> mem a -> Int -> IO b
    memFoldr :: (a -> b -> b) -> b -> mem a -> Int -> IO b
    memFoldMap :: Monoid m => (a -> m) -> mem a -> Int -> IO m

-- Convenient 
class MemCopyFunctor mem => MemCopyZipFunctor mem where

    memZipWithCopy :: (a -> b -> c) -> mem a -> mem b -> mem c -> Int -> IO ()

I’ve been iterating on this quite a bit (hence my delay in updating), but I eventually settled on recognizing that the most important functions in memory are not the ByteArray/Access classes, but rather the functions that they rely on for implementation, which are actually the functions in Data.Memory.ExtendedWords. Hence this successful iteration seeks to generalize those functions, and thus transitively get the ByteArray/Access functions more or less for free.

For example, although they should be defined per instance in a more efficient manner, memCopy = memCopyMap id, and memSet mem x = memMutateMap (const x) mem, and memXor = memZipWithCopy Data.Bits.xor.

Notably, Traversable may not have a similarly sensible interpretation, mostly because memory can only contain primitive things, so no sequence since that would require mem (m a) and there may be other issues with mapM. However, it seems that Mem*Functor and MemFoldable are sufficient to accomplish quite a lot.

The practical effect of this design is that it covers the most-used portions of the memory interface, and most of the functions in ByteArray/Access can / have found representation with some combination of Allocator, Bytes, Memory*Functor, and MemoryFoldable - and given how sparse ByteArray/Access is compared to ByteString and Vector, we may actually have better coverage.

NOTE: I have not unified this with the earlier Allocator classes but that is probably okay because how the allocator is chosen is left up to the implementation, otherwise MemAllocateFunctor would / will need an explicit allocator argument

I think I feel good about this, because with these classes, low-level Haskell programming is starting to feel “fun”, in the same way that programming in C can be - it is nice to be close to the metal, but at the same time I can fall back and rely on high-level Haskell to fill development gaps.

Bonus: Order

This is the third distinct time that I have wished for a more nuanced order typeclass hierarchy than just Eq and Ord - some very important classes burdened by legacy and history. Just look at the documentation and implementation notes in Data.Ord. I have taken the effort to at least illustrate what a proper order hierarchy would look like:

I am not entirely sure on how to express the necessary functions for each typeclass, but if these were actually lawful classes, Eq and Ord could be softly relaxed / demoted to focus more on their duty of providing convenient infix operators for data types that have equivalence and comparison relations on a non-exceptional subset of values, eg which is how they are actually being used now, because they are actually technically lawless. Fixing this would put us on par with other modern languages with more technically correct equivalence and comparison classes.

This will almost certainly not be accepted as a proposal though, due to the burden of legacy - eg fixing Ord Double could cause so many breakages probably.

Anyway, my justifcation for spending time on this is that it turns out that preorders (directed graphs with cycles) and partial orders (directed acyclic graphs) are intimately related to memory addressing, in that memory addresses are not only not guaranteed to be totally ordered, they are not even guaranteed to be partially ordered; they are actually only necessarily pre ordered*, though this pre order plus the equivalence relation of “addresses the same location” induces a weak ordering / total preorder duality (it is complicated).

* For example, segmented pointers allow multiple addresses to point to the same location, which gives rise to cycles because now a < a for every address.

Indeed, pre and partial orders are very useful for not just memory addressing but also memory management algorithm in general, because garbage collection is all about reachablity, which is what directed graphs (and thus pre and partial orders) are good for.

Responding

@jackdk - some things have changed, but I will try to answer as best I can:

Many classes have class-specific fooEq functions: AddressSpace has addressEq, Handle has hdlEq. Would it be better to have class Eq (Address asp) => AddressSpace asp, class (Eq (h a), Eq1 h) => Handle h, etc?

The difference between (==) addrEq and hdlEq is a subtle difference of equivalence - (==) is used for exact / structural equality, addrEq is used for same-location equivalence, and hdlEq is for same-reference equivalence which is basically when addrEq = (==).

Are your fooInit functions (layoutInit, allocInit, etc) meant to be safe bracket-style functions? Would it make sense to shoehorn a with into those names? Or are these reserve-and-initialise? I think it might be the latter; would naming the functions like layoutAndInit be clearer here?

Both? Bracket-style functions allow us to turn an alloc-and-init function into a with-temporary-resource function. The difference is whether or not the allocation persists afterwards, which may be allowable with eg counted references. So mostly the latter, but designed to enable support from the former.

At the moment, layoutInit reads to me like it initialises a layout, but actually it seems like it takes a tag indicating the LayoutSpace as well as the layout and returns an Address.

The relation between address spaces, addresses, memory spaces, layouts, and allocators is something I am still clarifying / working on - right now the way I conceptualize it is that roughly asp + addr + layout = pointer, eg where alloc :: Int -> IO (Ptr Word8) ~ allocAddr :: asp -> layout -> IO addr. The pointer type tells us the address space, and the pointer content type tells us layout needs, which may be count, alignment, pixel format, etc.

I think this is why I kept eg oldLayout as an argument for deallocate - it is still shaking loose.

Am I correctly reading that that an instance of LayoutSpace is not meant to be a singleton (e.g., you could have layout spaces for individual memory segments if you were in a strange memory model)?

Yes! You get it!

Nit: Should the type variable in LayoutSpace be lsp instead of alr or something?

Yes typoes I need to clean things up

The distinction between a LayoutSpace and an Allocator is still unclear to me, despite your clarification that “this is in comparison to a layout space, which only allocates individual addresses and doesn’t care what you do with them”. In particular, I struggle to imagine what I am able to do with a LayoutSpace and I don’t know what operations would be safe to pass to the callback in layoutInit. Could you please provide a code snippet explaining how to use this machinery both for simple malloc()/free() style memory usage, as well as for some more exotic layout like SoA?

I agree that it is unclear, (see the earlier answer), but conceptually is related to the difference between allocating addresses and allocating values - an allocator attaches some value judgement to an address, but a layout space just allows to to ‘find an available space’ which isn’t necessarily the same thing as claiming it.

Easy example is you have a bank of 64KiB of memory, it is completely unmanaged, and you need to find an address / location that fits the layout requirements. The layout space only cares whether a piece of data ‘fits’ at an address but it doesn’t yet care whether that address is occupied.

Is there a reason layoutInit takes a polymorphic callback while allocInit takes a monomorphic one?

I agree though that it is muddled - work in progress, shaking loose, etc.

layoutInit a CPS-style function equivalent for convenience, it isn’t technically necessary but may be more ergonomic for certain cases.

allocInit just forces you to be able to initialize without returning anything else, but is also for ergonomics. We can implement it with a default:

allocInit alr lo f = do
    aln <- alloc alr lo
    withAddress aln f
    pure aln

-- We also can implement allocRet
allocRet alr lo f = do
    -- aln <- allocInit alr lo (\_ -> pure ())
    -- Or, with just alloc
    aln <- alloc alr lo
    a <- withAddress aln f
    pure (a, aln)

However, it hinges upon withAddress which I may make into its on class - so it actually may be necessary.

Are the class names in your deallocator hierarchy too tightly coupled to specific allocation strategies? That is, is it possible to have a deallocator that can “drop all” that isn’t an arena allocator? (StackAllocator seems fine, since it’s a name of an abstract data type as well as a machine stack.)

Terminology for allocation strategies is incredibly inconsistent, so I understand your worry. I will need to be explicit on what I mean eg an arena to be, because different readers may interpret eg what a slab or an arena allocator are differently.

For this reason, the typeclasses are specifically about various properties that allocators have - so for “That is, is it possible to have a deallocator that can “drop all” that isn’t an arena allocator?” the answer is yes, sort of.

The classic ArenaAllocator implementation has only 2 operations - allocate, and deallocateAll, but since allocate is already identified with Allocator, that leaves us with deallocateAll as uniquely identifying Arena and Arena-like allocators.

A classic arena allocator might only be able to deallocate everything all at once, but you might have a combination of a Stack and an Arena allocator, that can pop the most recent alloction, or all of them - which it could do by popping all allocations thus deallocating them one by one.

What is the function parameter to pop used for?

Because pop is a deallocation, we can’t return the popped value to act on it after, and usually people want to be able to do something with the popped value. So the action gives you a chance to act on the popped value before it gets deallocated, and you can return the result.

Have you considered using the StateVar library? It seems like its class HasGetter is your class Reference, and its classes HasSetter and HasUpdate are your class MutableReference. It also allows write-only and write/update vars, in case that split is useful to you (e.g. for things which act like output registers).

Not specifically, but I have been going over many similar reference-like data types such as IORef and whatnot - so this is getting added to my list.

If a “pointer is just an address that”, should you have class Array ptr => Pointer ptr?

Pointers do have addresses (they are defined by addrOf), but pointers aren’t arrays - arrays can be pointers, but they don’t have to be, they might be references, etc.

Most of the time when pointers and arrays are mixed up, it is because C silently casts arrays to the pointer to their first element, but a pointer and an array are quite different things.

Consider the difference between a pointer-to-an-array, and an array-of-pointers - they are not the same. Consider also that a pointer can access multiple buckets in a single operation, whereas an array can not. Consider that a pointer may have padding between elements, whereas an array does not.

Pointers can efficiently implement arrays, but an array can only inefficiently implement pointers unless the element fits in a single bucket.

Is it true that the Int is a right group action on a ptr? This might be a useful law to note.

Yes - excellent catch

Are there any pointer schemes which lack a null pointer? It could potentially be very useful to do arithmetic on non-null pointers only.

I agree - I think I should split off Nullable or NonNullable to it own class like Castable.

Is it universally true that uintPtr nullPtr == 0? If so, this might be worth writing as a law; if not, there might be some work here to ensure that nullPtr doesn’t compare equal to a zero pointer.

It is extremely not universally true, and only perceptually true for historical reasons. Even in most languages that allow for assigning 0 to mean the same thing as assigning nullPtr, it is usually a compiler mechanic giving the zero literal special treatment when being assigned to a pointer. The null pointer itself does not actually have the zero address, and a non-null pointer with the zero address can usually be obtained by awkward multi-casting to get around the special compiler rules.

Is it true that for UIntPointers p and q plusPtr p (diffPtr p q) == q? Another potential law.

For the C std flat pointer? Yes. I think it holds more or less even for more exotic memory layouts (eg segmented pointers) so long as you only consider exact equality and not equivalence.

Should the pointer hierarchy have an Eq ptr constraint?

Probably - I think I omitted it because it is assumed that all allocations are Eq, so all pointers will get Eq from somewhere else, and the Eq constraint isn’t technically necessary for the class itself oddly enough.

I think I agree with you that there should be some kind of constraint on class Castable because otherwise that’s a pretty scary type. Maybe there needs to also be some kind of constraint that a and b are “castable to each other” in some kind of meaningful sense that depends on something elsewhere in your layout/address/pointer hierarchy?

Yes this is an area of research for me that is also relevant for memory functors regarding being able to cast between things that have the same sized representation. However, this starts getting into wierd things like quantified constraints because the constraint for an allocation / pointer content may be specific to the type of allocator. I am not quite sure what to do, but it should become more clear as things continue to develop.

Final conclusion & health

This isn’t published to git yet, but it will be this week.

I have been struggling with my health lately, and these concepts require a pretty deep dive / multi-hour concentrated effort so I have not been able to write as frequent of updates as I would like. I am pacing myself, just know that I am here quietly, not gone.

9 Likes

That seems wrong, Data.Bits is part of the Haskell 2010 standard.

And it shouldn’t, in my opinion. If you want logical right shift, you can use shiftR on Word (or one of its variants). My understanding is that languages with an arithmetic and a logical right shift operator only have both because they lack unsigned integer types.

I’m totally fine with .&. and .|.. I think using && and || instead would be a bad idea, since they suggest Bool to me, and bitwise and boolean operators are often used for very different applications.

5 Likes

We should correct that. But we should also update Bits to be more logically correct because 2010 was a long time ago. After all, we fixed Applicative and Monad, Semigroup and Monoid. We should fix this.

Like, I don’t disagree with you in a practical sense - yes, you can turn a Int8 to a Word8 to get the behavior that you want, but counterpoint: I shouldn’t have to coerce my types to do this - its precisely shenanigans like that that are the problem. Yes we can do it manually, but I am trying to make the respective functions explicitly and directly available to the data types that support it. I am not trying to make the previously existing behavior impossible, I am trying to make it not a requirement.

This understanding is not quite correct. A more correct definition of arithmetic shift is a logical shift that only applies to a privileged subset of bits, who’s fill rule is determined by the data type of the interpretation (and is usually the sign bit if it exists) - and this definition allows us to include floating and fixed point numbers in addition to integrals.

Remember, there are formats other than unsigned binary and two’s complement. One’s complement, excess-K - these are esoteric - but what about pixel formats? Pixels are certainly Bits! But they aren’t numbers!

Part of the problem with Bits is that we have this artificial restriction, that we must eg have a integral interpretation of the Bits - and what you propose actually doesn’t allow us to eg provide an instance of Bits for Float.

By breaking it up this way, we can include more things into the super-classes that can’t currently satisfy constraints of the sub-classes. For example, in the super-extended hierarchy which I did not show (because it is a much larger swallow), signof is part of SignedBits, which is a superclass of NumBits, as it nestles up to Num from below.

Allowing short circuiting isn’t necessarily incompatible with the new definition. because Boolean doesn’t imply Bits. If its necessary, we can keep the distinction, but I don’t think its. I more have a problem with operators being defined within typeclasses - in my Dream Haskell, operators defined in classes are replaced with proper function names, allowing us to eg, retain Num while using (+) for something else. That would give us both what we want.

3 Likes

A magic trick

It has been a rough week; my laptop display has shorted out, and I have not been able to repair it yet; I have been force to work from a phone, albeit one that can SSH into my laptop. I have, after many days, managed to acquire a monitor and connect to it using a horrifying dongle-stack of DVI-to-HDMI-to-USBC adapters.

I think, however, the incredibly low bandwidth of using SSH over a phone for a few days was somehow at least purifying, because having gotten my laptop at least functional again, today was a day of flying fingers, and it is now late in the evening and I would like to post tonight.

Remember those MemCopyFunctor, MemAllocateFunctor, and MemMutateFunctor classes I defined last week? We’re going to put them to use. For now, just assume that they are all part of the same class.

Without further ado, the magic trick:

First, we define a class for memory allocations (eg, a pointer or such - not the address- or layout- or memory- space; I have been trying to simplify to get something useful out of this sooner rather than later):

class Memory ptr where
    type Shape ptr :: * -- Layout-ish

Don’t worry about this one too much - Shape is usually Int, aka “how many”.

Next, we also define some subclasses!

-- Why is Observable IO? Because observing may have side effects
class (Memory ptr) => ObservableMemory ptr where
    memRead :: ptr a -> IO a

class (Memory ptr) => MutableMemory ptr where
    memWrite :: ptr a -> a -> IO ()

-- Copyable does not imply observable!
class (Memory ptr) => CopyableMemory ptr where
    memCopy :: ptr a -> Shape ptr -> ptr a -> IO ()

-- A simplified class for implicit / default memtype-dependent allocators
class (Memory ptr) => MemAllocator ptr where
    memAlloc :: Shape ptr -> IO (ptr a)

With that out of the way, we can redefine our various Mem*Functor classes:

-- NOTE: We don't actually *need* to combine our 'Mem*Functor' classes, but we
-- will do it here just to keep verbosity down. You'll thank me in a second.
-- Still doesn't imply observable!
class Memory ptr => MemFunctor ptr where
    memMapCopy :: (a -> b) -> ptr a -> Shape ptr -> ptr b -> IO ()
    memMapAlloc :: (a -> b) -> ptr a -> Shape ptr -> IO (ptr b)
    memMapMutate :: (a -> a) -> ptr a -> Shape ptr -> IO ()

Now that the stage is set, it is time to perform the magic. See, it turns out that memMapCopy is a critical function, and with the right classes, we get a lot of implementations for free!

default memCopy :: MemFunctor ptr => ptr a -> Shape ptr -> ptr a -> IO ()
memCopy src shape dest = memMapCopy id src shape dest

default memMapAlloc :: MemAllocator ptr => (a -> b) -> ptr a -> Shape ptr -> IO (ptr b)
memMapAlloc f src shape = do
    dest <- memAlloc shape
    memMapCopy f src shape dest
    return dest

default memMapMutate :: MutableMemory ptr => (a -> a) -> ptr a -> Shape ptr -> IO ()
memMapMutate f src shape = do memMapCopy f src shape src

That’s just some razzle-dazzle, though! Now, for the main event - are you watching closely?

We take some elegantly classy clothes:

-- First we define a memory tensor class
class (MemFunctor t) => MemTensor t (dims :: [Nat]) where
    -- Not interesting for the trick

-- Then we define a memory matrix class
class (MemTensor t [r,c]) => MemMatrix t (r :: Nat) (c :: Nat) where
    -- N / A

-- Then we define a memory vector class
class (MemMatrix t n 1) => MemVector t (n :: Nat) where
    -- N / A

And dress up our assistant data type Ptr in them:

newtype MemVec (n :: Nat) a
    = MkMemVec (Ptr a)

instance Memory (MemVec n) where
    type Shape (MemVec n) = Int
instance ObservableMemory (MemVec n) where
instance MutableMemory (MemVec n) where
instance CopyableMemory (MemVec n) where
instance MemAllocator (MemVec n) where
instance MemFunctor (MemVec n) where
instance MemTensor (MemVec n) [n,1] where
instance MemMatrix (MemVec n) n 1 where
instance MemVector (MemVec n) n where

We actually have a second assistant - they’re twins, really!

data MemString a
    = MkMemString
    { memStringPtr :: Ptr a
    , memStringUnitCount :: Int
    }

instance Memory MemString where
    type Shape MemString = Int
instance ObservableMemory (MemString n) where
instance MutableMemory MemString where
instance CopyableMemory MemString where
instance MemAllocator MemString where
instance MemFunctor MemString where

Are you ready for them to disappear?

newtype BitVec n = MkBitVec (MemVec n Bit)
    {- deriving ... -}
newtype ByteVec n = MkByteVec (MemVec n Byte)
    {- deriving ... -}
newtype BitString = MkBitString (MemString Bit)
    {- deriving ... -}
newtype ByteString = MkByteString (MemString Byte)
    {- deriving ... -}

Presto chango! The memory functor tensor matrix vector is now a ByteVec (and its dynamically-sized twin, a ByteString)! Get it? Memory pointer vanished into a Box? Boxed types? Pulling a rabbit ByteString out of a hat?

Only we’ve defined in such a way that it is trivial to give it a fixed length, or multiple dimensions - and that is important considering that MemVec n Word64 is trivially MemTensor t [n,8,8] because the bytes and bits form a tensor (8 bits per byte, 8 bytes per word) and using tensors actually allow us to talk about various addressable units more easily.

We could actually even make MemString and MemVec polymorphic over the pointer type - because then MemString ForeignPtr Byte would be truly backwards compatible with Data.ByteString. But again, I wanted to keep this short.

And this isn’t even applying MemFoldable yet! That’s all for now.


I hope this recreation of a ByteString data type from distant and non-obvious first principles (and subsequent ease of defining & allocating eg multi-dimensional arrays) is a good demonstration of what I am trying to achieve with this work - a sort of generalization / unification of ByteString, ByteArray, Ptr, ForeignPtr (and Array, too, considering the earlier work); I feel I am now ready to begin applying all of this back to Botan, because we are now equipped with the low-level memory safety and tools that we have been so sorely needing!

NOTE: I am trying to get this up to github, but have run out of steam for the day.

5 Likes