[Haskell-cafe] replicateM over vectors

Roman Leshchinskiy rl at cse.unsw.edu.au
Thu Apr 1 22:20:23 EDT 2010


On 02/04/2010, at 13:01, Don Stewart wrote:

> rl:
>> replicate :: Int -> a -> New a
>> replicate n x = Generic.New.unstream (Fusion.Stream.replicate n x)
>> 
>> and then either
>> 
>>  Mutable.run (replicate n x)
>> 
>> to get a mutable vector or
>> 
>>  new (replicate n x)
> 
> 
> Hmm, but here 'a' is pure. I don't think he wants
> 
>    newWith :: (PrimMonad m, MVector v a) => Int -> a -> m (v (PrimState m) a)
> 
> but more:
> 
>    newWithM :: (PrimMonad m, MVector v a) => Int -> m a -> m (v (PrimState m) a)

Ah. I missed that. Then your best bet is probably

replicate n action = munstream v $ Fusion.Stream.Monadic.generateM n (const action)
                                 $ new n

It's uglier that it should be but vector simply doesn't define the right combinators for this at the moment.

>> to get an immutable one. You could also chain operations on New, including monadic ones:
>> 
>>  v <- Mutable.run $ Generic.New.transform (Fusion.Stream.Monadic.mapM f)
>>                   $ replicate n x
>> 
> 
> Oh, that's interesting. But what if we want to fill directly with the monadic action?
> We wouldn't
> 
>    mapM (const a) $ replicate n undefined 
> 
> So how do we best do a fusible, e.g.:
> 
>    replicateM :: G.Vector v a => Int -> IO a -> IO (v a)

There are two things one would have to do. First, add a function to Generic.New which initialises a New from a Monadic.Stream and fusion rules for it. That's easy. The hard part is to generalise New to work with arbitrary monads: at the moment it is defined as:

data New a = New (forall mv s. MVector mv a => ST s (mv s a))

This is because its basic reason for existence is to be passed to Vector.new which then does a runST to produce an immutable vector. It is perhaps possible to make New more general but it's quite tricky. I'll think about it after the ICFP deadline :-)

Roman




More information about the Haskell-Cafe mailing list