{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE QualifiedDo #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Streaming.Internal.Process
(
next
, uncons
, splitAt
, split
, breaks
, break
, breakWhen
, breakWhen'
, span
, group
, groupBy
, distinguish
, switch
, separate
, unseparate
, eitherToSum
, sumToEither
, sumToCompose
, composeToSum
, partitionEithers
, partition
, catMaybes
, mapMaybe
, mapMaybeM
, hoist
, map
, mapM
, maps
, mapped
, mapsPost
, mapsMPost
, mappedPost
, for
, with
, subst
, copy
, duplicate
, store
, chain
, sequence
, nubOrd
, nubOrdOn
, nubInt
, nubIntOn
, filter
, filterM
, intersperse
, drop
, dropWhile
, scan
, scanM
, scanned
, delay
, read
, show
, cons
, slidingWindow
, wrapEffect
, destroyExposed
) where
import Streaming.Internal.Type
import Prelude.Linear ((&), ($), (.))
import Prelude (Maybe(..), Either(..), Bool(..), Int,
Ordering(..), Num(..), Eq(..), id, Ord(..), Read(..),
String, Double)
import qualified Prelude
import Data.Unrestricted.Linear
import qualified Control.Functor.Linear as Control
import System.IO.Linear
import Data.Functor.Sum
import Data.Functor.Compose
import qualified Data.Set as Set
import qualified Data.Sequence as Seq
import qualified Data.IntSet as IntSet
import Text.Read (readMaybe)
import Control.Concurrent (threadDelay)
import GHC.Stack
consFirstChunk :: Control.Monad m =>
a -> Stream (Stream (Of a) m) m r %1-> Stream (Stream (Of a) m) m r
consFirstChunk :: forall (m :: * -> *) a r.
Monad m =>
a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
consFirstChunk a
a Stream (Stream (Of a) m) m r
stream = Stream (Stream (Of a) m) m r
stream Stream (Stream (Of a) m) m r
%1 -> (Stream (Stream (Of a) m) m r
%1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (r %1 -> Stream (Stream (Of a) m) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r)))
Effect m (Stream (Stream (Of a) m) m r)
m -> m (Stream (Stream (Of a) m) m r) %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) a r.
Monad m =>
a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
consFirstChunk a
a) m (Stream (Stream (Of a) m) m r)
m
Step Stream (Of a) m (Stream (Stream (Of a) m) m r)
f -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> Stream (Of a) m (Stream (Stream (Of a) m) m r)
f))
destroyExposed
:: forall f m r b. (Control.Functor f, Control.Monad m) =>
Stream f m r %1-> (f b %1-> b) -> (m b %1-> b) -> (r %1-> b) -> b
destroyExposed :: forall (f :: * -> *) (m :: * -> *) r b.
(Functor f, Monad m) =>
Stream f m r
%1 -> (f b %1 -> b) -> (m b %1 -> b) -> (r %1 -> b) -> b
destroyExposed Stream f m r
stream0 f b %1 -> b
construct m b %1 -> b
theEffect r %1 -> b
done = (Functor f, Monad m) => Stream f m r %1 -> b
Stream f m r %1 -> b
loop Stream f m r
stream0
where
loop :: (Control.Functor f, Control.Monad m) =>
Stream f m r %1-> b
loop :: (Functor f, Monad m) => Stream f m r %1 -> b
loop Stream f m r
stream = Stream f m r
stream Stream f m r %1 -> (Stream f m r %1 -> b) %1 -> b
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> b
done r
r
Effect m (Stream f m r)
m -> m b %1 -> b
theEffect ((Stream f m r %1 -> b) %1 -> m (Stream f m r) %1 -> m b
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (Functor f, Monad m) => Stream f m r %1 -> b
Stream f m r %1 -> b
loop m (Stream f m r)
m)
Step f (Stream f m r)
f -> f b %1 -> b
construct ((Stream f m r %1 -> b) %1 -> f (Stream f m r) %1 -> f b
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (Functor f, Monad m) => Stream f m r %1 -> b
Stream f m r %1 -> b
loop f (Stream f m r)
f)
next :: forall a m r. Control.Monad m =>
Stream (Of a) m r %1-> m (Either r (Ur a, Stream (Of a) m r))
next :: forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
next Stream (Of a) m r
stream = Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> m (Either r (Ur a, Stream (Of a) m r))
loop :: Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r
%1 -> m (Either r (Ur a, Stream (Of a) m r)))
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r)))
%1 -> Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ r %1 -> Either r (Ur a, Stream (Of a) m r)
forall a b. a -> Either a b
Left r
r
Effect m (Stream (Of a) m r)
ms -> m (Stream (Of a) m r)
ms m (Stream (Of a) m r)
%1 -> (Stream (Of a) m r
%1 -> m (Either r (Ur a, Stream (Of a) m r)))
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
next
Step (a
a :> Stream (Of a) m r
as) -> Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r)))
%1 -> Either r (Ur a, Stream (Of a) m r)
%1 -> m (Either r (Ur a, Stream (Of a) m r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Ur a, Stream (Of a) m r) %1 -> Either r (Ur a, Stream (Of a) m r)
forall a b. b -> Either a b
Right (a -> Ur a
forall a. a -> Ur a
Ur a
a, Stream (Of a) m r
as)
{-# INLINABLE next #-}
uncons :: forall a m r. (Consumable r, Control.Monad m) =>
Stream (Of a) m r %1-> m (Maybe (a, Stream (Of a) m r))
uncons :: forall a (m :: * -> *) r.
(Consumable r, Monad m) =>
Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r))
uncons Stream (Of a) m r
stream = Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r))
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> m (Maybe (a, Stream (Of a) m r))
loop :: Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r))
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r)))
%1 -> m (Maybe (a, Stream (Of a) m r))
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r
%1 -> m (Maybe (a, Stream (Of a) m r))
%1 -> m (Maybe (a, Stream (Of a) m r))
forall a b. Consumable a => a %1 -> b %1 -> b
lseq r
r (m (Maybe (a, Stream (Of a) m r))
%1 -> m (Maybe (a, Stream (Of a) m r)))
%1 -> m (Maybe (a, Stream (Of a) m r))
%1 -> m (Maybe (a, Stream (Of a) m r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Maybe (a, Stream (Of a) m r) %1 -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return Maybe (a, Stream (Of a) m r)
forall a. Maybe a
Nothing
Effect m (Stream (Of a) m r)
ms -> m (Stream (Of a) m r)
ms m (Stream (Of a) m r)
%1 -> (Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r)))
%1 -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r))
forall a (m :: * -> *) r.
(Consumable r, Monad m) =>
Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r))
uncons
Step (a
a :> Stream (Of a) m r
as) -> Maybe (a, Stream (Of a) m r) %1 -> m (Maybe (a, Stream (Of a) m r))
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Maybe (a, Stream (Of a) m r)
%1 -> m (Maybe (a, Stream (Of a) m r)))
%1 -> Maybe (a, Stream (Of a) m r)
%1 -> m (Maybe (a, Stream (Of a) m r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a, Stream (Of a) m r) %1 -> Maybe (a, Stream (Of a) m r)
forall a. a -> Maybe a
Just (a
a, Stream (Of a) m r
as)
{-# INLINABLE uncons #-}
splitAt :: forall f m r. (Control.Monad m, Control.Functor f) =>
Int -> Stream f m r %1-> Stream f m (Stream f m r)
splitAt :: forall (f :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r %1 -> Stream f m (Stream f m r)
splitAt Int
n Stream f m r
stream = Int -> Stream f m r %1 -> Stream f m (Stream f m r)
loop Int
n Stream f m r
stream where
loop :: Int -> Stream f m r %1-> Stream f m (Stream f m r)
loop :: Int -> Stream f m r %1 -> Stream f m (Stream f m r)
loop Int
n Stream f m r
stream = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
Prelude.compare Int
n Int
0 of
Ordering
GT -> Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream f m (Stream f m r))
%1 -> Stream f m (Stream f m r)
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Stream f m r %1 -> Stream f m (Stream f m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (r %1 -> Stream f m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r)
Effect m (Stream f m r)
m -> m (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r)
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r))
%1 -> m (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ m (Stream f m r)
m m (Stream f m r)
%1 -> (Stream f m r %1 -> m (Stream f m (Stream f m r)))
%1 -> m (Stream f m (Stream f m r))
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= (Stream f m (Stream f m r) %1 -> m (Stream f m (Stream f m r))
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream f m (Stream f m r) %1 -> m (Stream f m (Stream f m r)))
%1 -> (Stream f m r %1 -> Stream f m (Stream f m r))
%1 -> Stream f m r
%1 -> m (Stream f m (Stream f m r))
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. Int -> Stream f m r %1 -> Stream f m (Stream f m r)
forall (f :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r %1 -> Stream f m (Stream f m r)
splitAt Int
n)
Step f (Stream f m r)
f -> f (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (f (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r))
%1 -> f (Stream f m (Stream f m r)) %1 -> Stream f m (Stream f m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream f m (Stream f m r))
%1 -> f (Stream f m r) %1 -> f (Stream f m (Stream f m r))
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (Int -> Stream f m r %1 -> Stream f m (Stream f m r)
forall (f :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r %1 -> Stream f m (Stream f m r)
splitAt (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) f (Stream f m r)
f
Ordering
_ -> Stream f m r %1 -> Stream f m (Stream f m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return Stream f m r
stream
{-# INLINABLE splitAt #-}
split :: forall a m r. (Eq a, Control.Monad m) =>
a -> Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
split :: forall a (m :: * -> *) r.
(Eq a, Monad m) =>
a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
split a
x Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
loop :: Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Stream (Of a) m) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Stream (Of a) m) m r) %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ m (Stream (Of a) m r)
m m (Stream (Of a) m r)
%1 -> (Stream (Of a) m r %1 -> m (Stream (Stream (Of a) m) m r))
%1 -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= (Stream (Stream (Of a) m) m r %1 -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Stream (Of a) m) m r
%1 -> m (Stream (Stream (Of a) m) m r))
%1 -> (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Of a) m r
%1 -> m (Stream (Stream (Of a) m) m r)
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
(Eq a, Monad m) =>
a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
split a
x)
Step (a
a :> Stream (Of a) m r
as) -> case a
a a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x of
Bool
True -> a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
(Eq a, Monad m) =>
a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
split a
x Stream (Of a) m r
as
Bool
False -> a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) a r.
Monad m =>
a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
consFirstChunk a
a (a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
(Eq a, Monad m) =>
a -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
split a
x Stream (Of a) m r
as)
{-# INLINABLE split #-}
break :: forall a m r. Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
break :: forall a (m :: * -> *) r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
break a -> Bool
f Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
loop :: Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). 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))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> m (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> m (Stream (Of a) m r)
%1 -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
break a -> Bool
f) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case a -> Bool
f a
a of
Bool
True -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
as)
Bool
False -> Of a (Stream (Of a) m (Stream (Of a) m r))
%1 -> 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)
%1 -> Of a (Stream (Of a) m (Stream (Of a) m r))
forall a b. a -> b -> Of a b
:> ((a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
break a -> Bool
f Stream (Of a) m r
as))
{-# INLINABLE break #-}
breaks :: forall a m r. Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
breaks :: forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
breaks a -> Bool
f Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
loop :: Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Stream (Of a) m) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Stream (Of a) m) m r) %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
breaks a -> Bool
f) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case a -> Bool
f a
a of
Bool
True -> (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
breaks a -> Bool
f Stream (Of a) m r
as
Bool
False -> a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) a r.
Monad m =>
a
-> Stream (Stream (Of a) m) m r %1 -> Stream (Stream (Of a) m) m r
consFirstChunk a
a ((a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
breaks a -> Bool
f Stream (Of a) m r
as)
{-# INLINABLE breaks #-}
breakWhen :: forall m a x b r. Control.Monad m
=> (x -> a -> x) -> x -> (x -> b) -> (b -> Bool)
-> Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
breakWhen :: forall (m :: * -> *) a x b r.
Monad m =>
(x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
breakWhen x -> a -> x
step x
x x -> b
end b -> Bool
pred Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
loop :: Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). 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))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> m (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> m (Stream (Of a) m r)
%1 -> m (Stream (Of a) m (Stream (Of a) m r))
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a x b r.
Monad m =>
(x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
breakWhen x -> a -> x
step x
x x -> b
end b -> Bool
pred) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case b -> Bool
pred (x -> b
end (x -> a -> x
step x
x a
a)) of
Bool
False -> Of a (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r))
%1 -> Of a (Stream (Of a) m (Stream (Of a) m r))
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a a
-> Stream (Of a) m (Stream (Of a) m r)
%1 -> Of a (Stream (Of a) m (Stream (Of a) m r))
forall a b. a -> b -> Of a b
:> ((x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a x b r.
Monad m =>
(x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
breakWhen x -> a -> x
step (x -> a -> x
step x
x a
a) x -> b
end b -> Bool
pred Stream (Of a) m r
as)
Bool
True -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
as))
{-# INLINABLE breakWhen #-}
breakWhen' :: Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
breakWhen' :: forall (m :: * -> *) a r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
breakWhen' a -> Bool
f Stream (Of a) m r
stream = (Bool -> a -> Bool)
-> Bool
-> (Bool -> Bool)
-> (Bool -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
forall (m :: * -> *) a x b r.
Monad m =>
(x -> a -> x)
-> x
-> (x -> b)
-> (b -> Bool)
-> Stream (Of a) m r
%1 -> Stream (Of a) m (Stream (Of a) m r)
breakWhen (\Bool
_ a
a -> a -> Bool
f a
a) Bool
True Bool -> Bool
forall a. a -> a
id Bool -> Bool
forall a. a -> a
id Stream (Of a) m r
stream
{-# INLINE breakWhen' #-}
span :: Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)
span :: forall (m :: * -> *) a r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
span a -> Bool
f = (a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
forall a (m :: * -> *) r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r)
break (Bool -> Bool
Prelude.not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. a -> Bool
f)
{-# INLINE span #-}
groupBy :: forall a m r. Control.Monad m =>
(a -> a -> Bool) -> Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
groupBy :: forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
loop :: Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Stream (Of a) m) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Stream (Of a) m) m r) %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> Stream (Of a) m r
as Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (r %1 -> Stream (Stream (Of a) m) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r)))
Effect m (Stream (Of a) m r)
m -> m (Stream (Stream (Of a) m) m r) %1 -> Stream (Stream (Of a) m) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$
m (Stream (Of a) m r)
m m (Stream (Of a) m r)
%1 -> (Stream (Of a) m r %1 -> m (Stream (Stream (Of a) m) m r))
%1 -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= (\Stream (Of a) m r
s -> Stream (Stream (Of a) m) m r %1 -> m (Stream (Stream (Of a) m) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Stream (Of a) m) m r
%1 -> m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Stream (Of a) m) m r
%1 -> m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals (Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
s)))
Step (a
a' :> Stream (Of a) m r
as') -> case a -> a -> Bool
equals a
a a
a' of
Bool
False ->
Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> 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)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> (Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals (Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
as')))
Bool
True ->
Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> 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)
%1 -> Stream (Stream (Of a) m) m r)
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Stream (Stream (Of a) m) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a' a
-> Stream (Of a) m (Stream (Stream (Of a) m) m r)
%1 -> Of a (Stream (Of a) m (Stream (Stream (Of a) m) m r))
forall a b. a -> b -> Of a b
:> (Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r))
%1 -> Stream (Stream (Of a) m) m r
%1 -> Stream (Of a) m (Stream (Stream (Of a) m) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
equals Stream (Of a) m r
as'))
{-# INLINABLE groupBy #-}
group :: (Control.Monad m, Eq a) =>
Stream (Of a) m r %1-> Stream (Stream (Of a) m) m r
group :: forall (m :: * -> *) a r.
(Monad m, Eq a) =>
Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
group = (a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
forall a (m :: * -> *) r.
Monad m =>
(a -> a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r
groupBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE group #-}
distinguish :: (a -> Bool) -> Of a r -> Sum (Of a) (Of a) r
distinguish :: forall a r. (a -> Bool) -> Of a r -> Sum (Of a) (Of a) r
distinguish a -> Bool
predicate (a
a :> r
b) = case a -> Bool
predicate a
a of
Bool
True -> 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)
Bool
False -> 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 #-}
switch :: Sum f g r -> Sum g f r
switch :: forall (f :: * -> *) (g :: * -> *) r. Sum f g r -> Sum g f r
switch Sum f g r
s = case Sum f g r
s of InL f r
a -> f r -> Sum g f r
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR f r
a; InR g r
a -> g r -> Sum g f r
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL g r
a
{-# INLINE switch #-}
sumToEither :: Sum (Of a) (Of b) r -> Of (Either a b) r
sumToEither :: forall a b r. 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 :: forall a b r. 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 :: forall (f :: * -> *) r. 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 :: forall (f :: * -> *) r. 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 #-}
separate :: forall m f g r.
(Control.Monad m, Control.Functor f, Control.Functor g) =>
Stream (Sum f g) m r -> Stream f (Stream g m) r
separate :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor f, Functor g) =>
Stream (Sum f g) m r -> Stream f (Stream g m) r
separate Stream (Sum f g) m r
stream = Stream (Sum f g) m r
%1 -> (Sum f g (Stream f (Stream g m) r)
%1 -> Stream f (Stream g m) r)
-> (m (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r)
-> (r %1 -> Stream f (Stream g m) r)
-> Stream f (Stream g m) r
forall (f :: * -> *) (m :: * -> *) r b.
(Functor f, Monad m) =>
Stream f m r
%1 -> (f b %1 -> b) -> (m b %1 -> b) -> (r %1 -> b) -> b
destroyExposed Stream (Sum f g) m r
stream Sum f g (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r
fromSum (Stream g m (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream g m (Stream f (Stream g m) r)
%1 -> Stream f (Stream g m) r)
%1 -> (m (Stream f (Stream g m) r)
%1 -> Stream g m (Stream f (Stream g m) r))
%1 -> m (Stream f (Stream g m) r)
%1 -> Stream f (Stream g m) r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. m (Stream f (Stream g m) r)
%1 -> Stream g m (Stream f (Stream g m) r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift) r %1 -> Stream f (Stream g m) r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return
where
fromSum :: Sum f g (Stream f (Stream g m) r) %1-> (Stream f (Stream g m) r)
fromSum :: Sum f g (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r
fromSum Sum f g (Stream f (Stream g m) r)
x = Sum f g (Stream f (Stream g m) r)
x Sum f g (Stream f (Stream g m) r)
%1 -> (Sum f g (Stream f (Stream g m) r)
%1 -> Stream f (Stream g m) r)
%1 -> Stream f (Stream g m) r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
InL f (Stream f (Stream g m) r)
fss -> f (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step f (Stream f (Stream g m) r)
fss
InR g (Stream f (Stream g m) r)
gss -> Stream g m (Stream f (Stream g m) r) %1 -> Stream f (Stream g m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (g (Stream g m (Stream f (Stream g m) r))
%1 -> Stream g m (Stream f (Stream g m) r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (g (Stream g m (Stream f (Stream g m) r))
%1 -> Stream g m (Stream f (Stream g m) r))
%1 -> g (Stream g m (Stream f (Stream g m) r))
%1 -> Stream g m (Stream f (Stream g m) r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f (Stream g m) r
%1 -> Stream g m (Stream f (Stream g m) r))
%1 -> g (Stream f (Stream g m) r)
%1 -> g (Stream g m (Stream f (Stream g m) r))
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f (Stream g m) r %1 -> Stream g m (Stream f (Stream g m) r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return g (Stream f (Stream g m) r)
gss)
{-# INLINABLE separate #-}
unseparate :: (Control.Monad m, Control.Functor f, Control.Functor g) =>
Stream f (Stream g m) r -> Stream (Sum f g) m r
unseparate :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor f, Functor g) =>
Stream f (Stream g m) r -> Stream (Sum f g) m r
unseparate Stream f (Stream g m) r
stream =
Stream f (Stream g m) r
%1 -> (f (Stream (Sum f g) m r) %1 -> Stream (Sum f g) m r)
-> (Stream g m (Stream (Sum f g) m r) %1 -> Stream (Sum f g) m r)
-> (r %1 -> Stream (Sum f g) m r)
-> Stream (Sum f g) m r
forall (f :: * -> *) (m :: * -> *) r b.
(Functor f, Monad m) =>
Stream f m r
%1 -> (f b %1 -> b) -> (m b %1 -> b) -> (r %1 -> b) -> b
destroyExposed Stream f (Stream g m) r
stream (Sum f g (Stream (Sum f g) m r) %1 -> Stream (Sum f g) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Sum f g (Stream (Sum f g) m r) %1 -> Stream (Sum f g) m r)
%1 -> (f (Stream (Sum f g) m r)
%1 -> Sum f g (Stream (Sum f g) m r))
%1 -> f (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. f (Stream (Sum f g) m r) %1 -> Sum f g (Stream (Sum f g) m r)
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). f a -> Sum f g a
InL) (Stream (Sum f g) m (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m r
forall (m :: * -> *) a. Monad m => m (m a) %1 -> m a
Control.join (Stream (Sum f g) m (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m r)
%1 -> (Stream g m (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m (Stream (Sum f g) m r))
%1 -> Stream g m (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. (forall x. g x %1 -> Sum f g x)
-> Stream g m (Stream (Sum f g) m r)
%1 -> Stream (Sum f g) m (Stream (Sum f g) m r)
forall (f :: * -> *) (g :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
maps forall x. g x %1 -> Sum f g x
forall {k} (f :: k -> *) (g :: k -> *) (a :: k). g a -> Sum f g a
InR) r %1 -> Stream (Sum f g) m r
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return
{-# INLINABLE unseparate #-}
partition :: forall a m r. Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) (Stream (Of a) m) r
partition :: forall a (m :: * -> *) r.
Monad m =>
(a -> Bool)
-> Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
partition a -> Bool
pred = Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) (Stream (Of a) m) r
loop :: Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) (Stream (Of a) m) r
forall r (f :: * -> *) (m :: * -> *). 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)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect ((Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m (Stream (Of a) m r)
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of a) m r) %1 -> Stream (Of a) m (Stream (Of a) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift m (Stream (Of a) m r)
m))
Step (a
a :> Stream (Of a) m r
as) -> case a -> Bool
pred a
a of
Bool
True -> Of a (Stream (Of a) (Stream (Of a) m) r)
%1 -> 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
%1 -> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
as)
Bool
False -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> 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 (Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a a
-> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> 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
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
as))
partitionEithers :: Control.Monad m =>
Stream (Of (Either a b)) m r %1-> Stream (Of a) (Stream (Of b) m) r
partitionEithers :: forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
partitionEithers = Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
loop
where
loop :: Control.Monad m =>
Stream (Of (Either a b)) m r %1-> Stream (Of a) (Stream (Of b) m) r
loop :: forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
loop Stream (Of (Either a b)) m r
stream = Stream (Of (Either a b)) m r
stream Stream (Of (Either a b)) m r
%1 -> (Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) (Stream (Of b) m) r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of (Either a b)) m r)
m -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of b) m (Stream (Of (Either a b)) m r)
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
loop (m (Stream (Of (Either a b)) m r)
%1 -> Stream (Of b) m (Stream (Of (Either a b)) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift m (Stream (Of (Either a b)) m r)
m)
Step (Left a
a :> Stream (Of (Either a b)) m r
as) -> Of a (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a
-> Stream (Of a) (Stream (Of b) m) r
%1 -> Of a (Stream (Of a) (Stream (Of b) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
loop Stream (Of (Either a b)) m r
as)
Step (Right b
b :> Stream (Of (Either a b)) m r
as) -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Stream (Of a) (Stream (Of b) m) r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Of b (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r))
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of b (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r))
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r))
%1 -> Of b (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r))
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ b
b b
-> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
%1 -> Of b (Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r))
forall a b. a -> b -> Of a b
:> Stream (Of a) (Stream (Of b) m) r
%1 -> Stream (Of b) m (Stream (Of a) (Stream (Of b) m) r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
forall (m :: * -> *) a b r.
Monad m =>
Stream (Of (Either a b)) m r
%1 -> Stream (Of a) (Stream (Of b) m) r
loop Stream (Of (Either a b)) m r
as))
catMaybes :: Control.Monad m => Stream (Of (Maybe a)) m r %1-> Stream (Of a) m r
catMaybes :: forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
catMaybes Stream (Of (Maybe a)) m r
stream = Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
loop Stream (Of (Maybe a)) m r
stream
where
loop :: Control.Monad m => Stream (Of (Maybe a)) m r %1-> Stream (Of a) m r
loop :: forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
loop Stream (Of (Maybe a)) m r
stream = Stream (Of (Maybe a)) m r
stream Stream (Of (Maybe a)) m r
%1 -> (Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of (Maybe a)) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of (Maybe a)) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
catMaybes m (Stream (Of (Maybe a)) m r)
m
Step (Maybe a
maybe :> Stream (Of (Maybe a)) m r
as) -> case Maybe a
maybe of
Maybe a
Nothing -> Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
catMaybes Stream (Of (Maybe a)) m r
as
Just a
a -> Of a (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of a (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> Of a (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ a
a a -> Stream (Of a) m r %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> (Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
forall (m :: * -> *) a r.
Monad m =>
Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r
catMaybes Stream (Of (Maybe a)) m r
as)
{-# INLINABLE catMaybes #-}
mapMaybe :: forall a b m r. Control.Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1-> Stream (Of b) m r
mapMaybe :: forall a b (m :: * -> *) r.
Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybe a -> Maybe b
f Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Of b) m r
loop :: Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of b) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of b) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
ms -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ m (Stream (Of a) m r)
ms m (Stream (Of a) m r)
%1 -> (Stream (Of a) m r %1 -> m (Stream (Of b) m r))
%1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a b.
Monad m =>
m a %1 -> (a %1 -> m b) %1 -> m b
Control.>>= (Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of a) m r
%1 -> m (Stream (Of b) m r)
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. (a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a b (m :: * -> *) r.
Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybe a -> Maybe b
f)
Step (a
a :> Stream (Of a) m r
s) -> case a -> Maybe b
f a
a of
Just b
b -> Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ b
b b -> Stream (Of b) m r %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> ((a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a b (m :: * -> *) r.
Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybe a -> Maybe b
f Stream (Of a) m r
s)
Maybe b
Nothing -> (a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a b (m :: * -> *) r.
Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybe a -> Maybe b
f Stream (Of a) m r
s
{-# INLINABLE mapMaybe #-}
mapMaybeM :: forall a m b r. Control.Monad m =>
(a -> m (Maybe (Ur b))) -> Stream (Of a) m r %1-> Stream (Of b) m r
mapMaybeM :: forall a (m :: * -> *) b r.
Monad m =>
(a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybeM a -> m (Maybe (Ur b))
f Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Of b) m r
loop :: Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of b) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of b) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of b) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a (m :: * -> *) b r.
Monad m =>
(a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybeM a -> m (Maybe (Ur b))
f) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Maybe (Ur b)
mb <- a -> m (Maybe (Ur b))
f a
a
Maybe (Ur b)
mb Maybe (Ur b)
%1 -> (Maybe (Ur b) %1 -> m (Stream (Of b) m r))
%1 -> m (Stream (Of b) m r)
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Maybe (Ur b)
Nothing -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a (m :: * -> *) b r.
Monad m =>
(a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybeM a -> m (Maybe (Ur b))
f Stream (Of a) m r
as
Just (Ur b
b) -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of b (Stream (Of b) m r) %1 -> 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 %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> (a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
forall a (m :: * -> *) b r.
Monad m =>
(a -> m (Maybe (Ur b)))
-> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybeM a -> m (Maybe (Ur b))
f Stream (Of a) m r
as)
{-# INLINABLE mapMaybeM #-}
hoist :: forall f m n r. (Control.Monad m, Control.Functor f) =>
(forall a. m a %1-> n a) ->
Stream f m r %1-> Stream f n r
hoist :: forall (f :: * -> *) (m :: * -> *) (n :: * -> *) r.
(Monad m, Functor f) =>
(forall a. m a %1 -> n a) -> Stream f m r %1 -> Stream f n r
hoist forall a. m a %1 -> n a
f Stream f m r
stream = Stream f m r %1 -> Stream f n r
loop Stream f m r
stream where
loop :: Stream f m r %1-> Stream f n r
loop :: Stream f m r %1 -> Stream f n r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream f n r) %1 -> Stream f n r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream f n r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> n (Stream f n r) %1 -> Stream f n r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (n (Stream f n r) %1 -> Stream f n r)
%1 -> n (Stream f n r) %1 -> Stream f n r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ m (Stream f n r) %1 -> n (Stream f n r)
forall a. m a %1 -> n a
f (m (Stream f n r) %1 -> n (Stream f n r))
%1 -> m (Stream f n r) %1 -> n (Stream f n r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream f n r)
%1 -> m (Stream f m r) %1 -> m (Stream f n r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream f n r
loop m (Stream f m r)
m
Step f (Stream f m r)
f -> f (Stream f n r) %1 -> Stream f n r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (f (Stream f n r) %1 -> Stream f n r)
%1 -> f (Stream f n r) %1 -> Stream f n r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream f n r)
%1 -> f (Stream f m r) %1 -> f (Stream f n r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream f n r
loop f (Stream f m r)
f
{-# INLINABLE hoist #-}
map :: Control.Monad m => (a -> b) -> Stream (Of a) m r %1-> Stream (Of b) m r
map :: forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
map a -> b
f = (forall x. Of a x %1 -> Of b x)
-> Stream (Of a) m r %1 -> Stream (Of b) m r
forall (f :: * -> *) (g :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
maps (\(a
x :> x
rest) -> a -> b
f a
x b -> x %1 -> Of b x
forall a b. a -> b -> Of a b
:> x
rest)
{-# INLINABLE map #-}
maps :: forall f g m r . (Control.Monad m, Control.Functor f) =>
(forall x . f x %1-> g x) -> Stream f m r %1-> Stream g m r
maps :: forall (f :: * -> *) (g :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
maps forall x. f x %1 -> g x
phi = Stream f m r %1 -> Stream g m r
loop
where
loop :: Stream f m r %1-> Stream g m r
loop :: Stream f m r %1 -> Stream g m r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream g m r) %1 -> Stream g m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream g m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> m (Stream f m r) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
forall (f :: * -> *) (g :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
maps forall x. f x %1 -> g x
phi) m (Stream f m r)
m
Step f (Stream f m r)
f -> g (Stream g m r) %1 -> Stream g m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (f (Stream g m r) %1 -> g (Stream g m r)
forall x. f x %1 -> g x
phi ((Stream f m r %1 -> Stream g m r)
%1 -> f (Stream f m r) %1 -> f (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop f (Stream f m r)
f))
{-# INLINABLE maps #-}
mapM :: Control.Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1-> Stream (Of b) m r
mapM :: forall (m :: * -> *) a b r.
Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapM a -> m (Ur b)
f Stream (Of a) m r
s = (a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop a -> m (Ur b)
f Stream (Of a) m r
s
where
loop :: Control.Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1-> Stream (Of b) m r
loop :: forall (m :: * -> *) a b r.
Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop a -> m (Ur b)
f Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of b) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of b) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of b) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop a -> m (Ur b)
f) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Ur b
b <- a -> m (Ur b)
f a
a
Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of b (Stream (Of b) m r) %1 -> 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 %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> ((a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop a -> m (Ur b)
f Stream (Of a) m r
as))
{-# INLINABLE mapM #-}
mapsPost :: forall m f g r. (Control.Monad m, Control.Functor g) =>
(forall x. f x %1-> g x) -> Stream f m r %1-> Stream g m r
mapsPost :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor g) =>
(forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r
mapsPost forall x. f x %1 -> g x
phi = Stream f m r %1 -> Stream g m r
loop
where
loop :: Stream f m r %1-> Stream g m r
loop :: Stream f m r %1 -> Stream g m r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream g m r) %1 -> Stream g m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream g m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> m (Stream f m r) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop m (Stream f m r)
m
Step f (Stream f m r)
f -> g (Stream g m r) %1 -> Stream g m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (g (Stream g m r) %1 -> Stream g m r)
%1 -> g (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> g (Stream f m r) %1 -> g (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop (g (Stream f m r) %1 -> g (Stream g m r))
%1 -> g (Stream f m r) %1 -> g (Stream g m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ f (Stream f m r) %1 -> g (Stream f m r)
forall x. f x %1 -> g x
phi f (Stream f m r)
f
{-# INLINABLE mapsPost #-}
mapped :: forall f g m r . (Control.Monad m, Control.Functor f) =>
(forall x. f x %1-> m (g x)) -> Stream f m r %1-> Stream g m r
mapped :: forall (f :: * -> *) (g :: * -> *) (m :: * -> *) r.
(Monad m, Functor f) =>
(forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r
mapped forall x. f x %1 -> m (g x)
phi = Stream f m r %1 -> Stream g m r
loop
where
loop :: Stream f m r %1-> Stream g m r
loop :: Stream f m r %1 -> Stream g m r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream g m r) %1 -> Stream g m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream g m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> m (Stream f m r) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop m (Stream f m r)
m
Step f (Stream f m r)
f -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (g (Stream g m r) %1 -> Stream g m r)
%1 -> m (g (Stream g m r)) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap g (Stream g m r) %1 -> Stream g m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (m (g (Stream g m r)) %1 -> m (Stream g m r))
%1 -> m (g (Stream g m r)) %1 -> m (Stream g m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ f (Stream g m r) %1 -> m (g (Stream g m r))
forall x. f x %1 -> m (g x)
phi (f (Stream g m r) %1 -> m (g (Stream g m r)))
%1 -> f (Stream g m r) %1 -> m (g (Stream g m r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> f (Stream f m r) %1 -> f (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop f (Stream f m r)
f
{-# INLINABLE mapped #-}
mapsMPost :: forall m f g r. (Control.Monad m, Control.Functor g) =>
(forall x. f x %1-> m (g x)) -> Stream f m r %1-> Stream g m r
mapsMPost :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor g) =>
(forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r
mapsMPost forall x. f x %1 -> m (g x)
phi = Stream f m r %1 -> Stream g m r
loop
where
loop :: Stream f m r %1-> Stream g m r
loop :: Stream f m r %1 -> Stream g m r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream g m r) %1 -> Stream g m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream g m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> m (Stream f m r) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop m (Stream f m r)
m
Step f (Stream f m r)
f -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (g (Stream f m r) %1 -> Stream g m r)
%1 -> m (g (Stream f m r)) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (g (Stream g m r) %1 -> Stream g m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (g (Stream g m r) %1 -> Stream g m r)
%1 -> (g (Stream f m r) %1 -> g (Stream g m r))
%1 -> g (Stream f m r)
%1 -> Stream g m r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. (Stream f m r %1 -> Stream g m r)
%1 -> g (Stream f m r) %1 -> g (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop) (m (g (Stream f m r)) %1 -> m (Stream g m r))
%1 -> m (g (Stream f m r)) %1 -> m (Stream g m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ f (Stream f m r) %1 -> m (g (Stream f m r))
forall x. f x %1 -> m (g x)
phi f (Stream f m r)
f
{-# INLINABLE mapsMPost #-}
mappedPost :: forall m f g r. (Control.Monad m, Control.Functor g) =>
(forall x. f x %1-> m (g x)) -> Stream f m r %1-> Stream g m r
mappedPost :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) r.
(Monad m, Functor g) =>
(forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r
mappedPost forall x. f x %1 -> m (g x)
phi = Stream f m r %1 -> Stream g m r
loop
where
loop :: Stream f m r %1-> Stream g m r
loop :: Stream f m r %1 -> Stream g m r
loop Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream g m r) %1 -> Stream g m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream g m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream f m r %1 -> Stream g m r)
%1 -> m (Stream f m r) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop m (Stream f m r)
m
Step f (Stream f m r)
f -> m (Stream g m r) %1 -> Stream g m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream g m r) %1 -> Stream g m r)
%1 -> m (Stream g m r) %1 -> Stream g m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (g (Stream f m r) %1 -> Stream g m r)
%1 -> m (g (Stream f m r)) %1 -> m (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (g (Stream g m r) %1 -> Stream g m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (g (Stream g m r) %1 -> Stream g m r)
%1 -> (g (Stream f m r) %1 -> g (Stream g m r))
%1 -> g (Stream f m r)
%1 -> Stream g m r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. (Stream f m r %1 -> Stream g m r)
%1 -> g (Stream f m r) %1 -> g (Stream g m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream f m r %1 -> Stream g m r
loop) (m (g (Stream f m r)) %1 -> m (Stream g m r))
%1 -> m (g (Stream f m r)) %1 -> m (Stream g m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ f (Stream f m r) %1 -> m (g (Stream f m r))
forall x. f x %1 -> m (g x)
phi f (Stream f m r)
f
{-# INLINABLE mappedPost #-}
for :: forall f m r a x . (Control.Monad m, Control.Functor f, Consumable x) =>
Stream (Of a) m r %1-> (a -> Stream f m x) -> Stream f m r
for :: forall (f :: * -> *) (m :: * -> *) r a x.
(Monad m, Functor f, Consumable x) =>
Stream (Of a) m r %1 -> (a -> Stream f m x) -> Stream f m r
for Stream (Of a) m r
stream a -> Stream f m x
expand = Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream f m r
loop :: Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream f m r) %1 -> Stream f m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream f m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream f m r) %1 -> Stream f m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m r) %1 -> Stream f m r)
%1 -> m (Stream f m r) %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream f m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream f m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream f m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> Control.do
x
x <- a -> Stream f m x
expand a
a
x %1 -> Stream f m r %1 -> Stream f m r
forall a b. Consumable a => a %1 -> b %1 -> b
lseq x
x (Stream f m r %1 -> Stream f m r)
%1 -> Stream f m r %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
as
{-# INLINABLE for #-}
with :: forall f m r a x . (Control.Monad m, Control.Functor f, Consumable x) =>
Stream (Of a) m r %1-> (a -> f x) -> Stream f m r
with :: forall (f :: * -> *) (m :: * -> *) r a x.
(Monad m, Functor f, Consumable x) =>
Stream (Of a) m r %1 -> (a -> f x) -> Stream f m r
with Stream (Of a) m r
s a -> f x
f = Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
s
where
loop :: Stream (Of a) m r %1-> Stream f m r
loop :: Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream f m r) %1 -> Stream f m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream f m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream f m r) %1 -> Stream f m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m r) %1 -> Stream f m r)
%1 -> m (Stream f m r) %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream f m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream f m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream f m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> f (Stream f m r) %1 -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (f (Stream f m r) %1 -> Stream f m r)
%1 -> f (Stream f m r) %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (x %1 -> Stream f m r) %1 -> f x %1 -> f (Stream f m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (x %1 -> Stream f m r %1 -> Stream f m r
forall a b. Consumable a => a %1 -> b %1 -> b
`lseq` (Stream (Of a) m r %1 -> Stream f m r
loop Stream (Of a) m r
as)) (a -> f x
f a
a)
{-# INLINABLE with #-}
subst :: (Control.Monad m, Control.Functor f, Consumable x) =>
(a -> f x) -> Stream (Of a) m r %1-> Stream f m r
subst :: forall (m :: * -> *) (f :: * -> *) x a r.
(Monad m, Functor f, Consumable x) =>
(a -> f x) -> Stream (Of a) m r %1 -> Stream f m r
subst = (Stream (Of a) m r %1 -> (a -> f x) -> Stream f m r)
-> (a -> f x) -> Stream (Of a) m r %1 -> Stream f m r
forall a b c. (a %1 -> b -> c) -> b -> a %1 -> c
flip Stream (Of a) m r %1 -> (a -> f x) -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r a x.
(Monad m, Functor f, Consumable x) =>
Stream (Of a) m r %1 -> (a -> f x) -> Stream f m r
with where
flip :: (a %1-> b -> c) -> b -> a %1-> c
flip :: forall a b c. (a %1 -> b -> c) -> b -> a %1 -> c
flip a %1 -> b -> c
f b
b a
a = a %1 -> b -> c
f a
a b
b
{-# INLINE subst #-}
copy :: forall a m r . Control.Monad m =>
Stream (Of a) m r %1-> Stream (Of a) (Stream (Of a) m) r
copy :: forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
copy = Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> (Stream (Of a) (Stream (Of a) m) r
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> Stream (Of a) (Stream (Of a) m) r
%1 -> Stream (Of a) (Stream (Of a) m) r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. Stream (Of a) (Stream (Of a) m) r
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of a) (Stream (Of a) m) r
%1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m r
%1 -> Stream (Of a) (Stream (Of a) m) r
forall b c a. (b %1 -> c) %1 -> (a %1 -> b) %1 -> a %1 -> c
. Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) (Stream (Of a) m) r
loop :: Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) (Stream (Of a) m) r
forall r (f :: * -> *) (m :: * -> *). 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)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m (Stream (Of a) m r)
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop (m (Stream (Of a) m r) %1 -> Stream (Of a) m (Stream (Of a) m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift m (Stream (Of a) m r)
m)
Step (a
a :> Stream (Of a) m r
as) -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
%1 -> Stream (Of a) (Stream (Of a) m) r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r))
%1 -> 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)
%1 -> 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
%1 -> Stream (Of a) m (Stream (Of a) (Stream (Of a) m) r)
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return (Of a (Stream (Of a) (Stream (Of a) m) r)
%1 -> 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
%1 -> Of a (Stream (Of a) (Stream (Of a) m) r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
loop Stream (Of a) m r
as)))
{-# INLINABLE copy#-}
duplicate :: forall a m r . Control.Monad m =>
Stream (Of a) m r %1-> Stream (Of a) (Stream (Of a) m) r
duplicate :: forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
duplicate = Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
copy
{-# INLINE duplicate#-}
store :: Control.Monad m =>
(Stream (Of a) (Stream (Of a) m) r %1-> t) -> Stream (Of a) m r %1-> t
store :: forall (m :: * -> *) a r t.
Monad m =>
(Stream (Of a) (Stream (Of a) m) r %1 -> t)
-> Stream (Of a) m r %1 -> t
store Stream (Of a) (Stream (Of a) m) r %1 -> t
f Stream (Of a) m r
x = Stream (Of a) (Stream (Of a) m) r %1 -> t
f (Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r
copy Stream (Of a) m r
x)
{-# INLINE store #-}
chain :: forall a m r y . (Control.Monad m, Consumable y) =>
(a -> m y) -> Stream (Of a) m r %1-> Stream (Of a) m r
chain :: forall a (m :: * -> *) r y.
(Monad m, Consumable y) =>
(a -> m y) -> Stream (Of a) m r %1 -> Stream (Of a) m r
chain a -> m y
f = Stream (Of a) m r %1 -> Stream (Of a) m r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> 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) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
y
y <- a -> m y
f a
a
Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of a) m r %1 -> m (Stream (Of a) m r))
%1 -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ y %1 -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a b. Consumable a => a %1 -> b %1 -> b
lseq y
y (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as)
{-# INLINABLE chain #-}
sequence :: forall a m r . Control.Monad m =>
Stream (Of (m (Ur a))) m r %1-> Stream (Of a) m r
sequence :: forall a (m :: * -> *) r.
Monad m =>
Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r
sequence = Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r
loop
where
loop :: Stream (Of (m (Ur a))) m r %1-> Stream (Of a) m r
loop :: Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r
loop Stream (Of (m (Ur a))) m r
stream = Stream (Of (m (Ur a))) m r
stream Stream (Of (m (Ur a))) m r
%1 -> (Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of (m (Ur a))) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of (m (Ur a))) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r
loop m (Stream (Of (m (Ur a))) m r)
m
Step (m (Ur a)
ma :> Stream (Of (m (Ur a))) m r
mas) -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Ur a
a <- m (Ur a)
ma
Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of a) m r %1 -> m (Stream (Of a) m r))
%1 -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of (m (Ur a))) m r %1 -> Stream (Of a) m r
loop Stream (Of (m (Ur a))) m r
mas)
{-# INLINABLE sequence #-}
nubOrd :: (Control.Monad m, Ord a) => Stream (Of a) m r %1-> Stream (Of a) m r
nubOrd :: forall (m :: * -> *) a r.
(Monad m, Ord a) =>
Stream (Of a) m r %1 -> Stream (Of a) m r
nubOrd = (a -> a) -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall (m :: * -> *) a b r.
(Monad m, Ord b) =>
(a -> b) -> Stream (Of a) m r %1 -> Stream (Of a) m r
nubOrdOn a -> a
forall a. a -> a
id
{-# INLINE nubOrd #-}
nubOrdOn :: forall m a b r . (Control.Monad m, Ord b) =>
(a -> b) -> Stream (Of a) m r %1-> Stream (Of a) m r
nubOrdOn :: forall (m :: * -> *) a b r.
(Monad m, Ord b) =>
(a -> b) -> Stream (Of a) m r %1 -> Stream (Of a) m r
nubOrdOn a -> b
f Stream (Of a) m r
xs = Set b -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Set b
forall a. Set a
Set.empty Stream (Of a) m r
xs
where
loop :: Set.Set b -> Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Set b -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop !Set b
set Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (Set b -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Set b
set) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case b -> Set b -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member (a -> b
f a
a) Set b
set of
Bool
True -> Set b -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Set b
set Stream (Of a) m r
as
Bool
False-> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Set b -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop (b -> Set b -> Set b
forall a. Ord a => a -> Set a -> Set a
Set.insert (a -> b
f a
a) Set b
set) Stream (Of a) m r
as)
nubInt :: Control.Monad m => Stream (Of Int) m r %1-> Stream (Of Int) m r
nubInt :: forall (m :: * -> *) r.
Monad m =>
Stream (Of Int) m r %1 -> Stream (Of Int) m r
nubInt = (Int -> Int) -> Stream (Of Int) m r %1 -> Stream (Of Int) m r
forall (m :: * -> *) a r.
Monad m =>
(a -> Int) -> Stream (Of a) m r %1 -> Stream (Of a) m r
nubIntOn Int -> Int
forall a. a -> a
id
{-# INLINE nubInt #-}
nubIntOn :: forall m a r . (Control.Monad m) =>
(a -> Int) -> Stream (Of a) m r %1-> Stream (Of a) m r
nubIntOn :: forall (m :: * -> *) a r.
Monad m =>
(a -> Int) -> Stream (Of a) m r %1 -> Stream (Of a) m r
nubIntOn a -> Int
f Stream (Of a) m r
xs = IntSet -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop IntSet
IntSet.empty Stream (Of a) m r
xs
where
loop :: IntSet.IntSet -> Stream (Of a) m r %1-> Stream (Of a) m r
loop :: IntSet -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop !IntSet
set Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (IntSet -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop IntSet
set) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case Int -> IntSet -> Bool
IntSet.member (a -> Int
f a
a) IntSet
set of
Bool
True -> IntSet -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop IntSet
set Stream (Of a) m r
as
Bool
False-> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> IntSet -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop (Int -> IntSet -> IntSet
IntSet.insert (a -> Int
f a
a) IntSet
set) Stream (Of a) m r
as)
filter :: forall a m r . Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) m r
filter :: forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r
filter a -> Bool
pred = Stream (Of a) m r %1 -> Stream (Of a) m r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream (Of a) m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case a -> Bool
pred a
a of
Bool
True -> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as)
Bool
False -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as
{-# INLINE filter #-}
filterM :: forall a m r . Control.Monad m =>
(a -> m Bool) -> Stream (Of a) m r %1-> Stream (Of a) m r
filterM :: forall a (m :: * -> *) r.
Monad m =>
(a -> m Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r
filterM a -> m Bool
pred = Stream (Of a) m r %1 -> Stream (Of a) m r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m-> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> 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) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Bool
bool <- a -> m Bool
pred a
a
Bool
bool Bool
%1 -> (Bool %1 -> m (Stream (Of a) m r))
%1 -> m (Stream (Of a) m r)
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Bool
True -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of a) m r %1 -> m (Stream (Of a) m r))
%1 -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as)
Bool
False -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of a) m r %1 -> m (Stream (Of a) m r))
%1 -> Stream (Of a) m r %1 -> m (Stream (Of a) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as
{-# INLINE filterM #-}
intersperse :: forall a m r . Control.Monad m =>
a -> Stream (Of a) m r %1-> Stream (Of a) m r
intersperse :: forall a (m :: * -> *) r.
Monad m =>
a -> Stream (Of a) m r %1 -> Stream (Of a) m r
intersperse a
x Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (a -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a (m :: * -> *) r.
Monad m =>
a -> Stream (Of a) m r %1 -> Stream (Of a) m r
intersperse a
x) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> a -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop a
a Stream (Of a) m r
as
where
loop :: a -> Stream (Of a) m r %1-> Stream (Of a) m r
loop :: a -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop !a
a Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r)
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (a -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop a
a) m (Stream (Of a) m r)
m
Step (a
a' :> Stream (Of a) m r
as) -> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> a -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop a
a' Stream (Of a) m r
as))
{-# INLINABLE intersperse #-}
drop :: forall a m r. (HasCallStack, Control.Monad m) =>
Int -> Stream (Of a) m r %1-> Stream (Of a) m r
drop :: forall a (m :: * -> *) r.
(HasCallStack, Monad m) =>
Int -> Stream (Of a) m r %1 -> Stream (Of a) m r
drop Int
n Stream (Of a) m r
stream = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
n Int
0 of
Ordering
LT -> [Char] -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"drop called with negative int" (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Stream (Of a) m r
stream
Ordering
EQ -> Stream (Of a) m r
stream
Ordering
GT -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream where
loop :: Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (Int -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a (m :: * -> *) r.
(HasCallStack, Monad m) =>
Int -> Stream (Of a) m r %1 -> Stream (Of a) m r
drop Int
n) m (Stream (Of a) m r)
m
Step (a
_ :> Stream (Of a) m r
as) -> Int -> Stream (Of a) m r %1 -> Stream (Of a) m r
forall a (m :: * -> *) r.
(HasCallStack, Monad m) =>
Int -> Stream (Of a) m r %1 -> Stream (Of a) m r
drop (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Stream (Of a) m r
as
{-# INLINABLE drop #-}
dropWhile :: forall a m r . Control.Monad m =>
(a -> Bool) -> Stream (Of a) m r %1-> Stream (Of a) m r
dropWhile :: forall a (m :: * -> *) r.
Monad m =>
(a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r
dropWhile a -> Bool
pred = Stream (Of a) m r %1 -> Stream (Of a) m r
loop
where
loop :: Stream (Of a) m r %1-> Stream (Of a) m r
loop :: Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> Stream (Of a) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of a) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of a) m r) %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> Stream (Of a) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of a) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of a) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Stream (Of a) m r %1 -> Stream (Of a) m r
loop m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> case a -> Bool
pred a
a of
Bool
True -> Stream (Of a) m r %1 -> Stream (Of a) m r
loop Stream (Of a) m r
as
Bool
False -> Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
as)
{-# INLINABLE dropWhile #-}
scan :: forall a x b m r . Control.Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1-> Stream (Of b) m r
scan :: forall a x b (m :: * -> *) r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
scan x -> a -> x
step x
begin x -> b
done Stream (Of a) m r
stream = Of b (Stream (Of b) m r) %1 -> 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 %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop x
begin Stream (Of a) m r
stream)
where
loop :: x -> Stream (Of a) m r %1-> Stream (Of b) m r
loop :: x -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop !x
acc Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of b) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of b) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of b) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (x -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop x
acc) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> Of b (Stream (Of b) m r) %1 -> 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 %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> x -> Stream (Of a) m r %1 -> Stream (Of b) m r
loop x
acc' Stream (Of a) m r
as) where
!acc' :: x
acc' = x -> a -> x
step x
acc a
a
{-# INLINABLE scan #-}
scanM :: forall a x b m r . Control.Monad m =>
(x %1-> a -> m (Ur x)) ->
m (Ur x) ->
(x %1-> m (Ur b)) ->
Stream (Of a) m r %1->
Stream (Of b) m r
scanM :: forall a x b (m :: * -> *) r.
Monad m =>
(x %1 -> a -> m (Ur x))
-> m (Ur x)
-> (x %1 -> m (Ur b))
-> Stream (Of a) m r
%1 -> Stream (Of b) m r
scanM x %1 -> a -> m (Ur x)
step m (Ur x)
mx x %1 -> m (Ur b)
done Stream (Of a) m r
stream = Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream
where
loop :: Stream (Of a) m r %1-> Stream (Of b) m r
loop :: Stream (Of a) m r %1 -> Stream (Of b) m r
loop Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> Stream (Of b) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Ur x
x <- m (Ur x)
mx
Ur b
b <- x %1 -> m (Ur b)
done x
x
Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ b
b b -> Stream (Of b) m r %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> r %1 -> Stream (Of b) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of b) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap ((x %1 -> a -> m (Ur x))
-> m (Ur x)
-> (x %1 -> m (Ur b))
-> Stream (Of a) m r
%1 -> Stream (Of b) m r
forall a x b (m :: * -> *) r.
Monad m =>
(x %1 -> a -> m (Ur x))
-> m (Ur x)
-> (x %1 -> m (Ur b))
-> Stream (Of a) m r
%1 -> Stream (Of b) m r
scanM x %1 -> a -> m (Ur x)
step m (Ur x)
mx x %1 -> m (Ur b)
done) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> m (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
Ur x
x <- m (Ur x)
mx
Ur b
b <- x %1 -> m (Ur b)
done x
x
Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream (Of b) m r %1 -> m (Stream (Of b) m r))
%1 -> Stream (Of b) m r %1 -> m (Stream (Of b) m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r)
%1 -> Of b (Stream (Of b) m r) %1 -> Stream (Of b) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ b
b b -> Stream (Of b) m r %1 -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> ((x %1 -> a -> m (Ur x))
-> m (Ur x)
-> (x %1 -> m (Ur b))
-> Stream (Of a) m r
%1 -> Stream (Of b) m r
forall a x b (m :: * -> *) r.
Monad m =>
(x %1 -> a -> m (Ur x))
-> m (Ur x)
-> (x %1 -> m (Ur b))
-> Stream (Of a) m r
%1 -> Stream (Of b) m r
scanM x %1 -> a -> m (Ur x)
step (x %1 -> a -> m (Ur x)
step x
x a
a) x %1 -> m (Ur b)
done Stream (Of a) m r
as)
{-# INLINABLE scanM #-}
scanned :: forall a x b m r . Control.Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1-> Stream (Of (a,b)) m r
scanned :: forall a x b (m :: * -> *) r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r
scanned x -> a -> x
step x
begin x -> b
done = x -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r
loop x
begin
where
loop :: x -> Stream (Of a) m r %1-> Stream (Of (a,b)) m r
loop :: x -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r
loop !x
x Stream (Of a) m r
stream = Stream (Of a) m r
stream Stream (Of a) m r
%1 -> (Stream (Of a) m r %1 -> Stream (Of (a, b)) m r)
%1 -> Stream (Of (a, b)) m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream (Of (a, b)) m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream (Of a) m r)
m -> m (Stream (Of (a, b)) m r) %1 -> Stream (Of (a, b)) m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream (Of (a, b)) m r) %1 -> Stream (Of (a, b)) m r)
%1 -> m (Stream (Of (a, b)) m r) %1 -> Stream (Of (a, b)) m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Stream (Of a) m r %1 -> Stream (Of (a, b)) m r)
%1 -> m (Stream (Of a) m r) %1 -> m (Stream (Of (a, b)) m r)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap (x -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r
loop x
x) m (Stream (Of a) m r)
m
Step (a
a :> Stream (Of a) m r
as) -> Control.do
let !acc :: b
acc = x -> b
done (x -> a -> x
step x
x a
a)
Of (a, b) (Stream (Of (a, b)) m ()) %1 -> Stream (Of (a, b)) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of (a, b) (Stream (Of (a, b)) m ()) %1 -> Stream (Of (a, b)) m ())
%1 -> Of (a, b) (Stream (Of (a, b)) m ())
%1 -> Stream (Of (a, b)) m ()
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (a
a, b
acc) (a, b)
-> Stream (Of (a, b)) m () -> Of (a, b) (Stream (Of (a, b)) m ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of (a, b)) m ()
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return ()
x -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r
loop (x -> a -> x
step x
x a
a) Stream (Of a) m r
as
{-# INLINABLE scanned #-}
read :: (Control.Monad m, Read a) =>
Stream (Of String) m r %1-> Stream (Of a) m r
read :: forall (m :: * -> *) a r.
(Monad m, Read a) =>
Stream (Of [Char]) m r %1 -> Stream (Of a) m r
read = ([Char] -> Maybe a)
-> Stream (Of [Char]) m r %1 -> Stream (Of a) m r
forall a b (m :: * -> *) r.
Monad m =>
(a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
mapMaybe [Char] -> Maybe a
forall a. Read a => [Char] -> Maybe a
readMaybe
{-# INLINE read #-}
delay :: forall a r. Double -> Stream (Of a) IO r %1-> Stream (Of a) IO r
delay :: forall a r. Double -> Stream (Of a) IO r %1 -> Stream (Of a) IO r
delay Double
seconds = Stream (Of a) IO r %1 -> Stream (Of a) IO r
loop
where
pico :: Int
pico = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
Prelude.truncate (Double
seconds Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000)
loop :: Stream (Of a) IO r %1-> Stream (Of a) IO r
loop :: Stream (Of a) IO r %1 -> Stream (Of a) IO r
loop Stream (Of a) IO r
stream = Control.do
Either r (Ur a, Stream (Of a) IO r)
e <- IO (Either r (Ur a, Stream (Of a) IO r))
%1 -> Stream (Of a) IO (Either r (Ur a, Stream (Of a) IO r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift (IO (Either r (Ur a, Stream (Of a) IO r))
%1 -> Stream (Of a) IO (Either r (Ur a, Stream (Of a) IO r)))
%1 -> IO (Either r (Ur a, Stream (Of a) IO r))
%1 -> Stream (Of a) IO (Either r (Ur a, Stream (Of a) IO r))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Stream (Of a) IO r %1 -> IO (Either r (Ur a, Stream (Of a) IO r))
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
next Stream (Of a) IO r
stream
Either r (Ur a, Stream (Of a) IO r)
e Either r (Ur a, Stream (Of a) IO r)
%1 -> (Either r (Ur a, Stream (Of a) IO r)
%1 -> Stream (Of a) IO r)
%1 -> Stream (Of a) IO r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Left r
r -> r %1 -> Stream (Of a) IO r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Right (Ur a
a,Stream (Of a) IO r
rest) -> Control.do
Of a (Stream (Of a) IO ()) -> Stream (Of a) IO ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (a
a a -> Stream (Of a) IO () -> Of a (Stream (Of a) IO ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of a) IO ()
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return ())
IO () %1 -> Stream (Of a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift (IO () %1 -> Stream (Of a) IO ())
%1 -> IO () %1 -> Stream (Of a) IO ()
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ IO () %1 -> IO ()
forall a. IO a %1 -> IO a
fromSystemIO (IO () %1 -> IO ()) %1 -> IO () %1 -> IO ()
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Int -> IO ()
threadDelay Int
pico
Stream (Of a) IO r %1 -> Stream (Of a) IO r
loop Stream (Of a) IO r
rest
{-# INLINABLE delay #-}
show :: (Control.Monad m, Prelude.Show a) =>
Stream (Of a) m r %1-> Stream (Of String) m r
show :: forall (m :: * -> *) a r.
(Monad m, Show a) =>
Stream (Of a) m r %1 -> Stream (Of [Char]) m r
show = (a -> [Char]) -> Stream (Of a) m r %1 -> Stream (Of [Char]) m r
forall (m :: * -> *) a b r.
Monad m =>
(a -> b) -> Stream (Of a) m r %1 -> Stream (Of b) m r
map a -> [Char]
forall a. Show a => a -> [Char]
Prelude.show
{-# INLINE show #-}
cons :: Control.Monad m => a -> Stream (Of a) m r %1-> Stream (Of a) m r
cons :: forall (m :: * -> *) a r.
Monad m =>
a -> Stream (Of a) m r %1 -> Stream (Of a) m r
cons a
a Stream (Of a) m r
str = Of a (Stream (Of a) m r) %1 -> 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 %1 -> Of a (Stream (Of a) m r)
forall a b. a -> b -> Of a b
:> Stream (Of a) m r
str)
{-# INLINE cons #-}
wrapEffect :: (Control.Monad m, Control.Functor f, Consumable y) =>
m a -> (a %1-> m y) -> Stream f m r %1-> Stream f m r
wrapEffect :: forall (m :: * -> *) (f :: * -> *) y a r.
(Monad m, Functor f, Consumable y) =>
m a -> (a %1 -> m y) -> Stream f m r %1 -> Stream f m r
wrapEffect m a
ma a %1 -> m y
action Stream f m r
stream = Stream f m r
stream Stream f m r
%1 -> (Stream f m r %1 -> Stream f m r) %1 -> Stream f m r
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Return r
r -> r %1 -> Stream f m r
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return r
r
Effect m (Stream f m r)
m -> m (Stream f m r) %1 -> Stream f m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m r) %1 -> Stream f m r)
%1 -> m (Stream f m r) %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
a
a <- m a
ma
y
y <- a %1 -> m y
action a
a
y %1 -> m (Stream f m r) %1 -> m (Stream f m r)
forall a b. Consumable a => a %1 -> b %1 -> b
lseq y
y (m (Stream f m r) %1 -> m (Stream f m r))
%1 -> m (Stream f m r) %1 -> m (Stream f m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ m (Stream f m r)
m
Step f (Stream f m r)
f -> m (Stream f m r) %1 -> Stream f m r
forall (m :: * -> *) (f :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect (m (Stream f m r) %1 -> Stream f m r)
%1 -> m (Stream f m r) %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Control.do
a
a <- m a
ma
y
y <- a %1 -> m y
action a
a
Stream f m r %1 -> m (Stream f m r)
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return (Stream f m r %1 -> m (Stream f m r))
%1 -> Stream f m r %1 -> m (Stream f m r)
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ y %1 -> Stream f m r %1 -> Stream f m r
forall a b. Consumable a => a %1 -> b %1 -> b
lseq y
y (Stream f m r %1 -> Stream f m r)
%1 -> Stream f m r %1 -> Stream f m r
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ f (Stream f m r) %1 -> Stream f m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step f (Stream f m r)
f
slidingWindow :: forall a b m. Control.Monad m => Int -> Stream (Of a) m b
%1-> Stream (Of (Seq.Seq a)) m b
slidingWindow :: forall a b (m :: * -> *).
Monad m =>
Int -> Stream (Of a) m b %1 -> Stream (Of (Seq a)) m b
slidingWindow Int
n = Int -> Seq a -> Stream (Of a) m b %1 -> 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. Seq a
Seq.empty
where
window :: Seq.Seq a -> Stream (Of a) m b %1-> Stream (Of (Seq.Seq a)) m b
window :: Seq a -> Stream (Of a) m b %1 -> Stream (Of (Seq a)) m b
window !Seq a
sequ Stream (Of a) m b
str = Control.do
Either b (Ur a, Stream (Of a) m b)
e <- m (Either b (Ur a, Stream (Of a) m b))
%1 -> Stream (Of (Seq a)) m (Either b (Ur a, Stream (Of a) m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift (Stream (Of a) m b %1 -> m (Either b (Ur a, Stream (Of a) m b))
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
next Stream (Of a) m b
str)
Either b (Ur a, Stream (Of a) m b)
e Either b (Ur a, Stream (Of a) m b)
%1 -> (Either b (Ur a, Stream (Of a) m b)
%1 -> Stream (Of (Seq a)) m b)
%1 -> Stream (Of (Seq a)) m b
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Left b
r -> b %1 -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return b
r
Right (Ur a
a,Stream (Of a) m b
rest) -> Control.do
Of (Seq a) (Stream (Of (Seq a)) m ())
%1 -> Stream (Of (Seq a)) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Of (Seq a) (Stream (Of (Seq a)) m ())
%1 -> Stream (Of (Seq a)) m ())
%1 -> Of (Seq a) (Stream (Of (Seq a)) m ())
%1 -> Stream (Of (Seq a)) m ()
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ (Seq a
sequ Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
a) Seq a
-> Stream (Of (Seq a)) m ()
-> Of (Seq a) (Stream (Of (Seq a)) m ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of (Seq a)) m ()
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return ()
Seq a -> Stream (Of a) m b %1 -> 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 Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
a) Stream (Of a) m b
rest
setup ::
Int -> Seq.Seq a -> Stream (Of a) m b %1-> Stream (Of (Seq.Seq a)) m b
setup :: Int -> Seq a -> Stream (Of a) m b %1 -> Stream (Of (Seq a)) m b
setup Int
0 !Seq a
sequ Stream (Of a) m b
str = Control.do
Of (Seq a) (Stream (Of (Seq a)) m ()) -> Stream (Of (Seq a)) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Seq a
sequ Seq a
-> Stream (Of (Seq a)) m ()
-> Of (Seq a) (Stream (Of (Seq a)) m ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of (Seq a)) m ()
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return ())
Seq a -> Stream (Of a) m b %1 -> 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 Int
n' Seq a
sequ Stream (Of a) m b
str = Control.do
Either b (Ur a, Stream (Of a) m b)
e <- m (Either b (Ur a, Stream (Of a) m b))
%1 -> Stream (Of (Seq a)) m (Either b (Ur a, Stream (Of a) m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a %1 -> t m a
Control.lift (m (Either b (Ur a, Stream (Of a) m b))
%1 -> Stream (Of (Seq a)) m (Either b (Ur a, Stream (Of a) m b)))
%1 -> m (Either b (Ur a, Stream (Of a) m b))
%1 -> Stream (Of (Seq a)) m (Either b (Ur a, Stream (Of a) m b))
forall a b. (a %1 -> b) %1 -> a %1 -> b
$ Stream (Of a) m b %1 -> m (Either b (Ur a, Stream (Of a) m b))
forall a (m :: * -> *) r.
Monad m =>
Stream (Of a) m r %1 -> m (Either r (Ur a, Stream (Of a) m r))
next Stream (Of a) m b
str
Either b (Ur a, Stream (Of a) m b)
e Either b (Ur a, Stream (Of a) m b)
%1 -> (Either b (Ur a, Stream (Of a) m b)
%1 -> Stream (Of (Seq a)) m b)
%1 -> Stream (Of (Seq a)) m b
forall a b. a %1 -> (a %1 -> b) %1 -> b
& \case
Left b
r -> Control.do
Of (Seq a) (Stream (Of (Seq a)) m ()) -> Stream (Of (Seq a)) m ()
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (Seq a
sequ Seq a
-> Stream (Of (Seq a)) m ()
-> Of (Seq a) (Stream (Of (Seq a)) m ())
forall a b. a -> b -> Of a b
:> () -> Stream (Of (Seq a)) m ()
forall r (f :: * -> *) (m :: * -> *). r -> Stream f m r
Return ())
b %1 -> Stream (Of (Seq a)) m b
forall (m :: * -> *) a. Monad m => a %1 -> m a
Control.return b
r
Right (Ur a
x,Stream (Of a) m b
rest) -> Int -> Seq a -> Stream (Of a) m b %1 -> Stream (Of (Seq a)) m b
setup (Int
n'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
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 #-}