Mutable and type-safe arrays

27 views
Skip to first unread message

Haskell-mouse

unread,
Feb 18, 2019, 10:20:38 AM2/18/19
to Accelerate
Hi!
I want to ask three questions: 

1. What about to add the dimensions of an array to its type?
Now I write some complex code(using REPA) and sometimes runtime dimensional errors make me crazy due to difficulty finding causes.
I decided to write a wrapper: 

newtype DimMatrix r (y :: Nat) (x :: Nat) a
  = DimMatrix { getInternal :: Matrix r a}

Now I can use it, even if I don't know its dimensions in runtime: 
   1) create DimMatrix in CPS style:       
withMat :: Array D DIM2 Double -> (forall x y. (KnownNat x, KnownNat y) => DimMatrix D x y Double -> k) -> k
   2) Write a complex function with its prerequisites, written as Constraint: 
         
someComplexFunction
  :: forall y1 x1 y2 x2.
  ( HasCallStack
  , AllConstrained KnownNat [x1, x2, y1, y2]
  , x2 ~ d
  , y1 ~ y2
  )
  => DimMatrix D y1 x1 Double
  -> DimMatrix D y2 x2 Double
  -> .....

   3) Check the prerequisites. Unfortunately, it should be done at runtime and compiler can't check the quality of checking. But in the case of simple properties, it is ok. 
       And use the Evidence from the dimensions library:
data Evidence :: Constraint -> Type where
  E :: a => Evidence a

withEvidence :: Evidence a -> (a => r) -> r
withEvidence d r = case d of E -> r

And now I have nice compile-time error messages in case of my mistakes and even more - now compiler can remind me about forgotten prerequisites. Of course, it is just a fast ad-hoc solution, but I think that it can be generalized and made more convenient.
What if I'll write a wrapper (or even native) array with dimensions in its type? Would it be useful?

2. Mutable arrays. Now (if I understand it correctly) Accelerate doesn't support it because it can't check that result's size is equal to the input array's size. 
    But with the type-safe arrays, it can! I did not look deep into the Accelerate's internal code and want to ask - Are there any other reasons that prevent us from a mutable array implementation? 
    Is it a time-consuming task? Would it be useful?  

I am asking that because I need to plan my time and don't want to spend it for something useless, but I would glad to make Accelerate library better!  :-) 

Thanks! 

Trevor McDonell

unread,
Feb 18, 2019, 10:47:32 AM2/18/19
to accelerat...@googlegroups.com
Hi!

Recently I thought that this might be nice as well.

Currently, we have that shapes and indices are type `Z :. Int :. Int` etc. but I think it would be nice to be able to generalise this a bit, so that it is easier to support something like `Z :. Nat :. Nat`. I haven't thought through the implications on this, but if I understand correctly this would also support what you wanted quite nicely?


2. Mutable arrays. Now (if I understand it correctly) Accelerate doesn't support it because it can't check that result's size is equal to the input array's size. 
    But with the type-safe arrays, it can! I did not look deep into the Accelerate's internal code and want to ask - Are there any other reasons that prevent us from a mutable array implementation? 
    Is it a time-consuming task? Would it be useful?  

I am asking that because I need to plan my time and don't want to spend it for something useless, but I would glad to make Accelerate library better!  :-) 

The main problem with supporting mutable arrays is that they are much more difficult to parallelise. If we wanted to support this interface we would need to think very hard about what kinds of operations should be supported (or, expose this as a different lower-level interface, with fewer guarantees on correctness).

But, it sounds like you are also thinking about, how to reuse the memory so that the results can be updated in place? At that level it isn't so important to have the extent in the type, since at that point the runtime system will have this information already (it must, in order to allocate the right amount of memory). For this use case what is needed is a precise analysis of when this is safe to do. Some of this happens already... the `permute` operation can sometimes do this in-place (but, see #432), and the runtime system knows to re-use allocations (but this is more to improve runtime system performance, not for reducing the high watermark of memory usage).

I'd be interested in hearing more about which one of these is important to you and any ideas / motivations you have in that direction.

Cheers,
-Trev

Haskell-mouse

unread,
Feb 19, 2019, 5:40:32 AM2/19/19
to Accelerate


понедельник, 18 февраля 2019 г., 18:47:32 UTC+3 пользователь Trevor L. McDonell написал:
Do you mean that Nat is a kind of type-level numbers? If yes, then it is exactly what I mean. Also, it can be just type-level list of dimensions like it is done in dimensions library
Dims '[2,7,3]

I'd be interested in hearing more about which one of these is important to you and any ideas / motivations you have in that direction.

The main interest is reducing the copying operations. It will make accelerate operations faster and it will reduce the GC working time. I think about something like ST mutable vectors, so you can write something like 

foo ::  forall x0 y0 z0 x1 y1 z1 i o s . (Size x0 y0 z0 i ~ Size x1 y1 z1 o)
 
=>  RST s (Acc (Array Dims '[x0, y0, z0] i)) -> RST s (Acc ( Array Dims '[x1, y1, z1] o))
foo marr
= do
    arr
<- marr
    sort arr
   
.... -- some more modifications
   
return $ usafeFreeze arr


bar
:: Acc (Array Dims '[x,y,z,] i) -> Acc (Array Dims '[x1,y1,z1] o)
bar arr
= RunRST $ foo (unMute arr)

Where i - is an input data format (Double, for example)
           o - an output data format (Float, for example)
           RST - is a monad like ST

Also - Accelerate arrays now can be a monad, like list (but it should look like  Array (Dim [x,y,z], a))  ;-) 
class RMonad m where
 
type RMonadCtxt m a :: Constraint
 
type RMonadCtxt m a = ()

  return :: RMonadCtxt m a => a -> m a
  (>>=) :: (RMonadCtxt m a, RMonadCtxt m b) => m a -> (a -> m b) -> m b

instance RMonad S.Set where
 
type RMonadCtxt S.Set a = Ord a
 
return
= S.singleton
  mx
>>= fxmy = S.fromList [y | x <- S.toList mx, y <- S.toList (fxmy x)]

Yes - Accelerate array now can be a monad ;-) 

Haskell-mouse

unread,
Feb 19, 2019, 5:42:37 AM2/19/19
to Accelerate
Now using foo and bar you avoid all copy operations inside the foo function

Haskell-mouse

unread,
Feb 20, 2019, 4:36:44 AM2/20/19
to Accelerate


вторник, 19 февраля 2019 г., 13:42:37 UTC+3 пользователь Haskell-mouse написал:
Now using foo and bar you avoid all copy operations inside the foo function

Ok, I read more about restricted monad and get back my words about it, because it is not monad and have many restrictions ( 
But anyway, type-safe dimensions and mutable arrays still looks useful. 

Haskell-mouse

unread,
Feb 25, 2019, 4:52:09 PM2/25/19
to Accelerate
Hi. Did I say something wrong or maybe you still have any questions? 


понедельник, 18 февраля 2019 г., 18:47:32 UTC+3 пользователь Trevor L. McDonell написал:
Hi!

Trevor McDonell

unread,
Feb 28, 2019, 7:56:54 AM2/28/19
to accelerat...@googlegroups.com
Hi!

Sorry for the slow reply. I think, I didn't have much more to add?

I think adding `Nat` as an acceptable argument to shapes is a good idea. This will effectively give us the same thing that you mention from the dimensions library; `Z` and `:.` are just type-level (snoc) lists.

About adding mutable arrays, I'm not sure will increase performance of individual operations per-se, except in the case I mentioned of permute, where you can update fewer elements. Certainly, it can help reduce GC time though. Actually, one of the main problems here (in the case of the GPU backend) is the need to call out to the external allocation function (via the FFI). So for a long time we have under-the-hood been doing some caching here, rather than calling malloc()/free() every time, which means you get a kind of double-buffering behaviour for free.

This doesn't help reduce the high water mark of memory usage, however, which can be the critical factor for some applications.

I could still be convinced though!

-Trev


--
You received this message because you are subscribed to the Google Groups "Accelerate" group.
To unsubscribe from this group and stop receiving emails from it, send an email to accelerate-hask...@googlegroups.com.
Visit this group at https://groups.google.com/group/accelerate-haskell.
For more options, visit https://groups.google.com/d/optout.
Reply all
Reply to author
Forward
0 new messages