Get 'replicateM' to specialize

This commit is contained in:
Artyom Kazak 2019-07-24 00:09:50 +03:00
parent 7c6eac87b0
commit 3d1ed1267c

View File

@ -273,7 +273,7 @@ import qualified Control.Monad.Catch as MC
import Streamly.Mem.Array.Types (Array(..))
import Streamly.Fold.Types (Fold(..))
import Streamly.Pipe.Types (Pipe(..), PipeState(..))
import Streamly.SVar (MonadAsync, defState, adaptState)
import Streamly.SVar (MonadAsync, defState, adaptState, State)
import Streamly.Streams.StreamD.Type
@ -366,10 +366,11 @@ repeat :: Monad m => a -> Stream m a
repeat x = Stream (\_ _ -> return $ Yield x ()) ()
{-# INLINE_NORMAL replicateM #-}
replicateM :: Monad m => Int -> m a -> Stream m a
replicateM :: forall m a. Monad m => Int -> m a -> Stream m a
replicateM n p = Stream step n
where
{-# INLINE_LATE step #-}
step :: State K.Stream m a -> Int -> m (Step Int a)
step _ i | i <= 0 = return Stop
| otherwise = do
x <- p