ArrayArrays

Edward Kmett ekmett at gmail.com
Fri Aug 21 14:58:00 UTC 2015


On Fri, Aug 21, 2015 at 9:49 AM, Ryan Yates <fryguybob at gmail.com> wrote:

> Hi Edward,
>
> I've been working on removing indirection in STM and I added a heap
> object like SmallArray, but with a mix of words and pointers (as well
> as a header with metadata for STM).  It appears to work well now, but
> it is missing the type information.  All the pointers have the same
> type which works fine for your Upper.  In my case I use it to
> represent a red-black tree node [1].
>

This would be perfect for my purposes.


> Also all the structures I make are fixed size and it would be nice if
> the compiler could treat that fix size like a constant in code
> generation.


To make the fixed sized thing work without an extra couple of size
parameters in the arguments, you'd want to be able to build an info table
for each generated size. That sounds messy.


> I don't know what the right design is or what would be
> needed, but it seems simple enough to give the right typing
> information to something like this and basically get a mutable struct.
> I'm talking about this work at HIW and really hope to find someone
> interested in extending this expressiveness to let us write something
> that looks clear in Haskell, but gives the heap representation that we
> really need for performance.


I'll be there. Let's talk.


> From the RTS perspective I think there are any obstacles.
>

FWIW- I was able to get some code put together that let me scribble
unlifted SmallMutableArray#s directly into other SmallMutableArray#s, which
nicely "just works" as long as you fix up all the fields that are supposed
to be arrays before you ever dare use them.

writeSmallMutableArraySmallArray# :: SmallMutableArray# s Any -> Int# ->
SmallMutableArray# s Any -> State# s -> State# s
writeSmallMutableArraySmallArray# m i a s = unsafeCoerce# writeSmallArray#
m i a s
{-# INLINE writeSmallMutableArraySmallArray# #-}

readSmallMutableArraySmallArray# :: SmallMutableArray# s Any -> Int# ->
State# s -> (# State# s, SmallMutableArray# s Any #)
readSmallMutableArraySmallArray# m i s = unsafeCoerce# readSmallArray# m i s
{-# INLINE readSmallMutableArraySmallArray# #-}

With some support for typed 'Field's I can write code now that looks like:
order :: PrimMonad m => Upper (PrimState m) -> Int -> Order (PrimState m)
-> Order (PrimState m) -> m (Order (PrimState m))
order p a l r = st $ do
  this <- primitive $ \s -> case unsafeCoerce# newSmallArray# 4# a s of
    (# s', b #) -> (# s', Order b #)
  set parent this p
  set next this l
  set prev this r
  return this

and in there basically build my own little strict, mutable, universe and
with some careful monitoring of the core make sure that the little Order
wrappers as the fringes get removed.

Here I'm using one of the slots as a pointer to a boxed Int for testing,
rather than as a pointer to a MutableByteArray that holds the Int.

-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20150821/390e1eca/attachment.html>


More information about the ghc-devs mailing list