{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Streaming.Prelude (
Of (..)
, yield
, each
, stdinLn
, readLn
, fromHandle
, readFile
, iterate
, iterateM
, repeat
, repeatM
, replicate
, untilLeft
, untilRight
, cycle
, replicateM
, enumFrom
, enumFromThen
, unfoldr
, stdoutLn
, stdoutLn'
, mapM_
, print
, toHandle
, writeFile
, effects
, erase
, drained
, map
, mapM
, maps
, mapsPost
, mapped
, mappedPost
, for
, with
, subst
, copy
, duplicate
, store
, chain
, sequence
, nubOrd
, nubOrdOn
, nubInt
, nubIntOn
, filter
, filterM
, mapMaybeM
, delay
, intersperse
, take
, takeWhile
, takeWhileM
, drop
, dropWhile
, concat
, scan
, scanM
, scanned
, read
, show
, cons
, slidingWindow
, slidingWindowMin
, slidingWindowMinBy
, slidingWindowMinOn
, slidingWindowMax
, slidingWindowMaxBy
, slidingWindowMaxOn
, wrapEffect
, next
, uncons
, splitAt
, split
, breaks
, break
, breakWhen
, span
, group
, groupBy
, distinguish
, switch
, separate
, unseparate
, eitherToSum
, sumToEither
, sumToCompose
, composeToSum
, fold
, fold_
, foldM
, foldM_
, foldMap
, foldMap_
, all
, all_
, any
, any_
, sum
, sum_
, product
, product_
, head
, head_
, last
, last_
, elem
, elem_
, notElem
, notElem_
, length
, length_
, toList
, toList_
, mconcat
, mconcat_
, minimum
, minimum_
, maximum
, maximum_
, foldrM
, foldrT
, zip
, zipWith
, zip3
, zipWith3
, unzip
, partitionEithers
, partition
, merge
, mergeOn
, mergeBy
, catMaybes
, mapMaybe
, lazily
, strictly
, fst'
, snd'
, mapOf
, _first
, _second
, reread
, Stream
) where
import Streaming.Internal
import Control.Applicative (Applicative (..))
import Control.Concurrent (threadDelay)
import Control.Exception (throwIO, try)
import Control.Monad hiding (filterM, mapM, mapM_, foldM, foldM_, replicateM, sequence)
import Control.Monad.Trans
import Data.Functor (Functor (..), (<$))
import Data.Functor.Compose
import Data.Functor.Identity
import Data.Functor.Of
import Data.Functor.Sum
import Data.Monoid (Monoid (mappend, mempty))
import Data.Ord (Ordering (..), comparing)
import Foreign.C.Error (Errno(Errno), ePIPE)
import Text.Read (readMaybe)
import qualified Data.Foldable as Foldable
import qualified Data.IntSet as IntSet
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import Data.Word (Word64)
import qualified GHC.IO.Exception as G
import qualified Prelude
import qualified System.IO as IO
import Prelude hiding (map, mapM, mapM_, filter, drop, dropWhile, take, mconcat
, sum, product, iterate, repeat, cycle, replicate, splitAt
, takeWhile, enumFrom, enumFromTo, enumFromThen, length
, print, zipWith, zip, zipWith3, zip3, unzip, seq, show, read
, readLn, sequence, concat, span, break, readFile, writeFile
, minimum, maximum, elem, notElem, all, any, head
, last, foldMap)
lazily :: Of a b -> (a,b)
lazily :: Of a b -> (a, b)
lazily = \(a
a:>b
b) -> (a
a,b
b)
{-# INLINE lazily #-}
strictly :: (a,b) -> Of a b
strictly :: (a, b) -> Of a b
strictly = \(a
a,b
b) -> a
a a -> b -> Of a b
forall a b. a -> b -> Of a b
:> b
b
{-# INLINE strictly #-}
fst' :: Of a b -> a
fst' :: Of a b -> a
fst' (a
a :> b
_) = a
a
{-# INLINE fst' #-}
snd' :: Of a b -> b
snd' :: Of a b -> b
snd' (a
_ :> b
b) = b
b
{-# INLINE snd' #-}
mapOf :: (a -> b) -> Of a r -> Of b r
mapOf :: (a -> b) -> Of a r -> Of b r
mapOf a -> b
f (a
a :> r
b) = a -> b
f a
a b -> r -> Of b r
forall a b. a -> b -> Of a b
:> r
b
{-# INLINE mapOf #-}
_first :: Functor f => (a -> f a') -> Of a b -> f (Of a' b)
_first :: (a -> f a') -> Of a b -> f (Of a' b)
_first a -> f a'
afb (a
a :> b
b) = (a' -> Of a' b) -> f a' -> f (Of a' b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a'
c -> a'
c a' -> b -> Of a' b
forall a b. a -> b -> Of a b
:> b
b) (a -> f a'
afb a
a)
{-# INLINE _first #-}
_second :: Functor f => (b -> f b') -> Of a b -> f (Of a b')
_second :: (b -> f b') -> Of a b -> f (Of a b')
_second b -> f b'
afb (a
a :> b
b) = (b' -> Of a b') -> f b' -> f (Of a b')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\b'
c -> a
a a -> b' -> Of a b'
forall a b. a -> b -> Of a b
:> b'
c) (b -> f b'
afb b
b)
{-# INLINABLE _second #-}
all :: Monad m => (a -> Bool) -> Stream (Of a) m r -> m (Of Bool r)
all :: (a -> Bool) -> Stream (Of a) m r -> m (Of Bool r)
all a -> Bool
thus = Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True where
loop :: Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
b Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
b Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of Bool r)) -> m (Of Bool r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
b
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thus a
a
then Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True Stream (Of a) m r
rest
else do
r
r <- Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
rest
Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
{-# INLINABLE all #-}
all_ :: Monad m => (a -> Bool) -> Stream (Of a) m r -> m Bool
all_ :: (a -> Bool) -> Stream (Of a) m r -> m Bool
all_ a -> Bool
thus = Bool -> Stream (Of a) m r -> m Bool
loop Bool
True where
loop :: Bool -> Stream (Of a) m r -> m Bool
loop Bool
b Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
b
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m Bool) -> m Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m Bool
loop Bool
b
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thus a
a
then Bool -> Stream (Of a) m r -> m Bool
loop Bool
True Stream (Of a) m r
rest
else Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
{-# INLINABLE all_ #-}
any :: Monad m => (a -> Bool) -> Stream (Of a) m r -> m (Of Bool r)
any :: (a -> Bool) -> Stream (Of a) m r -> m (Of Bool r)
any a -> Bool
thus = Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False where
loop :: Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
b Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
b Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of Bool r)) -> m (Of Bool r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
b
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thus a
a
then do
r
r <- Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
rest
Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
else Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False Stream (Of a) m r
rest
{-# INLINABLE any #-}
any_ :: Monad m => (a -> Bool) -> Stream (Of a) m r -> m Bool
any_ :: (a -> Bool) -> Stream (Of a) m r -> m Bool
any_ a -> Bool
thus = Bool -> Stream (Of a) m r -> m Bool
loop Bool
False where
loop :: Bool -> Stream (Of a) m r -> m Bool
loop Bool
b Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
b
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m Bool) -> m Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m Bool
loop Bool
b
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thus a
a
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else Bool -> Stream (Of a) m r -> m Bool
loop Bool
False Stream (Of a) m r
rest
{-# INLINABLE any_ #-}
break :: Monad m => (a -> Bool) -> Stream (Of a) m r
-> Stream (Of a) m (Stream (Of a) m r)
break :: (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
break a -> Bool
thePred = Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m r) -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thePred a
a
then Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
rest))
else Of a (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Of a) m r)
-> Of a (Stream (Of a) m (Stream (Of a) m r))
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
rest)
{-# INLINABLE break #-}
breakWhen :: Monad m => (x -> a -> x) -> x -> (x -> b) -> (b -> Bool) -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
breakWhen :: (x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
-> Stream (Of a) m (Stream (Of a) m r)
breakWhen x -> a -> x
step x
begin x -> b
done b -> Bool
thePred = x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop0 x
begin
where
loop0 :: x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop0 x
x Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Stream (Of a) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r)
Effect m (Stream (Of a) m r)
mn -> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m r) -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop0 x
x) m (Stream (Of a) m r)
mn
Step (a
a :> Stream (Of a) m r
rest) -> a -> x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop a
a (x -> a -> x
step x
x a
a) Stream (Of a) m r
rest
loop :: a -> x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop a
a !x
x Stream (Of a) m r
stream =
if b -> Bool
thePred (x -> b
done x
x)
then Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a Stream (Of a) m () -> Stream (Of a) m r -> Stream (Of a) m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Stream (Of a) m r
stream)
else case Stream (Of a) m r
stream of
Return r
r -> a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a Stream (Of a) m ()
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Stream (Of a) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r)
Effect m (Stream (Of a) m r)
mn -> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m r) -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop a
a x
x) m (Stream (Of a) m r)
mn
Step (a
a' :> Stream (Of a) m r
rest) -> do
a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a
a -> x -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop a
a' (x -> a -> x
step x
x a
a') Stream (Of a) m r
rest
{-# INLINABLE breakWhen #-}
breaks
:: Monad m =>
(a -> Bool) -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
breaks :: (a -> Bool) -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
breaks a -> Bool
thus = Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop where
loop :: Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r)
-> m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r
forall a b. (a -> b) -> a -> b
$ do
Either r (a, Stream (Of a) m r)
e <- Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m r
stream
Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r))
-> Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r)
forall a b. (a -> b) -> a -> b
$ case Either r (a, Stream (Of a) m r)
e of
Left r
r -> r -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Right (a
a, Stream (Of a) m r
p') ->
if Bool -> Bool
not (a -> Bool
thus a
a)
then Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r)
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Stream (Of a) m) m r)
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop (a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a Stream (Of a) m ()
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
break a -> Bool
thus Stream (Of a) m r
p')
else Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
p'
{-# INLINABLE breaks #-}
chain :: Monad m => (a -> m y) -> Stream (Of a) m r -> Stream (Of a) m r
chain :: (a -> m y) -> Stream (Of a) m r -> Stream (Of a) m r
chain a -> m y
f = Stream (Of a) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of a) m r)
mn -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m r
loop m (Stream (Of a) m r)
mn)
Step (a
a :> Stream (Of a) m r
rest) -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ do
y
_ <- a -> m y
f a
a
Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
rest))
{-# INLINABLE chain #-}
concat :: (Monad m, Foldable.Foldable f) => Stream (Of (f a)) m r -> Stream (Of a) m r
concat :: Stream (Of (f a)) m r -> Stream (Of a) m r
concat = Stream (Of (f a)) m r -> Stream (Of a) m r
forall (m :: * -> *) (t :: * -> *) a r.
(Functor m, Foldable t) =>
Stream (Of (t a)) m r -> Stream (Of a) m r
loop
where
loop :: Stream (Of (t a)) m r -> Stream (Of a) m r
loop Stream (Of (t a)) m r
str = case Stream (Of (t a)) m r
str of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of (t a)) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of (t a)) m r -> Stream (Of a) m r)
-> m (Stream (Of (t a)) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of (t a)) m r -> Stream (Of a) m r
loop m (Stream (Of (t a)) m r)
m)
Step (t a
lst :> Stream (Of (t a)) m r
as) ->
let inner :: [a] -> Stream (Of a) m r
inner [] = Stream (Of (t a)) m r -> Stream (Of a) m r
loop Stream (Of (t a)) m r
as
inner (a
x:[a]
rest) = Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
x a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> [a] -> Stream (Of a) m r
inner [a]
rest)
in [a] -> Stream (Of a) m r
inner (t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList t a
lst)
{-# INLINABLE concat #-}
cons :: (Monad m) => a -> Stream (Of a) m r -> Stream (Of a) m r
cons :: a -> Stream (Of a) m r -> Stream (Of a) m r
cons a
a Stream (Of a) m r
str = Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
str)
{-# INLINE cons #-}
cycle :: (Monad m, Functor f) => Stream f m r -> Stream f m s
cycle :: Stream f m r -> Stream f m s
cycle Stream f m r
str = Stream f m s
loop where loop :: Stream f m s
loop = Stream f m r
str Stream f m r -> Stream f m s -> Stream f m s
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Stream f m s
loop
{-# INLINABLE cycle #-}
delay :: MonadIO m => Double -> Stream (Of a) m r -> Stream (Of a) m r
delay :: Double -> Stream (Of a) m r -> Stream (Of a) m r
delay Double
seconds = Stream (Of a) m r -> Stream (Of a) m r
loop where
pico :: Int
pico = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
truncate (Double
seconds Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000)
loop :: Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
str = do
Either r (a, Stream (Of a) m r)
e <- m (Either r (a, Stream (Of a) m r))
-> Stream (Of a) m (Either r (a, Stream (Of a) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either r (a, Stream (Of a) m r))
-> Stream (Of a) m (Either r (a, Stream (Of a) m r)))
-> m (Either r (a, Stream (Of a) m r))
-> Stream (Of a) m (Either r (a, Stream (Of a) m r))
forall a b. (a -> b) -> a -> b
$ Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m r
str
case Either r (a, Stream (Of a) m r)
e of
Left r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Right (a
a,Stream (Of a) m r
rest) -> do
a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a
IO () -> Stream (Of a) m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Stream (Of a) m ()) -> IO () -> Stream (Of a) m ()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
pico
Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
rest
{-# INLINABLE delay #-}
drained :: (Monad m, Monad (t m), MonadTrans t) => t m (Stream (Of a) m r) -> t m r
drained :: t m (Stream (Of a) m r) -> t m r
drained t m (Stream (Of a) m r)
tms = t m (Stream (Of a) m r)
tms t m (Stream (Of a) m r) -> (Stream (Of a) m r -> t m r) -> t m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= m r -> t m r
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m r -> t m r)
-> (Stream (Of a) m r -> m r) -> Stream (Of a) m r -> t m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects
{-# INLINE drained #-}
drop :: (Monad m) => Int -> Stream (Of a) m r -> Stream (Of a) m r
drop :: Int -> Stream (Of a) m r -> Stream (Of a) m r
drop Int
n Stream (Of a) m r
str | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Stream (Of a) m r
str
drop Int
n Stream (Of a) m r
str = Int -> Stream (Of a) m r -> Stream (Of a) m r
forall a (m :: * -> *) a r.
(Eq a, Num a, Functor m) =>
a -> Stream (Of a) m r -> Stream (Of a) m r
loop Int
n Stream (Of a) m r
str where
loop :: a -> Stream (Of a) m r -> Stream (Of a) m r
loop a
0 Stream (Of a) m r
stream = Stream (Of a) m r
stream
loop a
m Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
ma -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> Stream (Of a) m r -> Stream (Of a) m r
loop a
m) m (Stream (Of a) m r)
ma)
Step (a
_ :> Stream (Of a) m r
as) -> a -> Stream (Of a) m r -> Stream (Of a) m r
loop (a
ma -> a -> a
forall a. Num a => a -> a -> a
-a
1) Stream (Of a) m r
as
{-# INLINABLE drop #-}
dropWhile :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r
dropWhile :: (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r
dropWhile a -> Bool
thePred = Stream (Of a) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
ma -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m r
loop m (Stream (Of a) m r)
ma)
Step (a
a :> Stream (Of a) m r
as) -> if a -> Bool
thePred a
a
then Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
as
else Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
as)
{-# INLINABLE dropWhile #-}
each :: (Monad m, Foldable.Foldable f) => f a -> Stream (Of a) m ()
each :: f a -> Stream (Of a) m ()
each = (a -> Stream (Of a) m () -> Stream (Of a) m ())
-> Stream (Of a) m () -> f a -> Stream (Of a) m ()
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr (\a
a Stream (Of a) m ()
p -> Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Stream (Of a) m ()
p)) (() -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ())
{-# INLINABLE each #-}
effects :: Monad m => Stream (Of a) m r -> m r
effects :: Stream (Of a) m r -> m r
effects = Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
loop where
loop :: Stream (Of a) m a -> m a
loop Stream (Of a) m a
stream = case Stream (Of a) m a
stream of
Return a
r -> a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
Effect m (Stream (Of a) m a)
m -> m (Stream (Of a) m a)
m m (Stream (Of a) m a) -> (Stream (Of a) m a -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m a -> m a
loop
Step (a
_ :> Stream (Of a) m a
rest) -> Stream (Of a) m a -> m a
loop Stream (Of a) m a
rest
{-# INLINABLE effects #-}
wrapEffect :: (Monad m, Functor f) => m a -> (a -> m y) -> Stream f m r -> Stream f m r
wrapEffect :: m a -> (a -> m y) -> Stream f m r -> Stream f m r
wrapEffect m a
m a -> m y
f = Stream f m r -> Stream f m r
loop where
loop :: Stream f m r -> Stream f m r
loop Stream f m r
stream = do
a
x <- m a -> Stream f m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m a
m
Either r (f (Stream f m r))
step <- m (Either r (f (Stream f m r)))
-> Stream f m (Either r (f (Stream f m r)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either r (f (Stream f m r)))
-> Stream f m (Either r (f (Stream f m r))))
-> m (Either r (f (Stream f m r)))
-> Stream f m (Either r (f (Stream f m r)))
forall a b. (a -> b) -> a -> b
$ Stream f m r -> m (Either r (f (Stream f m r)))
forall (m :: * -> *) (f :: * -> *) r.
Monad m =>
Stream f m r -> m (Either r (f (Stream f m r)))
inspect Stream f m r
stream
y
_ <- m y -> Stream f m y
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m y -> Stream f m y) -> m y -> Stream f m y
forall a b. (a -> b) -> a -> b
$ a -> m y
f a
x
(r -> Stream f m r)
-> (f (Stream f m r) -> Stream f m r)
-> Either r (f (Stream f m r))
-> Stream f m r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either r -> Stream f m r
forall (f :: * -> *) a. Applicative f => a -> f a
pure f (Stream f m r) -> Stream f m r
loop' Either r (f (Stream f m r))
step
loop' :: f (Stream f m r) -> Stream f m r
loop' f (Stream f m r)
stream = f (Stream f m r) -> Stream f m r
forall (m :: * -> *) (f :: * -> *) r.
(Monad m, Functor f) =>
f (Stream f m r) -> Stream f m r
wrap ((Stream f m r -> Stream f m r)
-> f (Stream f m r) -> f (Stream f m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream f m r -> Stream f m r
loop f (Stream f m r)
stream)
elem :: (Monad m, Eq a) => a -> Stream (Of a) m r -> m (Of Bool r)
elem :: a -> Stream (Of a) m r -> m (Of Bool r)
elem a
a' = Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False where
loop :: Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True Stream (Of a) m r
str = (r -> Of Bool r) -> m r -> m (Of Bool r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bool
True Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:>) (Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
str)
loop Bool
False Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of Bool r)) -> m (Of Bool r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False
Step (a
a:> Stream (Of a) m r
rest) ->
if a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a'
then (r -> Of Bool r) -> m r -> m (Of Bool r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bool
True Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:>) (Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
rest)
else Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False Stream (Of a) m r
rest
{-# INLINABLE elem #-}
elem_ :: (Monad m, Eq a) => a -> Stream (Of a) m r -> m Bool
elem_ :: a -> Stream (Of a) m r -> m Bool
elem_ a
a' = Bool -> Stream (Of a) m r -> m Bool
loop Bool
False where
loop :: Bool -> Stream (Of a) m r -> m Bool
loop Bool
True Stream (Of a) m r
_ = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
loop Bool
False Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m Bool) -> m Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m Bool
loop Bool
False
Step (a
a:> Stream (Of a) m r
rest) ->
if a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a'
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else Bool -> Stream (Of a) m r -> m Bool
loop Bool
False Stream (Of a) m r
rest
{-# INLINABLE elem_ #-}
enumFrom :: (Monad m, Enum n) => n -> Stream (Of n) m r
enumFrom :: n -> Stream (Of n) m r
enumFrom = n -> Stream (Of n) m r
forall (m :: * -> *) t r.
(Monad m, Enum t) =>
t -> Stream (Of t) m r
loop where
loop :: t -> Stream (Of t) m r
loop !t
n = m (Stream (Of t) m r) -> Stream (Of t) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of t) m r -> m (Stream (Of t) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of t (Stream (Of t) m r) -> Stream (Of t) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (t
n t -> Stream (Of t) m r -> Of t (Stream (Of t) m r)
forall a b. a -> b -> Of a b
:> t -> Stream (Of t) m r
loop (t -> t
forall a. Enum a => a -> a
succ t
n))))
{-# INLINABLE enumFrom #-}
enumFromThen:: (Monad m, Enum a) => a -> a -> Stream (Of a) m r
enumFromThen :: a -> a -> Stream (Of a) m r
enumFromThen a
first a
second = (Int -> a) -> Stream (Of Int) m r -> Stream (Of a) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
Streaming.Prelude.map Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> Stream (Of Int) m r
loop Int
_first)
where
_first :: Int
_first = a -> Int
forall a. Enum a => a -> Int
fromEnum a
first
_second :: Int
_second = a -> Int
forall a. Enum a => a -> Int
fromEnum a
second
diff :: Int
diff = Int
_second Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
_first
loop :: Int -> Stream (Of Int) m r
loop !Int
s = Of Int (Stream (Of Int) m r) -> Stream (Of Int) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Int
s Int -> Stream (Of Int) m r -> Of Int (Stream (Of Int) m r)
forall a b. a -> b -> Of a b
:> Int -> Stream (Of Int) m r
loop (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
diff))
{-# INLINABLE enumFromThen #-}
erase :: Monad m => Stream (Of a) m r -> Stream Identity m r
erase :: Stream (Of a) m r -> Stream Identity m r
erase = Stream (Of a) m r -> Stream Identity m r
forall (m :: * -> *) a r.
Functor m =>
Stream (Of a) m r -> Stream Identity m r
loop where
loop :: Stream (Of a) m r -> Stream Identity m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream Identity m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream Identity m r) -> Stream Identity m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream Identity m r)
-> m (Stream (Of a) m r) -> m (Stream Identity m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream Identity m r
loop m (Stream (Of a) m r)
m)
Step (a
_:>Stream (Of a) m r
rest) -> Identity (Stream Identity m r) -> Stream Identity m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Stream Identity m r -> Identity (Stream Identity m r)
forall a. a -> Identity a
Identity (Stream (Of a) m r -> Stream Identity m r
loop Stream (Of a) m r
rest))
{-# INLINABLE erase #-}
filter :: (Monad m) => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r
filter :: (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r
filter a -> Bool
thePred = Stream (Of a) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
as) -> if a -> Bool
thePred a
a
then Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
as)
else Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
as
{-# INLINE filter #-}
filterM :: (Monad m) => (a -> m Bool) -> Stream (Of a) m r -> Stream (Of a) m r
filterM :: (a -> m Bool) -> Stream (Of a) m r -> Stream (Of a) m r
filterM a -> m Bool
thePred = Stream (Of a) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ do
Bool
bool <- a -> m Bool
thePred a
a
if Bool
bool
then Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Of a) m r -> m (Stream (Of a) m r))
-> Stream (Of a) m r -> m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
as)
else Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Of a) m r -> m (Stream (Of a) m r))
-> Stream (Of a) m r -> m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ Stream (Of a) m r -> Stream (Of a) m r
loop Stream (Of a) m r
as
{-# INLINE filterM #-}
fold_ :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ :: (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ x -> a -> x
step x
begin x -> b
done = (Of b r -> b) -> m (Of b r) -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(b
a :> r
_) -> b
a) (m (Of b r) -> m b)
-> (Stream (Of a) m r -> m (Of b r)) -> Stream (Of a) m r -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold x -> a -> x
step x
begin x -> b
done
{-# INLINE fold_ #-}
fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold :: (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold x -> a -> x
step x
begin x -> b
done Stream (Of a) m r
str = Stream (Of a) m r -> x -> m (Of b r)
fold_loop Stream (Of a) m r
str x
begin
where
fold_loop :: Stream (Of a) m r -> x -> m (Of b r)
fold_loop Stream (Of a) m r
stream !x
x = case Stream (Of a) m r
stream of
Return r
r -> Of b r -> m (Of b r)
forall (m :: * -> *) a. Monad m => a -> m a
return (x -> b
done x
x b -> r -> Of b r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of b r)) -> m (Of b r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Stream (Of a) m r
str' -> Stream (Of a) m r -> x -> m (Of b r)
fold_loop Stream (Of a) m r
str' x
x
Step (a
a :> Stream (Of a) m r
rest) -> Stream (Of a) m r -> x -> m (Of b r)
fold_loop Stream (Of a) m r
rest (x -> m (Of b r)) -> x -> m (Of b r)
forall a b. (a -> b) -> a -> b
$! x -> a -> x
step x
x a
a
{-# INLINE fold #-}
foldM_
:: Monad m
=> (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> m b
foldM_ :: (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> m b
foldM_ x -> a -> m x
step m x
begin x -> m b
done = (Of b r -> b) -> m (Of b r) -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(b
a :> r
_) -> b
a) (m (Of b r) -> m b)
-> (Stream (Of a) m r -> m (Of b r)) -> Stream (Of a) m r -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x -> a -> m x)
-> m x -> (x -> m b) -> Stream (Of a) m r -> m (Of b r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> m x)
-> m x -> (x -> m b) -> Stream (Of a) m r -> m (Of b r)
foldM x -> a -> m x
step m x
begin x -> m b
done
{-# INLINE foldM_ #-}
foldM
:: Monad m
=> (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r ->m (Of b r)
foldM :: (x -> a -> m x)
-> m x -> (x -> m b) -> Stream (Of a) m r -> m (Of b r)
foldM x -> a -> m x
step m x
begin x -> m b
done Stream (Of a) m r
str = do
x
x0 <- m x
begin
Stream (Of a) m r -> x -> m (Of b r)
loop Stream (Of a) m r
str x
x0
where
loop :: Stream (Of a) m r -> x -> m (Of b r)
loop Stream (Of a) m r
stream !x
x = case Stream (Of a) m r
stream of
Return r
r -> x -> m b
done x
x m b -> (b -> m (Of b r)) -> m (Of b r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b
b -> Of b r -> m (Of b r)
forall (m :: * -> *) a. Monad m => a -> m a
return (b
b b -> r -> Of b r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of b r)) -> m (Of b r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Stream (Of a) m r
s -> Stream (Of a) m r -> x -> m (Of b r)
loop Stream (Of a) m r
s x
x
Step (a
a :> Stream (Of a) m r
rest) -> do
x
x' <- x -> a -> m x
step x
x a
a
Stream (Of a) m r -> x -> m (Of b r)
loop Stream (Of a) m r
rest x
x'
{-# INLINABLE foldM #-}
foldrT :: (Monad m, MonadTrans t, Monad (t m))
=> (a -> t m r -> t m r) -> Stream (Of a) m r -> t m r
foldrT :: (a -> t m r -> t m r) -> Stream (Of a) m r -> t m r
foldrT a -> t m r -> t m r
step = Stream (Of a) m r -> t m r
loop where
loop :: Stream (Of a) m r -> t m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> t m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> t m (Stream (Of a) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Stream (Of a) m r)
m t m (Stream (Of a) m r) -> (Stream (Of a) m r -> t m r) -> t m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> t m r
loop
Step (a
a :> Stream (Of a) m r
as) -> a -> t m r -> t m r
step a
a (Stream (Of a) m r -> t m r
loop Stream (Of a) m r
as)
{-# INLINABLE foldrT #-}
foldrM :: Monad m
=> (a -> m r -> m r) -> Stream (Of a) m r -> m r
foldrM :: (a -> m r -> m r) -> Stream (Of a) m r -> m r
foldrM a -> m r -> m r
step = Stream (Of a) m r -> m r
loop where
loop :: Stream (Of a) m r -> m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m r) -> m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> m r
loop
Step (a
a :> Stream (Of a) m r
as) -> a -> m r -> m r
step a
a (Stream (Of a) m r -> m r
loop Stream (Of a) m r
as)
{-# INLINABLE foldrM #-}
for :: (Monad m, Functor f) => Stream (Of a) m r -> (a -> Stream f m x) -> Stream f m r
for :: Stream (Of a) m r -> (a -> Stream f m x) -> Stream f m r
for Stream (Of a) m r
str0 a -> Stream f m x
f = Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
str0 where
loop :: Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream f m r) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m r) -> Stream f m r)
-> m (Stream f m r) -> Stream f m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream f m r)
-> m (Stream (Of a) m r) -> m (Stream f m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream f m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> a -> Stream f m x
f a
a Stream f m x -> Stream f m r -> Stream f m r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
as
{-# INLINABLE for #-}
groupBy :: Monad m
=> (a -> a -> Bool)
-> Stream (Of a) m r
-> Stream (Stream (Of a) m) m r
groupBy :: (a -> a -> Bool)
-> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals = Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop where
loop :: Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r)
-> m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r
forall a b. (a -> b) -> a -> b
$ do
Either r (a, Stream (Of a) m r)
e <- Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m r
stream
Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r))
-> Stream (Stream (Of a) m) m r -> m (Stream (Stream (Of a) m) m r)
forall a b. (a -> b) -> a -> b
$ case Either r (a, Stream (Of a) m r)
e of
Left r
r -> r -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Right (a
a, Stream (Of a) m r
p') -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r)
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r
forall a b. (a -> b) -> a -> b
$
(Stream (Of a) m r -> Stream (Stream (Of a) m) m r)
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop (a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a Stream (Of a) m ()
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
span (a -> a -> Bool
equals a
a) Stream (Of a) m r
p')
{-# INLINABLE groupBy #-}
group :: (Monad m, Eq a) => Stream (Of a) m r -> Stream (Stream (Of a) m) m r
group :: Stream (Of a) m r -> Stream (Stream (Of a) m) m r
group = (a -> a -> Bool)
-> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) a r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE group #-}
head :: Monad m => Stream (Of a) m r -> m (Of (Maybe a) r)
head :: Stream (Of a) m r -> m (Of (Maybe a) r)
head Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Of (Maybe a) r -> m (Of (Maybe a) r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a
forall a. Maybe a
Nothing Maybe a -> r -> Of (Maybe a) r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of (Maybe a) r)) -> m (Of (Maybe a) r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> m (Of (Maybe a) r)
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Of (Maybe a) r)
head
Step (a
a :> Stream (Of a) m r
rest) -> Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
rest m r -> (r -> m (Of (Maybe a) r)) -> m (Of (Maybe a) r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \r
r -> Of (Maybe a) r -> m (Of (Maybe a) r)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
a Maybe a -> r -> Of (Maybe a) r
forall a b. a -> b -> Of a b
:> r
r)
{-# INLINABLE head #-}
head_ :: Monad m => Stream (Of a) m r -> m (Maybe a)
head_ :: Stream (Of a) m r -> m (Maybe a)
head_ Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Maybe a)) -> m (Maybe a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> m (Maybe a)
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Maybe a)
head_
Step (a
a :> Stream (Of a) m r
_) -> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
a)
{-# INLINABLE head_ #-}
intersperse :: Monad m => a -> Stream (Of a) m r -> Stream (Of a) m r
intersperse :: a -> Stream (Of a) m r -> Stream (Of a) m r
intersperse a
x Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> Stream (Of a) m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
a -> Stream (Of a) m r -> Stream (Of a) m r
intersperse a
x) m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) -> a -> Stream (Of a) m r -> Stream (Of a) m r
loop a
a Stream (Of a) m r
rest
where
loop :: a -> Stream (Of a) m r -> Stream (Of a) m r
loop !a
a Stream (Of a) m r
theStr = case Stream (Of a) m r
theStr of
Return r
r -> Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> Stream (Of a) m r -> Stream (Of a) m r
loop a
a) m (Stream (Of a) m r)
m)
Step (a
b :> Stream (Of a) m r
rest) -> Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
x a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> a -> Stream (Of a) m r -> Stream (Of a) m r
loop a
b Stream (Of a) m r
rest))
{-# INLINABLE intersperse #-}
iterate :: Monad m => (a -> a) -> a -> Stream (Of a) m r
iterate :: (a -> a) -> a -> Stream (Of a) m r
iterate a -> a
f = a -> Stream (Of a) m r
loop where
loop :: a -> Stream (Of a) m r
loop a
a' = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a' a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> a -> Stream (Of a) m r
loop (a -> a
f a
a'))))
{-# INLINABLE iterate #-}
iterateM :: Monad m => (a -> m a) -> m a -> Stream (Of a) m r
iterateM :: (a -> m a) -> m a -> Stream (Of a) m r
iterateM a -> m a
f = m a -> Stream (Of a) m r
loop where
loop :: m a -> Stream (Of a) m r
loop m a
ma = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ do
a
a <- m a
ma
Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> m a -> Stream (Of a) m r
loop (a -> m a
f a
a)))
{-# INLINABLE iterateM #-}
last :: Monad m => Stream (Of a) m r -> m (Of (Maybe a) r)
last :: Stream (Of a) m r -> m (Of (Maybe a) r)
last = Maybe_ a -> Stream (Of a) m r -> m (Of (Maybe a) r)
forall (m :: * -> *) a b.
Monad m =>
Maybe_ a -> Stream (Of a) m b -> m (Of (Maybe a) b)
loop Maybe_ a
forall a. Maybe_ a
Nothing_ where
loop :: Maybe_ a -> Stream (Of a) m b -> m (Of (Maybe a) b)
loop Maybe_ a
mb Stream (Of a) m b
str = case Stream (Of a) m b
str of
Return b
r -> case Maybe_ a
mb of
Maybe_ a
Nothing_ -> Of (Maybe a) b -> m (Of (Maybe a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a
forall a. Maybe a
Nothing Maybe a -> b -> Of (Maybe a) b
forall a b. a -> b -> Of a b
:> b
r)
Just_ a
a -> Of (Maybe a) b -> m (Of (Maybe a) b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
a Maybe a -> b -> Of (Maybe a) b
forall a b. a -> b -> Of a b
:> b
r)
Effect m (Stream (Of a) m b)
m -> m (Stream (Of a) m b)
m m (Stream (Of a) m b)
-> (Stream (Of a) m b -> m (Of (Maybe a) b)) -> m (Of (Maybe a) b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe_ a -> Stream (Of a) m b -> m (Of (Maybe a) b)
loop Maybe_ a
mb
Step (a
a :> Stream (Of a) m b
rest) -> Maybe_ a -> Stream (Of a) m b -> m (Of (Maybe a) b)
loop (a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a) Stream (Of a) m b
rest
{-# INLINABLE last #-}
last_ :: Monad m => Stream (Of a) m r -> m (Maybe a)
last_ :: Stream (Of a) m r -> m (Maybe a)
last_ = Maybe_ a -> Stream (Of a) m r -> m (Maybe a)
forall (m :: * -> *) a r.
Monad m =>
Maybe_ a -> Stream (Of a) m r -> m (Maybe a)
loop Maybe_ a
forall a. Maybe_ a
Nothing_ where
loop :: Maybe_ a -> Stream (Of a) m r -> m (Maybe a)
loop Maybe_ a
mb Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> case Maybe_ a
mb of
Maybe_ a
Nothing_ -> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
Just_ a
a -> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
a)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Maybe a)) -> m (Maybe a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe_ a -> Stream (Of a) m r -> m (Maybe a)
loop Maybe_ a
mb
Step (a
a :> Stream (Of a) m r
rest) -> Maybe_ a -> Stream (Of a) m r -> m (Maybe a)
loop (a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a) Stream (Of a) m r
rest
{-# INLINABLE last_ #-}
length_ :: Monad m => Stream (Of a) m r -> m Int
length_ :: Stream (Of a) m r -> m Int
length_ = (Int -> a -> Int)
-> Int -> (Int -> Int) -> Stream (Of a) m r -> m Int
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ (\Int
n a
_ -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
0 Int -> Int
forall a. a -> a
id
{-# INLINE length_ #-}
length :: Monad m => Stream (Of a) m r -> m (Of Int r)
length :: Stream (Of a) m r -> m (Of Int r)
length = (Int -> a -> Int)
-> Int -> (Int -> Int) -> Stream (Of a) m r -> m (Of Int r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold (\Int
n a
_ -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
0 Int -> Int
forall a. a -> a
id
{-# INLINE length #-}
map :: Monad m => (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
map :: (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
map a -> b
f = (forall x. Of a x -> Of b x)
-> Stream (Of a) m r -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x -> g x) -> Stream f m r -> Stream g m r
maps (\(x :> rest) -> a -> b
f a
x b -> x -> Of b x
forall a b. a -> b -> Of a b
:> x
rest)
{-# INLINABLE map #-}
mapM :: Monad m => (a -> m b) -> Stream (Of a) m r -> Stream (Of b) m r
mapM :: (a -> m b) -> Stream (Of a) m r -> Stream (Of b) m r
mapM a -> m b
f = Stream (Of a) m r -> Stream (Of b) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of b) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of b) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of b) m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
as) -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) -> Stream (Of b) m r)
-> m (Stream (Of b) m r) -> Stream (Of b) m r
forall a b. (a -> b) -> a -> b
$ do
b
a' <- a -> m b
f a
a
Stream (Of b) m r -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
a' b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
as) )
{-# INLINABLE mapM #-}
mapM_ :: Monad m => (a -> m x) -> Stream (Of a) m r -> m r
mapM_ :: (a -> m x) -> Stream (Of a) m r -> m r
mapM_ a -> m x
f = Stream (Of a) m r -> m r
loop where
loop :: Stream (Of a) m r -> m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m r) -> m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> m r
loop
Step (a
a :> Stream (Of a) m r
as) -> a -> m x
f a
a m x -> m r -> m r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Stream (Of a) m r -> m r
loop Stream (Of a) m r
as
{-# INLINABLE mapM_ #-}
mapped :: (Monad m, Functor f) => (forall x . f x -> m (g x)) -> Stream f m r -> Stream g m r
mapped :: (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
mapped = (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
mapsM
{-# INLINE mapped #-}
mappedPost :: (Monad m, Functor g) => (forall x . f x -> m (g x)) -> Stream f m r -> Stream g m r
mappedPost :: (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
mappedPost = (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor g) =>
(forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
mapsMPost
{-# INLINE mappedPost #-}
foldMap :: (Monad m, Monoid w) => (a -> w) -> Stream (Of a) m r -> m (Of w r)
foldMap :: (a -> w) -> Stream (Of a) m r -> m (Of w r)
foldMap a -> w
f = (w -> a -> w) -> w -> (w -> w) -> Stream (Of a) m r -> m (Of w r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold (\ !w
acc a
a -> w -> w -> w
forall a. Monoid a => a -> a -> a
mappend w
acc (a -> w
f a
a)) w
forall a. Monoid a => a
mempty w -> w
forall a. a -> a
id
{-# INLINE foldMap #-}
foldMap_ :: (Monad m, Monoid w) => (a -> w) -> Stream (Of a) m r -> m w
foldMap_ :: (a -> w) -> Stream (Of a) m r -> m w
foldMap_ a -> w
f = (w -> a -> w) -> w -> (w -> w) -> Stream (Of a) m r -> m w
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ (\ !w
acc a
a -> w -> w -> w
forall a. Monoid a => a -> a -> a
mappend w
acc (a -> w
f a
a)) w
forall a. Monoid a => a
mempty w -> w
forall a. a -> a
id
{-# INLINE foldMap_ #-}
mconcat :: (Monad m, Monoid w) => Stream (Of w) m r -> m (Of w r)
mconcat :: Stream (Of w) m r -> m (Of w r)
mconcat = (w -> w -> w) -> w -> (w -> w) -> Stream (Of w) m r -> m (Of w r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold w -> w -> w
forall a. Monoid a => a -> a -> a
mappend w
forall a. Monoid a => a
mempty w -> w
forall a. a -> a
id
{-# INLINE mconcat #-}
data Maybe_ a = Just_ !a | Nothing_
mconcat_ :: (Monad m, Monoid w) => Stream (Of w) m r -> m w
mconcat_ :: Stream (Of w) m r -> m w
mconcat_ = (w -> w -> w) -> w -> (w -> w) -> Stream (Of w) m r -> m w
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ w -> w -> w
forall a. Monoid a => a -> a -> a
mappend w
forall a. Monoid a => a
mempty w -> w
forall a. a -> a
id
minimum :: (Monad m, Ord a) => Stream (Of a) m r -> m (Of (Maybe a) r)
minimum :: Stream (Of a) m r -> m (Of (Maybe a) r)
minimum = (Maybe_ a -> a -> Maybe_ a)
-> Maybe_ a
-> (Maybe_ a -> Maybe a)
-> Stream (Of a) m r
-> m (Of (Maybe a) r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold (\Maybe_ a
m a
a -> case Maybe_ a
m of Maybe_ a
Nothing_ -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a ; Just_ a
a' -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ (a -> a -> a
forall a. Ord a => a -> a -> a
min a
a a
a'))
Maybe_ a
forall a. Maybe_ a
Nothing_
(\Maybe_ a
m -> case Maybe_ a
m of Maybe_ a
Nothing_ -> Maybe a
forall a. Maybe a
Nothing; Just_ a
r -> a -> Maybe a
forall a. a -> Maybe a
Just a
r)
{-# INLINE minimum #-}
minimum_ :: (Monad m, Ord a) => Stream (Of a) m r -> m (Maybe a)
minimum_ :: Stream (Of a) m r -> m (Maybe a)
minimum_ = (Maybe_ a -> a -> Maybe_ a)
-> Maybe_ a
-> (Maybe_ a -> Maybe a)
-> Stream (Of a) m r
-> m (Maybe a)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ (\Maybe_ a
m a
a -> case Maybe_ a
m of Maybe_ a
Nothing_ -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a ; Just_ a
a' -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ (a -> a -> a
forall a. Ord a => a -> a -> a
min a
a a
a'))
Maybe_ a
forall a. Maybe_ a
Nothing_
(\Maybe_ a
m -> case Maybe_ a
m of Maybe_ a
Nothing_ -> Maybe a
forall a. Maybe a
Nothing; Just_ a
r -> a -> Maybe a
forall a. a -> Maybe a
Just a
r)
{-# INLINE minimum_ #-}
maximum :: (Monad m, Ord a) => Stream (Of a) m r -> m (Of (Maybe a) r)
maximum :: Stream (Of a) m r -> m (Of (Maybe a) r)
maximum = (Maybe_ a -> a -> Maybe_ a)
-> Maybe_ a
-> (Maybe_ a -> Maybe a)
-> Stream (Of a) m r
-> m (Of (Maybe a) r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold (\Maybe_ a
m a
a -> case Maybe_ a
m of Maybe_ a
Nothing_ -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a ; Just_ a
a' -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ (a -> a -> a
forall a. Ord a => a -> a -> a
max a
a a
a'))
Maybe_ a
forall a. Maybe_ a
Nothing_
(\Maybe_ a
m -> case Maybe_ a
m of Maybe_ a
Nothing_ -> Maybe a
forall a. Maybe a
Nothing; Just_ a
r -> a -> Maybe a
forall a. a -> Maybe a
Just a
r)
{-# INLINE maximum #-}
maximum_ :: (Monad m, Ord a) => Stream (Of a) m r -> m (Maybe a)
maximum_ :: Stream (Of a) m r -> m (Maybe a)
maximum_ = (Maybe_ a -> a -> Maybe_ a)
-> Maybe_ a
-> (Maybe_ a -> Maybe a)
-> Stream (Of a) m r
-> m (Maybe a)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ (\Maybe_ a
m a
a -> case Maybe_ a
m of Maybe_ a
Nothing_ -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ a
a ; Just_ a
a' -> a -> Maybe_ a
forall a. a -> Maybe_ a
Just_ (a -> a -> a
forall a. Ord a => a -> a -> a
max a
a a
a'))
Maybe_ a
forall a. Maybe_ a
Nothing_
(\Maybe_ a
m -> case Maybe_ a
m of Maybe_ a
Nothing_ -> Maybe a
forall a. Maybe a
Nothing; Just_ a
r -> a -> Maybe a
forall a. a -> Maybe a
Just a
r)
{-# INLINE maximum_ #-}
next :: Monad m => Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next :: Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next = Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
loop where
loop :: Stream (Of a) m a -> m (Either a (a, Stream (Of a) m a))
loop Stream (Of a) m a
stream = case Stream (Of a) m a
stream of
Return a
r -> Either a (a, Stream (Of a) m a)
-> m (Either a (a, Stream (Of a) m a))
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either a (a, Stream (Of a) m a)
forall a b. a -> Either a b
Left a
r)
Effect m (Stream (Of a) m a)
m -> m (Stream (Of a) m a)
m m (Stream (Of a) m a)
-> (Stream (Of a) m a -> m (Either a (a, Stream (Of a) m a)))
-> m (Either a (a, Stream (Of a) m a))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m a -> m (Either a (a, Stream (Of a) m a))
loop
Step (a
a :> Stream (Of a) m a
rest) -> Either a (a, Stream (Of a) m a)
-> m (Either a (a, Stream (Of a) m a))
forall (m :: * -> *) a. Monad m => a -> m a
return ((a, Stream (Of a) m a) -> Either a (a, Stream (Of a) m a)
forall a b. b -> Either a b
Right (a
a,Stream (Of a) m a
rest))
{-# INLINABLE next #-}
notElem :: (Monad m, Eq a) => a -> Stream (Of a) m r -> m (Of Bool r)
notElem :: a -> Stream (Of a) m r -> m (Of Bool r)
notElem a
a' = Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True where
loop :: Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
False Stream (Of a) m r
str = (r -> Of Bool r) -> m r -> m (Of Bool r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bool
False Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:>) (Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
str)
loop Bool
True Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Of Bool r -> m (Of Bool r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
TrueBool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:> r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Of Bool r)) -> m (Of Bool r)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True
Step (a
a:> Stream (Of a) m r
rest) ->
if a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a'
then (r -> Of Bool r) -> m r -> m (Of Bool r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bool
False Bool -> r -> Of Bool r
forall a b. a -> b -> Of a b
:>) (Stream (Of a) m r -> m r
forall (m :: * -> *) a r. Monad m => Stream (Of a) m r -> m r
effects Stream (Of a) m r
rest)
else Bool -> Stream (Of a) m r -> m (Of Bool r)
loop Bool
True Stream (Of a) m r
rest
{-# INLINABLE notElem #-}
notElem_ :: (Monad m, Eq a) => a -> Stream (Of a) m r -> m Bool
notElem_ :: a -> Stream (Of a) m r -> m Bool
notElem_ a
a' = Bool -> Stream (Of a) m r -> m Bool
loop Bool
True where
loop :: Bool -> Stream (Of a) m r -> m Bool
loop Bool
False Stream (Of a) m r
_ = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
loop Bool
True Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
_ -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r) -> (Stream (Of a) m r -> m Bool) -> m Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream (Of a) m r -> m Bool
loop Bool
True
Step (a
a:> Stream (Of a) m r
rest) ->
if a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a'
then Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else Bool -> Stream (Of a) m r -> m Bool
loop Bool
True Stream (Of a) m r
rest
{-# INLINABLE notElem_ #-}
nubOrd :: (Monad m, Ord a) => Stream (Of a) m r -> Stream (Of a) m r
nubOrd :: Stream (Of a) m r -> Stream (Of a) m r
nubOrd = (a -> a) -> Stream (Of a) m r -> Stream (Of a) m r
forall (m :: * -> *) b a r.
(Monad m, Ord b) =>
(a -> b) -> Stream (Of a) m r -> Stream (Of a) m r
nubOrdOn a -> a
forall a. a -> a
id
{-# INLINE nubOrd #-}
nubOrdOn :: (Monad m, Ord b) => (a -> b) -> Stream (Of a) m r -> Stream (Of a) m r
nubOrdOn :: (a -> b) -> Stream (Of a) m r -> Stream (Of a) m r
nubOrdOn a -> b
f Stream (Of a) m r
xs = Set b -> Stream (Of a) m r -> Stream (Of a) m r
loop Set b
forall a. Monoid a => a
mempty Stream (Of a) m r
xs where
loop :: Set b -> Stream (Of a) m r -> Stream (Of a) m r
loop !Set b
set Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Set b -> Stream (Of a) m r -> Stream (Of a) m r
loop Set b
set) m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) -> let !fa :: b
fa = a -> b
f a
a in
if b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member b
fa Set b
set
then Set b -> Stream (Of a) m r -> Stream (Of a) m r
loop Set b
set Stream (Of a) m r
rest
else Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Set b -> Stream (Of a) m r -> Stream (Of a) m r
loop (b -> Set b -> Set b
forall a. Ord a => a -> Set a -> Set a
Set.insert b
fa Set b
set) Stream (Of a) m r
rest)
nubInt :: Monad m => Stream (Of Int) m r -> Stream (Of Int) m r
nubInt :: Stream (Of Int) m r -> Stream (Of Int) m r
nubInt = (Int -> Int) -> Stream (Of Int) m r -> Stream (Of Int) m r
forall (m :: * -> *) a r.
Monad m =>
(a -> Int) -> Stream (Of a) m r -> Stream (Of a) m r
nubIntOn Int -> Int
forall a. a -> a
id
{-# INLINE nubInt #-}
nubIntOn :: Monad m => (a -> Int) -> Stream (Of a) m r -> Stream (Of a) m r
nubIntOn :: (a -> Int) -> Stream (Of a) m r -> Stream (Of a) m r
nubIntOn a -> Int
f Stream (Of a) m r
xs = IntSet -> Stream (Of a) m r -> Stream (Of a) m r
loop IntSet
forall a. Monoid a => a
mempty Stream (Of a) m r
xs where
loop :: IntSet -> Stream (Of a) m r -> Stream (Of a) m r
loop !IntSet
set Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of a) m r)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (IntSet -> Stream (Of a) m r -> Stream (Of a) m r
loop IntSet
set) m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) -> let !fa :: Int
fa = a -> Int
f a
a in
if Int -> IntSet -> Bool
IntSet.member Int
fa IntSet
set
then IntSet -> Stream (Of a) m r -> Stream (Of a) m r
loop IntSet
set Stream (Of a) m r
rest
else Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> IntSet -> Stream (Of a) m r -> Stream (Of a) m r
loop (Int -> IntSet -> IntSet
IntSet.insert Int
fa IntSet
set) Stream (Of a) m r
rest)
partition :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
partition :: (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
partition a -> Bool
thus = Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of a) m r) -> Stream (Of a) m (Stream (Of a) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Stream (Of a) m r)
m))
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thus a
a
then Of a (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) (Stream (Of a) m) r
-> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
rest)
else Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall a b. (a -> b) -> a -> b
$ do
a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a
Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
rest)
partitionEithers :: Monad m => Stream (Of (Either a b)) m r -> Stream (Of a) (Stream (Of b) m) r
partitionEithers :: Stream (Of (Either a b)) m r -> Stream (Of a) (Stream (Of b) m) r
partitionEithers = Stream (Of (Either a b)) m r -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a a r.
Monad m =>
Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop where
loop :: Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of (Either a a)) m r
str = case Stream (Of (Either a a)) m r
str of
Return r
r -> r -> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of (Either a a)) m r)
m -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of (Either a a)) m r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of (Either a a)) m r)
-> Stream (Of a) m (Stream (Of (Either a a)) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Stream (Of (Either a a)) m r)
m))
Step (Left a
a :> Stream (Of (Either a a)) m r
rest) -> Of a (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) (Stream (Of a) m) r
-> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of (Either a a)) m r
rest)
Step (Right a
b :> Stream (Of (Either a a)) m r
rest) -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall a b. (a -> b) -> a -> b
$ do
a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
b
Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Of (Either a a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of (Either a a)) m r
rest)
product_ :: (Monad m, Num a) => Stream (Of a) m () -> m a
product_ :: Stream (Of a) m () -> m a
product_ = (a -> a -> a) -> a -> (a -> a) -> Stream (Of a) m () -> m a
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ a -> a -> a
forall a. Num a => a -> a -> a
(*) a
1 a -> a
forall a. a -> a
id
{-# INLINE product_ #-}
product :: (Monad m, Num a) => Stream (Of a) m r -> m (Of a r)
product :: Stream (Of a) m r -> m (Of a r)
product = (a -> a -> a) -> a -> (a -> a) -> Stream (Of a) m r -> m (Of a r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold a -> a -> a
forall a. Num a => a -> a -> a
(*) a
1 a -> a
forall a. a -> a
id
{-# INLINE product #-}
read :: (Monad m, Read a) => Stream (Of String) m r -> Stream (Of a) m r
read :: Stream (Of String) m r -> Stream (Of a) m r
read Stream (Of String) m r
stream = Stream (Of String) m r
-> (String -> Stream (Of a) m ()) -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) a r x.
(Monad m, Functor f) =>
Stream (Of a) m r -> (a -> Stream f m x) -> Stream f m r
for Stream (Of String) m r
stream ((String -> Stream (Of a) m ()) -> Stream (Of a) m r)
-> (String -> Stream (Of a) m ()) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ \String
str -> case String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe String
str of
Maybe a
Nothing -> () -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just a
r -> a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
r
{-# INLINE read #-}
repeat :: Monad m => a -> Stream (Of a) m r
repeat :: a -> Stream (Of a) m r
repeat a
a = Stream (Of a) m r
loop where loop :: Stream (Of a) m r
loop = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
loop)))
{-# INLINE repeat #-}
repeatM :: Monad m => m a -> Stream (Of a) m r
repeatM :: m a -> Stream (Of a) m r
repeatM m a
ma = Stream (Of a) m r
loop where
loop :: Stream (Of a) m r
loop = do
a
a <- m a -> Stream (Of a) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m a
ma
a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a
Stream (Of a) m r
loop
{-# INLINABLE repeatM #-}
replicate :: Monad m => Int -> a -> Stream (Of a) m ()
replicate :: Int -> a -> Stream (Of a) m ()
replicate Int
n a
_ | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = () -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
replicate Int
n a
a = Int -> Stream (Of a) m ()
loop Int
n where
loop :: Int -> Stream (Of a) m ()
loop Int
0 = () -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ()
loop Int
m = m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m () -> m (Stream (Of a) m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Int -> Stream (Of a) m ()
loop (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))))
{-# INLINABLE replicate #-}
replicateM :: Monad m => Int -> m a -> Stream (Of a) m ()
replicateM :: Int -> m a -> Stream (Of a) m ()
replicateM Int
n m a
_ | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = () -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
replicateM Int
n m a
ma = Int -> Stream (Of a) m ()
loop Int
n where
loop :: Int -> Stream (Of a) m ()
loop Int
0 = () -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ()
loop Int
m = m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m ()) -> Stream (Of a) m ())
-> m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall a b. (a -> b) -> a -> b
$ do
a
a <- m a
ma
Stream (Of a) m () -> m (Stream (Of a) m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Int -> Stream (Of a) m ()
loop (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)))
{-# INLINABLE replicateM #-}
reread :: Monad m => (s -> m (Maybe a)) -> s -> Stream (Of a) m ()
reread :: (s -> m (Maybe a)) -> s -> Stream (Of a) m ()
reread s -> m (Maybe a)
step s
s = Stream (Of a) m ()
loop where
loop :: Stream (Of a) m ()
loop = m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m ()) -> Stream (Of a) m ())
-> m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall a b. (a -> b) -> a -> b
$ do
Maybe a
m <- s -> m (Maybe a)
step s
s
case Maybe a
m of
Maybe a
Nothing -> Stream (Of a) m () -> m (Stream (Of a) m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ())
Just a
a -> Stream (Of a) m () -> m (Stream (Of a) m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Stream (Of a) m ()
loop))
{-# INLINABLE reread #-}
scan :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of b) m r
scan :: (x -> a -> x)
-> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of b) m r
scan x -> a -> x
step x
begin x -> b
done Stream (Of a) m r
str = Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (x -> b
done x
begin b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
begin Stream (Of a) m r
str)
where
loop :: x -> Stream (Of a) m r -> Stream (Of b) m r
loop !x
acc Stream (Of a) m r
stream =
case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of b) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of b) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
acc) m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) ->
let !acc' :: x
acc' = x -> a -> x
step x
acc a
a
in Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (x -> b
done x
acc' b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
acc' Stream (Of a) m r
rest)
{-# INLINABLE scan #-}
scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> Stream (Of b) m r
scanM :: (x -> a -> m x)
-> m x -> (x -> m b) -> Stream (Of a) m r -> Stream (Of b) m r
scanM x -> a -> m x
step m x
begin x -> m b
done Stream (Of a) m r
str = m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) -> Stream (Of b) m r)
-> m (Stream (Of b) m r) -> Stream (Of b) m r
forall a b. (a -> b) -> a -> b
$ do
x
x <- m x
begin
b
b <- x -> m b
done x
x
Stream (Of b) m r -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
b b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
x Stream (Of a) m r
str))
where
loop :: x -> Stream (Of a) m r -> Stream (Of b) m r
loop !x
x Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (do
Stream (Of a) m r
stream' <- m (Stream (Of a) m r)
m
Stream (Of b) m r -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
x Stream (Of a) m r
stream')
)
Step (a
a :> Stream (Of a) m r
rest) -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (do
x
x' <- x -> a -> m x
step x
x a
a
b
b <- x -> m b
done x
x'
Stream (Of b) m r -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
b b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r -> Stream (Of b) m r
loop x
x' Stream (Of a) m r
rest))
)
{-# INLINABLE scanM #-}
scanned :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of (a,b)) m r
scanned :: (x -> a -> x)
-> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of (a, b)) m r
scanned x -> a -> x
step x
begin x -> b
done = Maybe' a -> x -> Stream (Of a) m r -> Stream (Of (a, b)) m r
loop Maybe' a
forall a. Maybe' a
Nothing' x
begin
where
loop :: Maybe' a -> x -> Stream (Of a) m r -> Stream (Of (a, b)) m r
loop !Maybe' a
m !x
x Stream (Of a) m r
stream =
case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of (a, b)) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of a) m r)
mn -> m (Stream (Of (a, b)) m r) -> Stream (Of (a, b)) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of (a, b)) m r) -> Stream (Of (a, b)) m r)
-> m (Stream (Of (a, b)) m r) -> Stream (Of (a, b)) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of (a, b)) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of (a, b)) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe' a -> x -> Stream (Of a) m r -> Stream (Of (a, b)) m r
loop Maybe' a
m x
x) m (Stream (Of a) m r)
mn
Step (a
a :> Stream (Of a) m r
rest) ->
case Maybe' a
m of
Maybe' a
Nothing' -> do
let !acc :: x
acc = x -> a -> x
step x
x a
a
(a, b) -> Stream (Of (a, b)) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield (a
a, x -> b
done x
acc)
Maybe' a -> x -> Stream (Of a) m r -> Stream (Of (a, b)) m r
loop (a -> Maybe' a
forall a. a -> Maybe' a
Just' a
a) x
acc Stream (Of a) m r
rest
Just' a
_ -> do
let !acc :: b
acc = x -> b
done (x -> a -> x
step x
x a
a)
(a, b) -> Stream (Of (a, b)) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield (a
a, b
acc)
Maybe' a -> x -> Stream (Of a) m r -> Stream (Of (a, b)) m r
loop (a -> Maybe' a
forall a. a -> Maybe' a
Just' a
a) (x -> a -> x
step x
x a
a) Stream (Of a) m r
rest
{-# INLINABLE scanned #-}
data Maybe' a = Just' a | Nothing'
sequence :: Monad m => Stream (Of (m a)) m r -> Stream (Of a) m r
sequence :: Stream (Of (m a)) m r -> Stream (Of a) m r
sequence = Stream (Of (m a)) m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (m a)) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of (m a)) m r -> Stream (Of a) m r
loop Stream (Of (m a)) m r
stream = case Stream (Of (m a)) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of (m a)) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of (m a)) m r -> Stream (Of a) m r)
-> m (Stream (Of (m a)) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of (m a)) m r -> Stream (Of a) m r
loop m (Stream (Of (m a)) m r)
m
Step (m a
ma :> Stream (Of (m a)) m r
rest) -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) -> Stream (Of a) m r)
-> m (Stream (Of a) m r) -> Stream (Of a) m r
forall a b. (a -> b) -> a -> b
$ do
a
a <- m a
ma
Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of (m a)) m r -> Stream (Of a) m r
loop Stream (Of (m a)) m r
rest))
{-# INLINABLE sequence #-}
show :: (Monad m, Show a) => Stream (Of a) m r -> Stream (Of String) m r
show :: Stream (Of a) m r -> Stream (Of String) m r
show = (a -> String) -> Stream (Of a) m r -> Stream (Of String) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
map a -> String
forall a. Show a => a -> String
Prelude.show
{-# INLINE show #-}
sum_ :: (Monad m, Num a) => Stream (Of a) m () -> m a
sum_ :: Stream (Of a) m () -> m a
sum_ = (a -> a -> a) -> a -> (a -> a) -> Stream (Of a) m () -> m a
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ a -> a -> a
forall a. Num a => a -> a -> a
(+) a
0 a -> a
forall a. a -> a
id
{-# INLINE sum_ #-}
sum :: (Monad m, Num a) => Stream (Of a) m r -> m (Of a r)
sum :: Stream (Of a) m r -> m (Of a r)
sum = (a -> a -> a) -> a -> (a -> a) -> Stream (Of a) m r -> m (Of a r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold a -> a -> a
forall a. Num a => a -> a -> a
(+) a
0 a -> a
forall a. a -> a
id
{-# INLINABLE sum #-}
span :: Monad m => (a -> Bool) -> Stream (Of a) m r
-> Stream (Of a) m (Stream (Of a) m r)
span :: (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
span a -> Bool
thePred = Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r))
-> m (Stream (Of a) m r) -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
rest) -> if a -> Bool
thePred a
a
then Of a (Stream (Of a) m (Stream (Of a) m r))
-> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Of a) m r)
-> Of a (Stream (Of a) m (Stream (Of a) m r))
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
rest)
else Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
rest))
{-# INLINABLE span #-}
split :: (Eq a, Monad m) =>
a -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
split :: a -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r
split a
t = Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop where
loop :: Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Stream (Of a) m) m r) -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Stream (Of a) m) m r)
-> m (Stream (Of a) m r) -> m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) ->
if a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
t
then Stream (Of a) m (Stream (Stream (Of a) m) m r)
-> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step ((Stream (Of a) m r -> Stream (Stream (Of a) m) m r)
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop (a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
a Stream (Of a) m ()
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)
break (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t) Stream (Of a) m r
rest))
else Stream (Of a) m r -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
rest
{-# INLINABLE split #-}
splitAt :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Stream f m r)
splitAt :: Int -> Stream f m r -> Stream f m (Stream f m r)
splitAt = Int -> Stream f m r -> Stream f m (Stream f m r)
forall (m :: * -> *) (f :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r -> Stream f m (Stream f m r)
splitsAt
{-# INLINE splitAt #-}
subst :: (Monad m, Functor f) => (a -> f x) -> Stream (Of a) m r -> Stream f m r
subst :: (a -> f x) -> Stream (Of a) m r -> Stream f m r
subst a -> f x
f Stream (Of a) m r
s = Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
s where
loop :: Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream f m r) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream f m r)
-> m (Stream (Of a) m r) -> m (Stream f m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream f m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) -> f (Stream f m r) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
rest Stream f m r -> f x -> f (Stream f m r)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ a -> f x
f a
a)
{-# INLINABLE subst #-}
take :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m ()
take :: Int -> Stream f m r -> Stream f m ()
take Int
n0 Stream f m r
_ | Int
n0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = () -> Stream f m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
take Int
n0 Stream f m r
str = Int -> Stream f m r -> Stream f m ()
forall t (m :: * -> *) (f :: * -> *) r.
(Eq t, Num t, Monad m, Functor f) =>
t -> Stream f m r -> Stream f m ()
loop Int
n0 Stream f m r
str where
loop :: t -> Stream f m r -> Stream f m ()
loop t
0 Stream f m r
_ = () -> Stream f m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
loop t
n Stream f m r
p =
case Stream f m r
p of
Step f (Stream f m r)
fas -> f (Stream f m ()) -> Stream f m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step ((Stream f m r -> Stream f m ())
-> f (Stream f m r) -> f (Stream f m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t -> Stream f m r -> Stream f m ()
loop (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)) f (Stream f m r)
fas)
Effect m (Stream f m r)
m -> m (Stream f m ()) -> Stream f m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream f m r -> Stream f m ())
-> m (Stream f m r) -> m (Stream f m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t -> Stream f m r -> Stream f m ()
loop t
n) m (Stream f m r)
m)
Return r
_ -> () -> Stream f m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ()
{-# INLINABLE take #-}
takeWhile :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m ()
takeWhile :: (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m ()
takeWhile a -> Bool
thePred = Stream (Of a) m r -> Stream (Of a) m ()
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m ()
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Step (a
a :> Stream (Of a) m r
as) -> Bool -> Stream (Of a) m () -> Stream (Of a) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (a -> Bool
thePred a
a) (Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m ()
loop Stream (Of a) m r
as))
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m ())
-> m (Stream (Of a) m r) -> m (Stream (Of a) m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m ()
loop m (Stream (Of a) m r)
m)
Return r
_ -> () -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ()
{-# INLINE takeWhile #-}
takeWhileM :: Monad m => (a -> m Bool) -> Stream (Of a) m r -> Stream (Of a) m ()
takeWhileM :: (a -> m Bool) -> Stream (Of a) m r -> Stream (Of a) m ()
takeWhileM a -> m Bool
thePred = Stream (Of a) m r -> Stream (Of a) m ()
loop where
loop :: Stream (Of a) m r -> Stream (Of a) m ()
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Step (a
a :> Stream (Of a) m r
as) -> do
Bool
b <- m Bool -> Stream (Of a) m Bool
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (a -> m Bool
thePred a
a)
Bool -> Stream (Of a) m () -> Stream (Of a) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b (Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m ()
loop Stream (Of a) m r
as))
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) m ())
-> m (Stream (Of a) m r) -> m (Stream (Of a) m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) m ()
loop m (Stream (Of a) m r)
m)
Return r
_ -> () -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ()
{-# INLINE takeWhileM #-}
toList_ :: Monad m => Stream (Of a) m r -> m [a]
toList_ :: Stream (Of a) m r -> m [a]
toList_ = (([a] -> [a]) -> a -> [a] -> [a])
-> ([a] -> [a])
-> (([a] -> [a]) -> [a])
-> Stream (Of a) m r
-> m [a]
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b
fold_ (\[a] -> [a]
diff a
a [a]
ls -> [a] -> [a]
diff (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
ls)) [a] -> [a]
forall a. a -> a
id (\[a] -> [a]
diff -> [a] -> [a]
diff [])
{-# INLINE toList_ #-}
toList :: Monad m => Stream (Of a) m r -> m (Of [a] r)
toList :: Stream (Of a) m r -> m (Of [a] r)
toList = (([a] -> [a]) -> a -> [a] -> [a])
-> ([a] -> [a])
-> (([a] -> [a]) -> [a])
-> Stream (Of a) m r
-> m (Of [a] r)
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r)
fold (\[a] -> [a]
diff a
a [a]
ls -> [a] -> [a]
diff (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
ls)) [a] -> [a]
forall a. a -> a
id (\[a] -> [a]
diff -> [a] -> [a]
diff [])
{-# INLINE toList #-}
uncons :: Monad m => Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
uncons :: Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
uncons = Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
loop where
loop :: Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
_ -> Maybe (a, Stream (Of a) m r) -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (a, Stream (Of a) m r)
forall a. Maybe a
Nothing
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r)
m m (Stream (Of a) m r)
-> (Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r)))
-> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m r -> m (Maybe (a, Stream (Of a) m r))
loop
Step (a
a :> Stream (Of a) m r
rest) -> Maybe (a, Stream (Of a) m r) -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return ((a, Stream (Of a) m r) -> Maybe (a, Stream (Of a) m r)
forall a. a -> Maybe a
Just (a
a,Stream (Of a) m r
rest))
{-# INLINABLE uncons #-}
unfoldr :: Monad m
=> (s -> m (Either r (a, s))) -> s -> Stream (Of a) m r
unfoldr :: (s -> m (Either r (a, s))) -> s -> Stream (Of a) m r
unfoldr s -> m (Either r (a, s))
step = s -> Stream (Of a) m r
loop where
loop :: s -> Stream (Of a) m r
loop s
s0 = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (do
Either r (a, s)
e <- s -> m (Either r (a, s))
step s
s0
case Either r (a, s)
e of
Left r
r -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
Right (a
a,s
s) -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> s -> Stream (Of a) m r
loop s
s)))
{-# INLINABLE unfoldr #-}
untilLeft :: Monad m => m (Either r a) -> Stream (Of a) m r
untilLeft :: m (Either r a) -> Stream (Of a) m r
untilLeft m (Either r a)
act = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect m (Stream (Of a) m r)
loop where
loop :: m (Stream (Of a) m r)
loop = do
Either r a
e <- m (Either r a)
act
case Either r a
e of
Right a
a -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect m (Stream (Of a) m r)
loop))
Left r
r -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
{-# INLINABLE untilLeft #-}
untilRight :: Monad m => m (Either a r) -> Stream (Of a) m r
untilRight :: m (Either a r) -> Stream (Of a) m r
untilRight m (Either a r)
act = m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect m (Stream (Of a) m r)
loop where
loop :: m (Stream (Of a) m r)
loop = do
Either a r
e <- m (Either a r)
act
case Either a r
e of
Right r
r -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r)
Left a
a -> Stream (Of a) m r -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect m (Stream (Of a) m r)
loop))
{-# INLINABLE untilRight #-}
with :: (Monad m, Functor f) => Stream (Of a) m r -> (a -> f x) -> Stream f m r
with :: Stream (Of a) m r -> (a -> f x) -> Stream f m r
with Stream (Of a) m r
s a -> f x
f = Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
s where
loop :: Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream f m r) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream f m r)
-> m (Stream (Of a) m r) -> m (Stream f m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream f m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
rest) -> f (Stream f m r) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Stream (Of a) m r -> Stream f m r
loop Stream (Of a) m r
rest Stream f m r -> f x -> f (Stream f m r)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ a -> f x
f a
a)
{-# INLINABLE with #-}
yield :: Monad m => a -> Stream (Of a) m ()
yield :: a -> Stream (Of a) m ()
yield a
a = Of a (Stream (Of a) m ()) -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m () -> Of a (Stream (Of a) m ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of a) m ()
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ())
{-# INLINE yield #-}
zip :: Monad m
=> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of (a,b)) m r
zip :: Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of (a, b)) m r
zip = (a -> b -> (a, b))
-> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of (a, b)) m r
forall (m :: * -> *) a b c r.
Monad m =>
(a -> b -> c)
-> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
zipWith (,)
{-# INLINE zip #-}
zipWith :: Monad m
=> (a -> b -> c)
-> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
zipWith :: (a -> b -> c)
-> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
zipWith a -> b -> c
f = Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
loop
where
loop :: Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
loop Stream (Of a) m r
str0 Stream (Of b) m r
str1 = case Stream (Of a) m r
str0 of
Return r
r -> r -> Stream (Of c) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of c) m r) -> Stream (Of c) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of c) m r) -> Stream (Of c) m r)
-> m (Stream (Of c) m r) -> Stream (Of c) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of c) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of c) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Stream (Of a) m r
str -> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
loop Stream (Of a) m r
str Stream (Of b) m r
str1) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
rest0) -> case Stream (Of b) m r
str1 of
Return r
r -> r -> Stream (Of c) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of b) m r)
m -> m (Stream (Of c) m r) -> Stream (Of c) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of c) m r) -> Stream (Of c) m r)
-> m (Stream (Of c) m r) -> Stream (Of c) m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of b) m r -> Stream (Of c) m r)
-> m (Stream (Of b) m r) -> m (Stream (Of c) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
loop Stream (Of a) m r
str0) m (Stream (Of b) m r)
m
Step (b
b :> Stream (Of b) m r
rest1) -> Of c (Stream (Of c) m r) -> Stream (Of c) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a -> b -> c
f a
a b
b c -> Stream (Of c) m r -> Of c (Stream (Of c) m r)
forall a b. a -> b -> Of a b
:>Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r
loop Stream (Of a) m r
rest0 Stream (Of b) m r
rest1)
{-# INLINABLE zipWith #-}
zipWith3 :: Monad m =>
(a -> b -> c -> d)
-> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of d) m r
zipWith3 :: (a -> b -> c -> d)
-> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of d) m r
zipWith3 a -> b -> c -> d
op = Stream (Of a) m r
-> Stream (Of b) m r -> Stream (Of c) m r -> Stream (Of d) m r
loop where
loop :: Stream (Of a) m r
-> Stream (Of b) m r -> Stream (Of c) m r -> Stream (Of d) m r
loop Stream (Of a) m r
str0 Stream (Of b) m r
str1 Stream (Of c) m r
str2 = do
Either r (a, Stream (Of a) m r)
e0 <- m (Either r (a, Stream (Of a) m r))
-> Stream (Of d) m (Either r (a, Stream (Of a) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m r
str0)
case Either r (a, Stream (Of a) m r)
e0 of
Left r
r0 -> r -> Stream (Of d) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r0
Right (a
a0,Stream (Of a) m r
rest0) -> do
Either r (b, Stream (Of b) m r)
e1 <- m (Either r (b, Stream (Of b) m r))
-> Stream (Of d) m (Either r (b, Stream (Of b) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Stream (Of b) m r -> m (Either r (b, Stream (Of b) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of b) m r
str1)
case Either r (b, Stream (Of b) m r)
e1 of
Left r
r1 -> r -> Stream (Of d) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r1
Right (b
a1,Stream (Of b) m r
rest1) -> do
Either r (c, Stream (Of c) m r)
e2 <- m (Either r (c, Stream (Of c) m r))
-> Stream (Of d) m (Either r (c, Stream (Of c) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Stream (Of c) m r -> m (Either r (c, Stream (Of c) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of c) m r
str2)
case Either r (c, Stream (Of c) m r)
e2 of
Left r
r2 -> r -> Stream (Of d) m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r2
Right (c
a2,Stream (Of c) m r
rest2) -> do
d -> Stream (Of d) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield (a -> b -> c -> d
op a
a0 b
a1 c
a2)
Stream (Of a) m r
-> Stream (Of b) m r -> Stream (Of c) m r -> Stream (Of d) m r
loop Stream (Of a) m r
rest0 Stream (Of b) m r
rest1 Stream (Of c) m r
rest2
{-# INLINABLE zipWith3 #-}
zip3 :: Monad m
=> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of (a,b,c)) m r
zip3 :: Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of (a, b, c)) m r
zip3 = (a -> b -> c -> (a, b, c))
-> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of (a, b, c)) m r
forall (m :: * -> *) a b c d r.
Monad m =>
(a -> b -> c -> d)
-> Stream (Of a) m r
-> Stream (Of b) m r
-> Stream (Of c) m r
-> Stream (Of d) m r
zipWith3 (,,)
{-# INLINABLE zip3 #-}
stdinLn :: MonadIO m => Stream (Of String) m ()
stdinLn :: Stream (Of String) m ()
stdinLn = Handle -> Stream (Of String) m ()
forall (m :: * -> *).
MonadIO m =>
Handle -> Stream (Of String) m ()
fromHandle Handle
IO.stdin
{-# INLINABLE stdinLn #-}
readLn :: (MonadIO m, Read a) => Stream (Of a) m ()
readLn :: Stream (Of a) m ()
readLn = Stream (Of a) m ()
loop where
loop :: Stream (Of a) m ()
loop = do
Bool
eof <- IO Bool -> Stream (Of a) m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Bool
IO.isEOF
Bool -> Stream (Of a) m () -> Stream (Of a) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
eof (Stream (Of a) m () -> Stream (Of a) m ())
-> Stream (Of a) m () -> Stream (Of a) m ()
forall a b. (a -> b) -> a -> b
$ do
String
str <- IO String -> Stream (Of a) m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getLine
case String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe String
str of
Maybe a
Nothing -> Stream (Of a) m ()
forall (m :: * -> *) a. (MonadIO m, Read a) => Stream (Of a) m ()
readLn
Just a
n -> a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
n Stream (Of a) m () -> Stream (Of a) m () -> Stream (Of a) m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Stream (Of a) m ()
loop
{-# INLINABLE readLn #-}
fromHandle :: MonadIO m => IO.Handle -> Stream (Of String) m ()
fromHandle :: Handle -> Stream (Of String) m ()
fromHandle Handle
h = Stream (Of String) m ()
go
where
go :: Stream (Of String) m ()
go = do
Bool
eof <- IO Bool -> Stream (Of String) m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Stream (Of String) m Bool)
-> IO Bool -> Stream (Of String) m Bool
forall a b. (a -> b) -> a -> b
$ Handle -> IO Bool
IO.hIsEOF Handle
h
Bool -> Stream (Of String) m () -> Stream (Of String) m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
eof (Stream (Of String) m () -> Stream (Of String) m ())
-> Stream (Of String) m () -> Stream (Of String) m ()
forall a b. (a -> b) -> a -> b
$ do
String
str <- IO String -> Stream (Of String) m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> Stream (Of String) m String)
-> IO String -> Stream (Of String) m String
forall a b. (a -> b) -> a -> b
$ Handle -> IO String
IO.hGetLine Handle
h
String -> Stream (Of String) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield String
str
Stream (Of String) m ()
go
{-# INLINABLE fromHandle #-}
toHandle :: MonadIO m => IO.Handle -> Stream (Of String) m r -> m r
toHandle :: Handle -> Stream (Of String) m r -> m r
toHandle Handle
handle = Stream (Of String) m r -> m r
loop where
loop :: Stream (Of String) m r -> m r
loop Stream (Of String) m r
str = case Stream (Of String) m r
str of
Return r
r -> r -> m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Effect m (Stream (Of String) m r)
m -> m (Stream (Of String) m r)
m m (Stream (Of String) m r)
-> (Stream (Of String) m r -> m r) -> m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of String) m r -> m r
loop
Step (String
s :> Stream (Of String) m r
rest) -> do
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> String -> IO ()
IO.hPutStrLn Handle
handle String
s)
Stream (Of String) m r -> m r
loop Stream (Of String) m r
rest
{-# INLINABLE toHandle #-}
print :: (MonadIO m, Show a) => Stream (Of a) m r -> m r
print :: Stream (Of a) m r -> m r
print = Stream (Of a) m r -> m r
forall (m :: * -> *) a a.
(MonadIO m, Show a) =>
Stream (Of a) m a -> m a
loop where
loop :: Stream (Of a) m a -> m a
loop Stream (Of a) m a
stream = case Stream (Of a) m a
stream of
Return a
r -> a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
Effect m (Stream (Of a) m a)
m -> m (Stream (Of a) m a)
m m (Stream (Of a) m a) -> (Stream (Of a) m a -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of a) m a -> m a
loop
Step (a
a :> Stream (Of a) m a
rest) -> do
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (a -> IO ()
forall a. Show a => a -> IO ()
Prelude.print a
a)
Stream (Of a) m a -> m a
loop Stream (Of a) m a
rest
stdoutLn :: MonadIO m => Stream (Of String) m () -> m ()
stdoutLn :: Stream (Of String) m () -> m ()
stdoutLn = Stream (Of String) m () -> m ()
forall (m :: * -> *) r. MonadIO m => Stream (Of String) m r -> m ()
loop
where
loop :: Stream (Of String) m r -> m ()
loop Stream (Of String) m r
stream = case Stream (Of String) m r
stream of
Return r
_ -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Effect m (Stream (Of String) m r)
m -> m (Stream (Of String) m r)
m m (Stream (Of String) m r)
-> (Stream (Of String) m r -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Stream (Of String) m r -> m ()
loop
Step (String
s :> Stream (Of String) m r
rest) -> do
Either IOException ()
x <- IO (Either IOException ()) -> m (Either IOException ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either IOException ()) -> m (Either IOException ()))
-> IO (Either IOException ()) -> m (Either IOException ())
forall a b. (a -> b) -> a -> b
$ IO () -> IO (Either IOException ())
forall e a. Exception e => IO a -> IO (Either e a)
try (String -> IO ()
putStrLn String
s)
case Either IOException ()
x of
Left (G.IOError { ioe_type :: IOException -> IOErrorType
G.ioe_type = IOErrorType
G.ResourceVanished
, ioe_errno :: IOException -> Maybe CInt
G.ioe_errno = Just CInt
ioe })
| CInt -> Errno
Errno CInt
ioe Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
ePIPE
-> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Left IOException
e -> IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO IOException
e)
Right () -> Stream (Of String) m r -> m ()
loop Stream (Of String) m r
rest
{-# INLINABLE stdoutLn #-}
readFile :: FilePath -> (Stream (Of String) IO () -> IO a) -> IO a
readFile :: String -> (Stream (Of String) IO () -> IO a) -> IO a
readFile String
f Stream (Of String) IO () -> IO a
s = String -> IOMode -> (Handle -> IO a) -> IO a
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile String
f IOMode
IO.ReadMode ((Handle -> IO a) -> IO a) -> (Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle
h -> Stream (Of String) IO () -> IO a
s (Handle -> Stream (Of String) IO ()
forall (m :: * -> *).
MonadIO m =>
Handle -> Stream (Of String) m ()
fromHandle Handle
h)
writeFile :: FilePath -> Stream (Of String) IO r -> IO r
writeFile :: String -> Stream (Of String) IO r -> IO r
writeFile String
f = String -> IOMode -> (Handle -> IO r) -> IO r
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile String
f IOMode
IO.WriteMode ((Handle -> IO r) -> IO r)
-> (Stream (Of String) IO r -> Handle -> IO r)
-> Stream (Of String) IO r
-> IO r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Handle -> Stream (Of String) IO r -> IO r)
-> Stream (Of String) IO r -> Handle -> IO r
forall a b c. (a -> b -> c) -> b -> a -> c
flip Handle -> Stream (Of String) IO r -> IO r
forall (m :: * -> *) r.
MonadIO m =>
Handle -> Stream (Of String) m r -> m r
toHandle
stdoutLn' :: MonadIO m => Stream (Of String) m r -> m r
stdoutLn' :: Stream (Of String) m r -> m r
stdoutLn' = Handle -> Stream (Of String) m r -> m r
forall (m :: * -> *) r.
MonadIO m =>
Handle -> Stream (Of String) m r -> m r
toHandle Handle
IO.stdout
distinguish :: (a -> Bool) -> Of a r -> Sum (Of a) (Of a) r
distinguish :: (a -> Bool) -> Of a r -> Sum (Of a) (Of a) r
distinguish a -> Bool
predicate (a
a :> r
b) = if a -> Bool
predicate a
a then Of a r -> Sum (Of a) (Of a) r
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
b) else Of a r -> Sum (Of a) (Of a) r
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
b)
{-# INLINE distinguish #-}
sumToEither ::Sum (Of a) (Of b) r -> Of (Either a b) r
sumToEither :: Sum (Of a) (Of b) r -> Of (Either a b) r
sumToEither Sum (Of a) (Of b) r
s = case Sum (Of a) (Of b) r
s of
InL (a
a :> r
r) -> a -> Either a b
forall a b. a -> Either a b
Left a
a Either a b -> r -> Of (Either a b) r
forall a b. a -> b -> Of a b
:> r
r
InR (b
b :> r
r) -> b -> Either a b
forall a b. b -> Either a b
Right b
b Either a b -> r -> Of (Either a b) r
forall a b. a -> b -> Of a b
:> r
r
{-# INLINE sumToEither #-}
eitherToSum :: Of (Either a b) r -> Sum (Of a) (Of b) r
eitherToSum :: Of (Either a b) r -> Sum (Of a) (Of b) r
eitherToSum Of (Either a b) r
s = case Of (Either a b) r
s of
Left a
a :> r
r -> Of a r -> Sum (Of a) (Of b) r
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
r)
Right b
b :> r
r -> Of b r -> Sum (Of a) (Of b) r
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR (b
b b -> r -> Of b r
forall a b. a -> b -> Of a b
:> r
r)
{-# INLINE eitherToSum #-}
composeToSum :: Compose (Of Bool) f r -> Sum f f r
composeToSum :: Compose (Of Bool) f r -> Sum f f r
composeToSum Compose (Of Bool) f r
x = case Compose (Of Bool) f r
x of
Compose (Bool
True :> f r
f) -> f r -> Sum f f r
forall k (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR f r
f
Compose (Bool
False :> f r
f) -> f r -> Sum f f r
forall k (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL f r
f
{-# INLINE composeToSum #-}
sumToCompose :: Sum f f r -> Compose (Of Bool) f r
sumToCompose :: Sum f f r -> Compose (Of Bool) f r
sumToCompose Sum f f r
x = case Sum f f r
x of
InR f r
f -> Of Bool (f r) -> Compose (Of Bool) f r
forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (Bool
True Bool -> f r -> Of Bool (f r)
forall a b. a -> b -> Of a b
:> f r
f)
InL f r
f -> Of Bool (f r) -> Compose (Of Bool) f r
forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (Bool
False Bool -> f r -> Of Bool (f r)
forall a b. a -> b -> Of a b
:> f r
f)
{-# INLINE sumToCompose #-}
store
:: Monad m =>
(Stream (Of a) (Stream (Of a) m) r -> t) -> Stream (Of a) m r -> t
store :: (Stream (Of a) (Stream (Of a) m) r -> t) -> Stream (Of a) m r -> t
store Stream (Of a) (Stream (Of a) m) r -> t
f Stream (Of a) m r
x = Stream (Of a) (Stream (Of a) m) r -> t
f (Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
copy Stream (Of a) m r
x)
{-# INLINE store #-}
copy
:: Monad m =>
Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
copy :: Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
copy = Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r)
-> (Stream (Of a) m r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
-> Stream (Of a) m r
-> Stream (Of a) (Stream (Of a) m) r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
-> (Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop where
loop :: Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
str = case Stream (Of a) m r
str of
Return r
r -> r -> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of a) m r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of a) m r) -> Stream (Of a) m (Stream (Of a) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Stream (Of a) m r)
m))
Step (a
a :> Stream (Of a) m r
rest) -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
forall a b. a -> b -> Of a b
:> Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (Of a (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) (Stream (Of a) m) r
-> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
rest))))
{-# INLINABLE copy#-}
duplicate
:: Monad m =>
Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
duplicate :: Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
duplicate = Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r
copy
{-# INLINE duplicate #-}
unzip :: Monad m => Stream (Of (a,b)) m r -> Stream (Of a) (Stream (Of b) m) r
unzip :: Stream (Of (a, b)) m r -> Stream (Of a) (Stream (Of b) m) r
unzip = Stream (Of (a, b)) m r -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a a r.
Monad m =>
Stream (Of (a, a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop where
loop :: Stream (Of (a, a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of (a, a)) m r
str = case Stream (Of (a, a)) m r
str of
Return r
r -> r -> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of (a, a)) m r)
m -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of (a, a)) m r -> Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) m (Stream (Of (a, a)) m r)
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of (a, a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of (a, a)) m r)
-> Stream (Of a) m (Stream (Of (a, a)) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (Stream (Of (a, a)) m r)
m))
Step ((a
a,a
b):> Stream (Of (a, a)) m r
rest) -> Of a (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) (Stream (Of a) m) r
-> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Stream (Of a) (Stream (Of a) m) r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
b a
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
-> Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
forall a b. a -> b -> Of a b
:> Stream (Of a) (Stream (Of a) m) r
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return (Stream (Of (a, a)) m r -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of (a, a)) m r
rest))))
{-# INLINABLE unzip #-}
merge :: (Monad m, Ord a)
=> Stream (Of a) m r
-> Stream (Of a) m s
-> Stream (Of a) m (r, s)
merge :: Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
merge = (a -> a -> Ordering)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
forall (m :: * -> *) a r s.
Monad m =>
(a -> a -> Ordering)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
mergeBy a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE merge #-}
mergeOn :: (Monad m, Ord b)
=> (a -> b)
-> Stream (Of a) m r
-> Stream (Of a) m s
-> Stream (Of a) m (r, s)
mergeOn :: (a -> b)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
mergeOn a -> b
f = (a -> a -> Ordering)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
forall (m :: * -> *) a r s.
Monad m =>
(a -> a -> Ordering)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
mergeBy ((a -> b) -> a -> a -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing a -> b
f)
{-# INLINE mergeOn #-}
mergeBy :: Monad m
=> (a -> a -> Ordering)
-> Stream (Of a) m r
-> Stream (Of a) m s
-> Stream (Of a) m (r, s)
mergeBy :: (a -> a -> Ordering)
-> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
mergeBy a -> a -> Ordering
cmp = Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop
where
loop :: Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
str0 Stream (Of a) m s
str1 = case Stream (Of a) m r
str0 of
Return r
r0 -> (\ s
r1 -> (r
r0, s
r1)) (s -> (r, s)) -> Stream (Of a) m s -> Stream (Of a) m (r, s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Stream (Of a) m s
str1
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s))
-> m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m r -> Stream (Of a) m (r, s))
-> m (Stream (Of a) m r) -> m (Stream (Of a) m (r, s))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ Stream (Of a) m r
str -> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
str Stream (Of a) m s
str1) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
rest0) -> case Stream (Of a) m s
str1 of
Return s
r1 -> (\ r
r0 -> (r
r0, s
r1)) (r -> (r, s)) -> Stream (Of a) m r -> Stream (Of a) m (r, s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Stream (Of a) m r
str0
Effect m (Stream (Of a) m s)
m -> m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s))
-> m (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall a b. (a -> b) -> a -> b
$ (Stream (Of a) m s -> Stream (Of a) m (r, s))
-> m (Stream (Of a) m s) -> m (Stream (Of a) m (r, s))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
str0) m (Stream (Of a) m s)
m
Step (a
b :> Stream (Of a) m s
rest1) -> case a -> a -> Ordering
cmp a
a a
b of
Ordering
LT -> Of a (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m (r, s) -> Of a (Stream (Of a) m (r, s))
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
rest0 Stream (Of a) m s
str1)
Ordering
EQ -> Of a (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m (r, s) -> Of a (Stream (Of a) m (r, s))
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
rest0 Stream (Of a) m s
str1)
Ordering
GT -> Of a (Stream (Of a) m (r, s)) -> Stream (Of a) m (r, s)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
b a -> Stream (Of a) m (r, s) -> Of a (Stream (Of a) m (r, s))
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
loop Stream (Of a) m r
str0 Stream (Of a) m s
rest1)
{-# INLINABLE mergeBy #-}
catMaybes :: Monad m => Stream (Of (Maybe a)) m r -> Stream (Of a) m r
catMaybes :: Stream (Of (Maybe a)) m r -> Stream (Of a) m r
catMaybes = Stream (Of (Maybe a)) m r -> Stream (Of a) m r
forall (m :: * -> *) a r.
Functor m =>
Stream (Of (Maybe a)) m r -> Stream (Of a) m r
loop where
loop :: Stream (Of (Maybe a)) m r -> Stream (Of a) m r
loop Stream (Of (Maybe a)) m r
stream = case Stream (Of (Maybe a)) m r
stream of
Return r
r -> r -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of (Maybe a)) m r)
m -> m (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of (Maybe a)) m r -> Stream (Of a) m r)
-> m (Stream (Of (Maybe a)) m r) -> m (Stream (Of a) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of (Maybe a)) m r -> Stream (Of a) m r
loop m (Stream (Of (Maybe a)) m r)
m)
Step (Maybe a
ma :> Stream (Of (Maybe a)) m r
snext) -> case Maybe a
ma of
Maybe a
Nothing -> Stream (Of (Maybe a)) m r -> Stream (Of a) m r
loop Stream (Of (Maybe a)) m r
snext
Just a
a -> Of a (Stream (Of a) m r) -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) m r -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of (Maybe a)) m r -> Stream (Of a) m r
loop Stream (Of (Maybe a)) m r
snext)
{-# INLINABLE catMaybes #-}
mapMaybe :: Monad m => (a -> Maybe b) -> Stream (Of a) m r -> Stream (Of b) m r
mapMaybe :: (a -> Maybe b) -> Stream (Of a) m r -> Stream (Of b) m r
mapMaybe a -> Maybe b
phi = Stream (Of a) m r -> Stream (Of b) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of b) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of b) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of b) m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
snext) -> case a -> Maybe b
phi a
a of
Maybe b
Nothing -> Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
snext
Just b
b -> Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
b b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
snext)
{-# INLINABLE mapMaybe #-}
slidingWindow :: Monad m
=> Int
-> Stream (Of a) m b
-> Stream (Of (Seq.Seq a)) m b
slidingWindow :: Int -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
slidingWindow Int
n = Int -> Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
forall t (m :: * -> *) a b.
(Eq t, Num t, Monad m) =>
t -> Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
setup (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 Int
n :: Int) Seq a
forall a. Monoid a => a
mempty
where
window :: Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
window !Seq a
sequ Stream (Of a) m b
str = do
Either b (a, Stream (Of a) m b)
e <- m (Either b (a, Stream (Of a) m b))
-> Stream (Of (Seq a)) m (Either b (a, Stream (Of a) m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Stream (Of a) m b -> m (Either b (a, Stream (Of a) m b))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m b
str)
case Either b (a, Stream (Of a) m b)
e of
Left b
r -> b -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
Right (a
a,Stream (Of a) m b
rest) -> do
Seq a -> Stream (Of (Seq a)) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield (Seq a
sequ Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
a)
Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
window (Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.drop Int
1 (Seq a -> Seq a) -> Seq a -> Seq a
forall a b. (a -> b) -> a -> b
$ Seq a
sequ Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
a) Stream (Of a) m b
rest
setup :: t -> Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
setup t
0 !Seq a
sequ Stream (Of a) m b
str = do
Seq a -> Stream (Of (Seq a)) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield Seq a
sequ
Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a b.
Monad m =>
Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
window (Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.drop Int
1 Seq a
sequ) Stream (Of a) m b
str
setup t
m Seq a
sequ Stream (Of a) m b
str = do
Either b (a, Stream (Of a) m b)
e <- m (Either b (a, Stream (Of a) m b))
-> Stream (Of (Seq a)) m (Either b (a, Stream (Of a) m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either b (a, Stream (Of a) m b))
-> Stream (Of (Seq a)) m (Either b (a, Stream (Of a) m b)))
-> m (Either b (a, Stream (Of a) m b))
-> Stream (Of (Seq a)) m (Either b (a, Stream (Of a) m b))
forall a b. (a -> b) -> a -> b
$ Stream (Of a) m b -> m (Either b (a, Stream (Of a) m b))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m b
str
case Either b (a, Stream (Of a) m b)
e of
Left b
r -> Seq a -> Stream (Of (Seq a)) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield Seq a
sequ Stream (Of (Seq a)) m ()
-> Stream (Of (Seq a)) m b -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> b -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
Right (a
x,Stream (Of a) m b
rest) -> t -> Seq a -> Stream (Of a) m b -> Stream (Of (Seq a)) m b
setup (t
mt -> t -> t
forall a. Num a => a -> a -> a
-t
1) (Seq a
sequ Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
x) Stream (Of a) m b
rest
{-# INLINABLE slidingWindow #-}
slidingWindowMin :: (Monad m, Ord a) => Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMin :: Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMin = (a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMinBy a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE slidingWindowMin #-}
slidingWindowMax :: (Monad m, Ord a) => Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMax :: Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMax = (a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMaxBy a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE slidingWindowMax #-}
slidingWindowMinBy :: Monad m => (a -> a -> Ordering) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMinBy :: (a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMinBy a -> a -> Ordering
cmp = (a -> a)
-> (a -> a -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
forall (m :: * -> *) a p b.
Monad m =>
(a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
slidingWindowOrd a -> a
forall a. a -> a
id (\a
a a
b -> a -> a -> Ordering
cmp a
a a
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT)
{-# INLINE slidingWindowMinBy #-}
slidingWindowMaxBy :: Monad m => (a -> a -> Ordering) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMaxBy :: (a -> a -> Ordering)
-> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMaxBy a -> a -> Ordering
cmp = (a -> a)
-> (a -> a -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
forall (m :: * -> *) a p b.
Monad m =>
(a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
slidingWindowOrd a -> a
forall a. a -> a
id (\a
a a
b -> a -> a -> Ordering
cmp a
a a
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT)
{-# INLINE slidingWindowMaxBy #-}
slidingWindowMinOn :: (Monad m, Ord p) => (a -> p) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMinOn :: (a -> p) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMinOn a -> p
proj = (a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
forall (m :: * -> *) a p b.
Monad m =>
(a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
slidingWindowOrd a -> p
proj (\p
a p
b -> p -> p -> Ordering
forall a. Ord a => a -> a -> Ordering
compare p
a p
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT)
{-# INLINE slidingWindowMinOn #-}
slidingWindowMaxOn :: (Monad m, Ord p) => (a -> p) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMaxOn :: (a -> p) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowMaxOn a -> p
proj = (a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
forall (m :: * -> *) a p b.
Monad m =>
(a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
slidingWindowOrd a -> p
proj (\p
a p
b -> p -> p -> Ordering
forall a. Ord a => a -> a -> Ordering
compare p
a p
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT)
{-# INLINE slidingWindowMaxOn #-}
slidingWindowOrd :: Monad m => (a -> p) -> (p -> p -> Bool) -> Int -> Stream (Of a) m b -> Stream (Of a) m b
slidingWindowOrd :: (a -> p)
-> (p -> p -> Bool)
-> Int
-> Stream (Of a) m b
-> Stream (Of a) m b
slidingWindowOrd a -> p
proj p -> p -> Bool
f Int
n =
Int -> Stream (Of a) m b -> Stream (Of a) m b
forall (m :: * -> *) a r.
Monad m =>
Int -> Stream (Of a) m r -> Stream (Of a) m r
dropButRetainAtLeastOne (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Stream (Of a) m b -> Stream (Of a) m b)
-> (Stream (Of a) m b -> Stream (Of a) m b)
-> Stream (Of a) m b
-> Stream (Of a) m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream (Of (Maybe a)) m b -> Stream (Of a) m b
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r -> Stream (Of a) m r
catMaybes (Stream (Of (Maybe a)) m b -> Stream (Of a) m b)
-> (Stream (Of a) m b -> Stream (Of (Maybe a)) m b)
-> Stream (Of a) m b
-> Stream (Of a) m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SlidingWindowOrdState a p -> a -> SlidingWindowOrdState a p)
-> SlidingWindowOrdState a p
-> (SlidingWindowOrdState a p -> Maybe a)
-> Stream (Of a) m b
-> Stream (Of (Maybe a)) m b
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of b) m r
scan SlidingWindowOrdState a p -> a -> SlidingWindowOrdState a p
update SlidingWindowOrdState a p
forall a p. SlidingWindowOrdState a p
initial SlidingWindowOrdState a p -> Maybe a
forall a p. SlidingWindowOrdState a p -> Maybe a
extract
where
k :: Int
k = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 Int
n
initial :: SlidingWindowOrdState a p
initial = Word64
-> Seq (SlidingWindowOrdElement a p) -> SlidingWindowOrdState a p
forall a p.
Word64
-> Seq (SlidingWindowOrdElement a p) -> SlidingWindowOrdState a p
SlidingWindowOrdState Word64
0 Seq (SlidingWindowOrdElement a p)
forall a. Monoid a => a
mempty
update :: SlidingWindowOrdState a p -> a -> SlidingWindowOrdState a p
update (SlidingWindowOrdState Word64
i Seq (SlidingWindowOrdElement a p)
w0) a
a =
let projected :: p
projected = a -> p
proj a
a
w1 :: Seq (SlidingWindowOrdElement a p)
w1 = (SlidingWindowOrdElement a p -> Bool)
-> Seq (SlidingWindowOrdElement a p)
-> Seq (SlidingWindowOrdElement a p)
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileR (\(SlidingWindowOrdElement Word64
_ a
_ p
p) -> p -> p -> Bool
f p
p p
projected) Seq (SlidingWindowOrdElement a p)
w0
w2 :: Seq (SlidingWindowOrdElement a p)
w2 = Seq (SlidingWindowOrdElement a p)
w1 Seq (SlidingWindowOrdElement a p)
-> SlidingWindowOrdElement a p -> Seq (SlidingWindowOrdElement a p)
forall a. Seq a -> a -> Seq a
Seq.|> Word64 -> a -> p -> SlidingWindowOrdElement a p
forall a p. Word64 -> a -> p -> SlidingWindowOrdElement a p
SlidingWindowOrdElement Word64
i a
a p
projected
w3 :: Seq (SlidingWindowOrdElement a p)
w3 = (SlidingWindowOrdElement a p -> Bool)
-> Seq (SlidingWindowOrdElement a p)
-> Seq (SlidingWindowOrdElement a p)
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileL (\(SlidingWindowOrdElement Word64
j a
_ p
_) -> Word64
j Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
i) Seq (SlidingWindowOrdElement a p)
w2
in Word64
-> Seq (SlidingWindowOrdElement a p) -> SlidingWindowOrdState a p
forall a p.
Word64
-> Seq (SlidingWindowOrdElement a p) -> SlidingWindowOrdState a p
SlidingWindowOrdState (Word64
i Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Seq (SlidingWindowOrdElement a p)
w3
extract :: SlidingWindowOrdState a p -> Maybe a
extract (SlidingWindowOrdState Word64
_ Seq (SlidingWindowOrdElement a p)
w) =
case Seq (SlidingWindowOrdElement a p)
-> ViewL (SlidingWindowOrdElement a p)
forall a. Seq a -> ViewL a
Seq.viewl Seq (SlidingWindowOrdElement a p)
w of
SlidingWindowOrdElement Word64
_ a
m p
_ Seq.:< Seq (SlidingWindowOrdElement a p)
_ -> a -> Maybe a
forall a. a -> Maybe a
Just a
m
ViewL (SlidingWindowOrdElement a p)
_ -> Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE slidingWindowOrd #-}
data SlidingWindowOrdState a p =
SlidingWindowOrdState !Word64
!(Seq.Seq (SlidingWindowOrdElement a p))
data SlidingWindowOrdElement a p = SlidingWindowOrdElement !Word64 a p
dropButRetainAtLeastOne :: Monad m => Int -> Stream (Of a) m r -> Stream (Of a) m r
dropButRetainAtLeastOne :: Int -> Stream (Of a) m r -> Stream (Of a) m r
dropButRetainAtLeastOne Int
0 = Stream (Of a) m r -> Stream (Of a) m r
forall a. a -> a
id
dropButRetainAtLeastOne Int
n = Maybe a -> Int -> Stream (Of a) m r -> Stream (Of a) m r
forall t (m :: * -> *) a a.
(Eq t, Num t, Monad m) =>
Maybe a -> t -> Stream (Of a) m a -> Stream (Of a) m a
loop Maybe a
forall a. Maybe a
Nothing Int
n
where
loop :: Maybe a -> t -> Stream (Of a) m a -> Stream (Of a) m a
loop (Just a
final) (-1) Stream (Of a) m a
str = a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
final Stream (Of a) m () -> Stream (Of a) m a -> Stream (Of a) m a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Stream (Of a) m a
str
loop Maybe a
final t
m Stream (Of a) m a
str = do
Either a (a, Stream (Of a) m a)
e <- m (Either a (a, Stream (Of a) m a))
-> Stream (Of a) m (Either a (a, Stream (Of a) m a))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Stream (Of a) m a -> m (Either a (a, Stream (Of a) m a))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
next Stream (Of a) m a
str)
case Either a (a, Stream (Of a) m a)
e of
Left a
r -> do
case Maybe a
final of
Maybe a
Nothing -> () -> Stream (Of a) m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just a
l -> a -> Stream (Of a) m ()
forall (m :: * -> *) a. Monad m => a -> Stream (Of a) m ()
yield a
l
a -> Stream (Of a) m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
Right (a
x, Stream (Of a) m a
rest) -> Maybe a -> t -> Stream (Of a) m a -> Stream (Of a) m a
loop (a -> Maybe a
forall a. a -> Maybe a
Just a
x) (t
m t -> t -> t
forall a. Num a => a -> a -> a
- t
1) Stream (Of a) m a
rest
{-# INLINABLE dropButRetainAtLeastOne #-}
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Stream (Of a) m r -> Stream (Of b) m r
mapMaybeM :: (a -> m (Maybe b)) -> Stream (Of a) m r -> Stream (Of b) m r
mapMaybeM a -> m (Maybe b)
phi = Stream (Of a) m r -> Stream (Of b) m r
loop where
loop :: Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
stream = case Stream (Of a) m r
stream of
Return r
r -> r -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r -> Stream (Of b) m r)
-> m (Stream (Of a) m r) -> m (Stream (Of b) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of a) m r -> Stream (Of b) m r
loop m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
snext) -> m (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) -> Stream (Of b) m r)
-> m (Stream (Of b) m r) -> Stream (Of b) m r
forall a b. (a -> b) -> a -> b
$
((Maybe b -> Stream (Of b) m r)
-> m (Maybe b) -> m (Stream (Of b) m r))
-> m (Maybe b)
-> (Maybe b -> Stream (Of b) m r)
-> m (Stream (Of b) m r)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe b -> Stream (Of b) m r)
-> m (Maybe b) -> m (Stream (Of b) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> m (Maybe b)
phi a
a) ((Maybe b -> Stream (Of b) m r) -> m (Stream (Of b) m r))
-> (Maybe b -> Stream (Of b) m r) -> m (Stream (Of b) m r)
forall a b. (a -> b) -> a -> b
$ \Maybe b
x -> case Maybe b
x of
Maybe b
Nothing -> Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
snext
Just b
b -> Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
b b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r -> Stream (Of b) m r
loop Stream (Of a) m r
snext)
{-# INLINABLE mapMaybeM #-}