roshask-0.2.1: Haskell support for the ROS robotics framework.

Safe HaskellSafe
LanguageHaskell2010

Ros.Topic

Description

The ROS Topic type and basic operations on Topics.

Note: Many of these operations have the same names as similar operations on lists in the Prelude. The ambiguity may be resolved using either qualification (e.g. import qualified Ros.TopicUtil as T), an explicit import list, or a hiding clause.

Synopsis

Documentation

newtype Topic m a Source

A Topic is an infinite stream of values that steps between values in a Monad.

Constructors

Topic 

Fields

runTopic :: m (a, Topic m a)
 

head :: Functor m => Topic m a -> m a Source

Return the first value produced by a Topic.

uncons :: Topic m a -> m (a, Topic m a) Source

Return the first value produced by a Topic along with the remaining Topic data.

force :: Monad m => Topic m a -> m (Topic m a) Source

Force evaluation of a topic until it produces a value.

cons :: Monad m => a -> Topic m a -> Topic m a Source

Prepend a single item to the front of a Topic.

tail :: Monad m => Topic m a -> Topic m a Source

Returns a Topic containing all the values from the given Topic after the first.

tails :: Monad m => Topic m a -> Topic m (Topic m a) Source

Return a Topic of all the suffixes of a Topic.

filter :: Monad m => (a -> Bool) -> Topic m a -> Topic m a Source

Returns a Topic containing only those elements of the supplied Topic for which the given predicate returns True.

take :: Monad m => Int -> Topic m a -> m [a] Source

take n t returns the prefix of t of length n.

take_ :: Monad m => Int -> Topic m a -> m () Source

Run a Topic for the specified number of iterations, discarding the values it produces.

drop :: Monad m => Int -> Topic m a -> Topic m a Source

drop n t returns the suffix of t after the first n elements.

dropWhile :: Monad m => (a -> Bool) -> Topic m a -> Topic m a Source

dropWhile p t returns the suffix of t after all elements satisfying predicate p have been dropped.

takeWhile :: Monad m => (a -> Bool) -> Topic m a -> m [a] Source

takeWhile p t returns the longest prefix (possibly empty) of t all of whose elements satisfy the predicate p.

break :: Monad m => (a -> Bool) -> Topic m a -> m ([a], Topic m a) Source

break p t returns a tuple whose first element is the longest prefix (possibly empty) of t all of whose elements satisfy the predicate p, and whose second element is the remainder of the Topic.

splitAt :: Monad m => Int -> Topic m a -> m ([a], Topic m a) Source

splitAt n t returns a tuple whose first element is the prefix of t of length n, and whose second element is the remainder of the Topic.

catMaybes :: Monad m => Topic m (Maybe a) -> Topic m a Source

Returns a Topic that includes only the Just values from the given Topic.

repeatM :: Monad m => m a -> Topic m a Source

Repeatedly execute a monadic action feeding the values into a Topic.

unfold :: Functor m => (b -> m (a, b)) -> b -> Topic m a Source

Build a Topic from a seed value. The supplied function is applied to the seed value to produce both a value that goes into the Topic and a new seed value for the next recursive call.

newtype IterCont a b Source

A pair of an optional value and a continuation for producing more such pairs. This type is used by metamorph to implement a streaming unfold . fold composition.

Constructors

IterCont (Maybe b, a -> IterCont a b) 

Instances

newtype IterContM m a b Source

A pair of an optional value and a continuation with effects for producing more such pairs. This type is used by metamorphM to implement a streaming unfold . fold composition.

Constructors

IterContM (Maybe b, a -> m (IterContM m a b)) 

Instances

yield :: b -> (a -> IterCont a b) -> IterCont a b Source

Yield a value and a continuation in a metamorphism (used with metamorph).

skip :: (a -> IterCont a b) -> IterCont a b Source

Do not yield a value, but provide a continuation in a metamorphism (used with metamorph).

yieldM :: Monad m => b -> (a -> m (IterContM m a b)) -> m (IterContM m a b) Source

Yield a value and a continuation in a monad as part of a monadic metamorphism (used with metamorphM).

skipM :: Monad m => (a -> m (IterContM m a b)) -> m (IterContM m a b) Source

Do not yield a value, but provide a continuation in a metamorphism (used with metamorphM).

metamorph :: Monad m => (a -> IterCont a b) -> Topic m a -> Topic m b Source

A metamorphism (cf. Jeremy Gibbons) on Topics. This is an unfold following a fold (i.e. unfoldr . foldl), with the expectation that partial results of the unfold may be returned before the fold is completed. The supplied function produces a optional value and a continuation when applied to an element of the first Topic. The value is returned by the new Topic if it is not Nothing, and the continuation is used to produce the rest of the returned Topic.

metamorphM :: Monad m => (a -> m (IterContM m a b)) -> Topic m a -> Topic m b Source

Similar to metamorph, but the metamorphism may have effects.

bimetamorph :: Monad m => (a -> IterCont a b) -> (a -> IterCont a b) -> Topic m a -> Topic m b Source

Fold two functions along a Topic collecting their productions in a new Topic.

bimetamorphM :: Monad m => (a -> m (IterContM m a b)) -> (a -> m (IterContM m a b)) -> Topic m a -> Topic m b Source

Fold two monadic functions along a Topic collecting their productions in a new Topic.

bimetamorphE :: Monad m => (a -> IterCont a b) -> (a -> IterCont a c) -> Topic m a -> Topic m (Either b c) Source

Fold two functions along a Topic collecting and tagging their productions in a new Topic.

bimetamorphME :: Monad m => (a -> m (IterContM m a b)) -> (a -> m (IterContM m a c)) -> Topic m a -> Topic m (Either b c) Source

Fold two monadic functions along a Topic collecting and tagging their productions in a new Topic.

join :: (Functor m, Monad m) => Topic m (m a) -> Topic m a Source

Removes one level of monadic structure from the values a Topic produces.

forever :: Monad m => Topic m a -> m b Source

forever t runs all monadic actions a Topic produces. This is useful for Topics whose steps produce side-effects, but not useful pure values.

mapM :: (Functor m, Monad m) => (a -> m b) -> Topic m a -> Topic m b Source

Map a monadic action over a Topic.

mapM_ :: Monad m => (a -> m ()) -> Topic m a -> m () Source

Map a monadic action of a Topic purely for its side effects. This function will never return.

scan :: Monad m => (a -> b -> a) -> a -> Topic m b -> Topic m a Source

A left-associative scan of a Topic is a fold whose every intermediate value is produced as a value of a new Topic.

showTopic :: (MonadIO m, Functor m, Show a) => Topic m a -> Topic m () Source

Print all the values produced by a Topic.