{-# LANGUAGE RankNTypes, Trustworthy #-}
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
module Pipes.Prelude (
stdinLn
, readLn
, fromHandle
, repeatM
, replicateM
, unfoldr
, stdoutLn
, stdoutLn'
, mapM_
, print
, toHandle
, drain
, map
, mapM
, sequence
, mapFoldable
, filter
, mapMaybe
, filterM
, wither
, take
, takeWhile
, takeWhile'
, drop
, dropWhile
, concat
, elemIndices
, findIndices
, scan
, scanM
, chain
, read
, show
, seq
, loop
, fold
, fold'
, foldM
, foldM'
, all
, any
, and
, or
, elem
, notElem
, find
, findIndex
, head
, index
, last
, length
, maximum
, minimum
, null
, sum
, product
, toList
, toListM
, toListM'
, zip
, zipWith
, tee
, generalize
) where
import Control.Exception (throwIO, try)
import Control.Monad (liftM, when, unless, (>=>))
import Control.Monad.Trans.State.Strict (get, put)
import Data.Functor.Identity (Identity, runIdentity)
import Foreign.C.Error (Errno(Errno), ePIPE)
import GHC.Exts (build)
import Pipes
import Pipes.Core
import Pipes.Internal
import Pipes.Lift (evalStateP)
import qualified GHC.IO.Exception as G
import qualified System.IO as IO
import qualified Prelude
import Prelude hiding (
all
, and
, any
, concat
, drop
, dropWhile
, elem
, filter
, head
, last
, length
, map
, mapM
, mapM_
, maximum
, minimum
, notElem
, null
, or
, print
, product
, read
, readLn
, sequence
, show
, seq
, sum
, take
, takeWhile
, zip
, zipWith
)
stdinLn :: MonadIO m => Producer' String m ()
stdinLn = fromHandle IO.stdin
{-# INLINABLE stdinLn #-}
readLn :: (MonadIO m, Read a) => Producer' a m ()
readLn = stdinLn >-> read
{-# INLINABLE readLn #-}
fromHandle :: MonadIO m => IO.Handle -> Producer' String m ()
fromHandle h = go
where
go = do
eof <- liftIO $ IO.hIsEOF h
unless eof $ do
str <- liftIO $ IO.hGetLine h
yield str
go
{-# INLINABLE fromHandle #-}
repeatM :: Monad m => m a -> Producer' a m r
repeatM m = lift m >~ cat
{-# INLINABLE [1] repeatM #-}
{-# RULES
"repeatM m >-> p" forall m p . repeatM m >-> p = lift m >~ p
#-}
replicateM :: Monad m => Int -> m a -> Producer' a m ()
replicateM n m = lift m >~ take n
{-# INLINABLE replicateM #-}
stdoutLn :: MonadIO m => Consumer' String m ()
stdoutLn = go
where
go = do
str <- await
x <- liftIO $ try (putStrLn str)
case x of
Left (G.IOError { G.ioe_type = G.ResourceVanished
, G.ioe_errno = Just ioe })
| Errno ioe == ePIPE
-> return ()
Left e -> liftIO (throwIO e)
Right () -> go
{-# INLINABLE stdoutLn #-}
stdoutLn' :: MonadIO m => Consumer' String m r
stdoutLn' = for cat (\str -> liftIO (putStrLn str))
{-# INLINABLE [1] stdoutLn' #-}
{-# RULES
"p >-> stdoutLn'" forall p .
p >-> stdoutLn' = for p (\str -> liftIO (putStrLn str))
#-}
mapM_ :: Monad m => (a -> m ()) -> Consumer' a m r
mapM_ f = for cat (\a -> lift (f a))
{-# INLINABLE [1] mapM_ #-}
{-# RULES
"p >-> mapM_ f" forall p f .
p >-> mapM_ f = for p (\a -> lift (f a))
#-}
print :: (MonadIO m, Show a) => Consumer' a m r
print = for cat (\a -> liftIO (Prelude.print a))
{-# INLINABLE [1] print #-}
{-# RULES
"p >-> print" forall p .
p >-> print = for p (\a -> liftIO (Prelude.print a))
#-}
toHandle :: MonadIO m => IO.Handle -> Consumer' String m r
toHandle handle = for cat (\str -> liftIO (IO.hPutStrLn handle str))
{-# INLINABLE [1] toHandle #-}
{-# RULES
"p >-> toHandle handle" forall p handle .
p >-> toHandle handle = for p (\str -> liftIO (IO.hPutStrLn handle str))
#-}
drain :: Functor m => Consumer' a m r
drain = for cat discard
{-# INLINABLE [1] drain #-}
{-# RULES
"p >-> drain" forall p .
p >-> drain = for p discard
#-}
map :: Functor m => (a -> b) -> Pipe a b m r
map f = for cat (\a -> yield (f a))
{-# INLINABLE [1] map #-}
{-# RULES
"p >-> map f" forall p f . p >-> map f = for p (\a -> yield (f a))
; "map f >-> p" forall p f . map f >-> p = (do
a <- await
return (f a) ) >~ p
#-}
mapM :: Monad m => (a -> m b) -> Pipe a b m r
mapM f = for cat $ \a -> do
b <- lift (f a)
yield b
{-# INLINABLE [1] mapM #-}
{-# RULES
"p >-> mapM f" forall p f . p >-> mapM f = for p (\a -> do
b <- lift (f a)
yield b )
; "mapM f >-> p" forall p f . mapM f >-> p = (do
a <- await
b <- lift (f a)
return b ) >~ p
#-}
sequence :: Monad m => Pipe (m a) a m r
sequence = mapM id
{-# INLINABLE sequence #-}
mapFoldable :: (Functor m, Foldable t) => (a -> t b) -> Pipe a b m r
mapFoldable f = for cat (\a -> each (f a))
{-# INLINABLE [1] mapFoldable #-}
{-# RULES
"p >-> mapFoldable f" forall p f .
p >-> mapFoldable f = for p (\a -> each (f a))
#-}
filter :: Functor m => (a -> Bool) -> Pipe a a m r
filter predicate = for cat $ \a -> when (predicate a) (yield a)
{-# INLINABLE [1] filter #-}
{-# RULES
"p >-> filter predicate" forall p predicate.
p >-> filter predicate = for p (\a -> when (predicate a) (yield a))
#-}
mapMaybe :: Functor m => (a -> Maybe b) -> Pipe a b m r
mapMaybe f = for cat $ maybe (pure ()) yield . f
{-# INLINABLE [1] mapMaybe #-}
{-# RULES
"p >-> mapMaybe f" forall p f.
p >-> mapMaybe f = for p $ maybe (pure ()) yield . f
#-}
filterM :: Monad m => (a -> m Bool) -> Pipe a a m r
filterM predicate = for cat $ \a -> do
b <- lift (predicate a)
when b (yield a)
{-# INLINABLE [1] filterM #-}
{-# RULES
"p >-> filterM predicate" forall p predicate .
p >-> filterM predicate = for p (\a -> do
b <- lift (predicate a)
when b (yield a) )
#-}
wither :: Monad m => (a -> m (Maybe b)) -> Pipe a b m r
wither f = for cat $ lift . f >=> maybe (pure ()) yield
{-# INLINABLE [1] wither #-}
{-# RULES
"p >-> wither f" forall p f .
p >-> wither f = for p $ lift . f >=> maybe (pure ()) yield
#-}
take :: Functor m => Int -> Pipe a a m ()
take = go
where
go 0 = return ()
go n = do
a <- await
yield a
go (n-1)
{-# INLINABLE take #-}
takeWhile :: Functor m => (a -> Bool) -> Pipe a a m ()
takeWhile predicate = go
where
go = do
a <- await
if (predicate a)
then do
yield a
go
else return ()
{-# INLINABLE takeWhile #-}
takeWhile' :: Functor m => (a -> Bool) -> Pipe a a m a
takeWhile' predicate = go
where
go = do
a <- await
if (predicate a)
then do
yield a
go
else return a
{-# INLINABLE takeWhile' #-}
drop :: Functor m => Int -> Pipe a a m r
drop = go
where
go 0 = cat
go n = do
await
go (n-1)
{-# INLINABLE drop #-}
dropWhile :: Functor m => (a -> Bool) -> Pipe a a m r
dropWhile predicate = go
where
go = do
a <- await
if (predicate a)
then go
else do
yield a
cat
{-# INLINABLE dropWhile #-}
concat :: (Functor m, Foldable f) => Pipe (f a) a m r
concat = for cat each
{-# INLINABLE [1] concat #-}
{-# RULES
"p >-> concat" forall p . p >-> concat = for p each
#-}
elemIndices :: (Functor m, Eq a) => a -> Pipe a Int m r
elemIndices a = findIndices (a ==)
{-# INLINABLE elemIndices #-}
findIndices :: Functor m => (a -> Bool) -> Pipe a Int m r
findIndices predicate = go 0
where
go n = do
a <- await
when (predicate a) (yield n)
go $! n + 1
{-# INLINABLE findIndices #-}
scan :: Functor m => (x -> a -> x) -> x -> (x -> b) -> Pipe a b m r
scan step begin done = go begin
where
go x = do
yield (done x)
a <- await
let x' = step x a
go $! x'
{-# INLINABLE scan #-}
scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Pipe a b m r
scanM step begin done = do
x <- lift begin
go x
where
go x = do
b <- lift (done x)
yield b
a <- await
x' <- lift (step x a)
go $! x'
{-# INLINABLE scanM #-}
chain :: Monad m => (a -> m ()) -> Pipe a a m r
chain f = for cat $ \a -> do
lift (f a)
yield a
{-# INLINABLE [1] chain #-}
{-# RULES
"p >-> chain f" forall p f .
p >-> chain f = for p (\a -> do
lift (f a)
yield a )
; "chain f >-> p" forall p f .
chain f >-> p = (do
a <- await
lift (f a)
return a ) >~ p
#-}
read :: (Functor m, Read a) => Pipe String a m r
read = for cat $ \str -> case (reads str) of
[(a, "")] -> yield a
_ -> return ()
{-# INLINABLE [1] read #-}
{-# RULES
"p >-> read" forall p .
p >-> read = for p (\str -> case (reads str) of
[(a, "")] -> yield a
_ -> return () )
#-}
show :: (Functor m, Show a) => Pipe a String m r
show = map Prelude.show
{-# INLINABLE show #-}
seq :: Functor m => Pipe a a m r
seq = for cat $ \a -> yield $! a
{-# INLINABLE seq #-}
loop :: Monad m => (a -> ListT m b) -> Pipe a b m r
loop k = for cat (every . k)
{-# INLINABLE loop #-}
fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
fold step begin done p0 = go p0 begin
where
go p x = case p of
Request v _ -> closed v
Respond a fu -> go (fu ()) $! step x a
M m -> m >>= \p' -> go p' x
Pure _ -> return (done x)
{-# INLINABLE fold #-}
fold' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Producer a m r -> m (b, r)
fold' step begin done p0 = go p0 begin
where
go p x = case p of
Request v _ -> closed v
Respond a fu -> go (fu ()) $! step x a
M m -> m >>= \p' -> go p' x
Pure r -> return (done x, r)
{-# INLINABLE fold' #-}
foldM
:: Monad m
=> (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
foldM step begin done p0 = do
x0 <- begin
go p0 x0
where
go p x = case p of
Request v _ -> closed v
Respond a fu -> do
x' <- step x a
go (fu ()) $! x'
M m -> m >>= \p' -> go p' x
Pure _ -> done x
{-# INLINABLE foldM #-}
foldM'
:: Monad m
=> (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m r -> m (b, r)
foldM' step begin done p0 = do
x0 <- begin
go p0 x0
where
go p x = case p of
Request v _ -> closed v
Respond a fu -> do
x' <- step x a
go (fu ()) $! x'
M m -> m >>= \p' -> go p' x
Pure r -> do
b <- done x
return (b, r)
{-# INLINABLE foldM' #-}
all :: Monad m => (a -> Bool) -> Producer a m () -> m Bool
all predicate p = null $ p >-> filter (\a -> not (predicate a))
{-# INLINABLE all #-}
any :: Monad m => (a -> Bool) -> Producer a m () -> m Bool
any predicate p = liftM not $ null (p >-> filter predicate)
{-# INLINABLE any #-}
and :: Monad m => Producer Bool m () -> m Bool
and = all id
{-# INLINABLE and #-}
or :: Monad m => Producer Bool m () -> m Bool
or = any id
{-# INLINABLE or #-}
elem :: (Monad m, Eq a) => a -> Producer a m () -> m Bool
elem a = any (a ==)
{-# INLINABLE elem #-}
notElem :: (Monad m, Eq a) => a -> Producer a m () -> m Bool
notElem a = all (a /=)
{-# INLINABLE notElem #-}
find :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe a)
find predicate p = head (p >-> filter predicate)
{-# INLINABLE find #-}
findIndex :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe Int)
findIndex predicate p = head (p >-> findIndices predicate)
{-# INLINABLE findIndex #-}
head :: Monad m => Producer a m () -> m (Maybe a)
head p = do
x <- next p
return $ case x of
Left _ -> Nothing
Right (a, _) -> Just a
{-# INLINABLE head #-}
index :: Monad m => Int -> Producer a m () -> m (Maybe a)
index n p = head (p >-> drop n)
{-# INLINABLE index #-}
last :: Monad m => Producer a m () -> m (Maybe a)
last p0 = do
x <- next p0
case x of
Left _ -> return Nothing
Right (a, p') -> go a p'
where
go a p = do
x <- next p
case x of
Left _ -> return (Just a)
Right (a', p') -> go a' p'
{-# INLINABLE last #-}
length :: Monad m => Producer a m () -> m Int
length = fold (\n _ -> n + 1) 0 id
{-# INLINABLE length #-}
maximum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)
maximum = fold step Nothing id
where
step x a = Just $ case x of
Nothing -> a
Just a' -> max a a'
{-# INLINABLE maximum #-}
minimum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)
minimum = fold step Nothing id
where
step x a = Just $ case x of
Nothing -> a
Just a' -> min a a'
{-# INLINABLE minimum #-}
null :: Monad m => Producer a m () -> m Bool
null p = do
x <- next p
return $ case x of
Left _ -> True
Right _ -> False
{-# INLINABLE null #-}
sum :: (Monad m, Num a) => Producer a m () -> m a
sum = fold (+) 0 id
{-# INLINABLE sum #-}
product :: (Monad m, Num a) => Producer a m () -> m a
product = fold (*) 1 id
{-# INLINABLE product #-}
toList :: Producer a Identity () -> [a]
toList prod0 = build (go prod0)
where
go prod cons nil =
case prod of
Request v _ -> closed v
Respond a fu -> cons a (go (fu ()) cons nil)
M m -> go (runIdentity m) cons nil
Pure _ -> nil
{-# INLINE toList #-}
toListM :: Monad m => Producer a m () -> m [a]
toListM = fold step begin done
where
step x a = x . (a:)
begin = id
done x = x []
{-# INLINABLE toListM #-}
toListM' :: Monad m => Producer a m r -> m ([a], r)
toListM' = fold' step begin done
where
step x a = x . (a:)
begin = id
done x = x []
{-# INLINABLE toListM' #-}
zip :: Monad m
=> (Producer a m r)
-> (Producer b m r)
-> (Producer' (a, b) m r)
zip = zipWith (,)
{-# INLINABLE zip #-}
zipWith :: Monad m
=> (a -> b -> c)
-> (Producer a m r)
-> (Producer b m r)
-> (Producer' c m r)
zipWith f = go
where
go p1 p2 = do
e1 <- lift $ next p1
case e1 of
Left r -> return r
Right (a, p1') -> do
e2 <- lift $ next p2
case e2 of
Left r -> return r
Right (b, p2') -> do
yield (f a b)
go p1' p2'
{-# INLINABLE zipWith #-}
tee :: Monad m => Consumer a m r -> Pipe a a m r
tee p = evalStateP Nothing $ do
r <- up >\\ (hoist lift p //> dn)
ma <- lift get
case ma of
Nothing -> return ()
Just a -> yield a
return r
where
up () = do
ma <- lift get
case ma of
Nothing -> return ()
Just a -> yield a
a <- await
lift $ put (Just a)
return a
dn v = closed v
{-# INLINABLE tee #-}
generalize :: Monad m => Pipe a b m r -> x -> Proxy x a x b m r
generalize p x0 = evalStateP x0 $ up >\\ hoist lift p //> dn
where
up () = do
x <- lift get
request x
dn a = do
x <- respond a
lift $ put x
{-# INLINABLE generalize #-}
unfoldr :: Monad m
=> (s -> m (Either r (a, s))) -> s -> Producer a m r
unfoldr step = go where
go s0 = do
e <- lift (step s0)
case e of
Left r -> return r
Right (a,s) -> do
yield a
go s
{-# INLINABLE unfoldr #-}