replicateM over vectors

Hi, I'd like to be able to do replicateM, but over a vector instead of a list. Right now I'm doing this: import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed.Mutable as M replicateM n action = do mu <- M.unsafeNew n let go !i | i < n = action >>= M.unsafeWrite mu i >> go (i+1) | otherwise = G.unsafeFreeze mu go 0 I thought it might be useful to express this in terms of the available primitives, since this might fuse more easily, but I don't yet see a way to do it. Is there a better (more elegant and/or faster) way to write this? Thanks, Chad

Chad.Scherrer:
Hi,
I'd like to be able to do replicateM, but over a vector instead of a list. Right now I'm doing this:
import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed.Mutable as M replicateM n action = do mu <- M.unsafeNew n let go !i | i < n = action >>= M.unsafeWrite mu i >> go (i+1) | otherwise = G.unsafeFreeze mu go 0
I thought it might be useful to express this in terms of the available primitives, since this might fuse more easily, but I don't yet see a way to do it.
Is there a better (more elegant and/or faster) way to write this?
The way you're writing it is fine and direct, but yes, I think the challenge is to have have monadic generators that will fuse. The direct style, I'd write as: import qualified Data.Vector.Generic as G import qualified Data.Vector.Generic.Mutable as M import qualified Data.Vector.Generic.New as N import qualified Data.Vector.Fusion.Stream.Monadic as S replicateM :: (G.Vector v a) => Int -> IO a -> IO (v a) replicateM n a = do v <- M.new n fill v 0 G.unsafeFreeze v where fill v i | i < n = do x <- a M.unsafeWrite v i x fill v (i+1) | otherwise = return () But that doesn't fuse, obviously. So it seems we should be able to do something like: -- Almost there: replicateS n a = {-unsafeFreeze-} (M.unstream (S.replicate n a)) Or use Data.Vector.Generic.New, but I couldn't get the monadic action to work out, ending up in a twisty maze of PrimMonads. Roman? Can we generate frozen arrays for monadic generators, and still fuse in the current New/Mutable/MStream architecture? -- Don

On 02/04/2010, at 12:16, Don Stewart wrote:
Chad.Scherrer:
Hi,
I'd like to be able to do replicateM, but over a vector instead of a list. Right now I'm doing this:
The operation you are looking for is called newWith. It probably should be called replicate.
Roman? Can we generate frozen arrays for monadic generators, and still fuse in the current New/Mutable/MStream architecture?
For monadic stuff, fusion happens on things of type New. For instance, you could write this (I'm omitting the class contexts and Data.Vector prefixes): 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) 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 and this ought to fuse. Note that the New stuff is quite rough and only really intended for internal use at the moment. I wanted to get the "normal" APIs working properly first. Roman

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)
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) -- Don

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

Roman Leshchinskiy
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.
I'm having trouble getting this to typecheck. I'll reread your "Recycle Your Arrays" paper; maybe then it will make more sense.
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
But the "m" I'm interested in happens to be ST. Sounds like it's still easy in principle, but not immediate. Is that right? Thanks, Chad

On 04/04/2010, at 05:33, Chad Scherrer wrote:
Roman Leshchinskiy
writes: 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.
I'm having trouble getting this to typecheck. I'll reread your "Recycle Your Arrays" paper; maybe then it will make more sense.
Ugh. I shouldn't write emails while frantically scrambling to make a conference deadline. What I meant is this: replicate n action = do { v <- new n; v' <- munstream v (generate M n (const action)) } Sorry for the confusion.
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
But the "m" I'm interested in happens to be ST. Sounds like it's still easy in principle, but not immediate. Is that right?
Not really. The big step is getting from the type above to a fixed s so that you can use it in a particular ST computation. It's not just a question of making the types work, either. I also have to convince myself that it is actually safe to do so (in particular, that the rewrite rules in the library can't break things). Getting from there to IO is very easy. Roman
participants (4)
-
Chad Scherrer
-
Don Stewart
-
Roman Leshchinskiy
-
Scherrer, Chad