CV-0.3.5.4: OpenCV based machine vision library

Safe HaskellSafe-Infered

Utils.Stream

Synopsis

Documentation

data Stream m a Source

Stream of monadic values

Constructors

Terminated 
Value (m (a, Stream m a)) 

Instances

Monad m => Functor (Stream m)

Map over a stream

Monad m => Applicative (Stream m) 

sideEffect :: Monad m => (a -> m ()) -> Stream m a -> Stream m aSource

Attaching side effects

listToStream :: Monad m => [a] -> Stream m aSource

Repeating stream

repeatS :: Monad m => a -> Stream m aSource

repeatSM :: Monad m => m a -> Stream m aSource

iterateS :: Monad m => (a -> m a) -> a -> Stream m aSource

Create a stream by iterating a monadic action

foldS :: Monad m => (a -> t -> a) -> a -> Stream m t -> m aSource

Pure and monadic left fold over a stream

foldSM :: Monad m => (a -> t -> m a) -> a -> Stream m t -> m aSource

time :: (t, t1) -> tSource

Merge two (time)streams

value :: (t, t1) -> t1Source

mergeTimeStreams :: (Monad m, Ord t1) => t -> t2 -> Stream m (t1, t) -> Stream m (t1, t2) -> Stream m (t1, (t, t2))Source

mergeTimeStreamsWith :: (Monad m, Ord t2) => t -> t1 -> (t -> t1 -> t3) -> Stream m (t2, t) -> Stream m (t2, t1) -> Stream m (t2, t3)Source

mergeManyW :: (Monad m, Ord t) => [t1] -> (t1 -> t1 -> t1) -> [Stream m (t, t1)] -> Stream m (t, t1)Source

mergeS :: (Monad m, Ord t2) => Stream m (t2, t) -> Stream m (t2, t1) -> Stream m (LRB (t2, t) (t2, (t, t1)) (t2, t1))Source

data LRB a b c Source

Constructors

L a 
B b 
R c 

Instances

(Show a, Show b, Show c) => Show (LRB a b c) 

mergeE :: Monad m => (t, t2) -> Stream m (LRB (t1, t) (t1, (t, t2)) (t1, t2)) -> Stream m (t1, (t, t2))Source

push :: Monad m => a -> Stream m a -> Stream m aSource

zipS :: Applicative f => f a1 -> f a -> f (a1, a)Source

sequenceS :: Monad m => Stream m (m a) -> Stream m aSource

mapMS :: Monad m => (a -> m b) -> Stream m a -> Stream m bSource

dropS :: Monad m => Int -> Stream m a -> Stream m aSource

Drop elements from the stream. Due to stream structure, this operation cannot fail gracefully when dropping more elements than what is found in the stream

takeS :: Monad m => Int -> Stream m a -> Stream m aSource

takeWhileS :: Monad m => (a -> Bool) -> Stream m a -> Stream m aSource

consS :: Monad m => a -> Stream m a -> Stream m aSource

pairS :: Monad m => Stream m a -> Stream m (a, a)Source

terminateOn :: Monad m => (a -> Bool) -> Stream m a -> Stream m aSource

runStream :: Monad m => Stream m a -> m [a]Source

runStream_ :: Monad m => Stream m t -> m ()Source

runLast :: Monad m => a -> Stream m a -> m aSource

runLast1 :: Monad m => Stream m a -> m aSource