dunai-0.9.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.
Copyright(c) Ivan Perez and Manuel Baerenz 2016
LicenseBSD3
Maintainerivan.perez@keera.co.uk
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Trans.MSF.List

Description

Warning: This module uses the ListT transformer, which is considered deprecated.

MSFs with a list monadic layer.

This module contains functions to work with MSFs that include a ListT monadic layer. MSFs on a list monad may produce multiple outputs and continuations, or none. This enables the possibility for spawning new MSFs, or stopping MSFs, at will.

A common use case is to be able to dynamically spawn new interactive elements in applications (e.g., a game object that splits in two, or that fires to an enemy).

WARNING: the ListT transformer is considered dangerous, and imposes additional constraints on the inner monad in order for the combination of the monad and the transformer to be a monad. Use at your own risk.

Synopsis

Documentation

widthFirst :: (Functor m, Monad m) => MSF (ListT m) a b -> MSF m a [b] Source #

Run an MSF in the ListT transformer (i.e., multiple MSFs producing each producing one output), by applying the input stream to each MSF in the list transformer and concatenating the outputs of the MSFs together.

An MSF in the ListT transformer can spawn into more than one MSF, or none, so the outputs produced at each individual step are not guaranteed to all have the same length.

sequenceS :: Monad m => [MSF m a b] -> MSF (ListT m) a b Source #

Build an MSF in the ListT transformer by broadcasting the input stream value to each MSF in a given list.

mapMSF :: Monad m => MSF m a b -> MSF m [a] [b] Source #

Apply an MSF to every input.

newtype ListT (m :: Type -> Type) a #

Parameterizable list monad, with an inner monad.

Note: this does not yield a monad unless the argument monad is commutative.

Constructors

ListT 

Fields

Instances

Instances details
MonadTrans ListT 
Instance details

Defined in Control.Monad.Trans.List

Methods

lift :: Monad m => m a -> ListT m a #

MonadSplit g m => MonadSplit g (ListT m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getSplit :: ListT m g #

MonadBase b m => MonadBase b (ListT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ListT m α #

Monad m => Monad (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

(>>=) :: ListT m a -> (a -> ListT m b) -> ListT m b #

(>>) :: ListT m a -> ListT m b -> ListT m b #

return :: a -> ListT m a #

Functor m => Functor (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

fmap :: (a -> b) -> ListT m a -> ListT m b #

(<$) :: a -> ListT m b -> ListT m a #

MonadFix m => MonadFix (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

mfix :: (a -> ListT m a) -> ListT m a #

Monad m => MonadFail (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

fail :: String -> ListT m a #

Applicative m => Applicative (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

pure :: a -> ListT m a #

(<*>) :: ListT m (a -> b) -> ListT m a -> ListT m b #

liftA2 :: (a -> b -> c) -> ListT m a -> ListT m b -> ListT m c #

(*>) :: ListT m a -> ListT m b -> ListT m b #

(<*) :: ListT m a -> ListT m b -> ListT m a #

Foldable f => Foldable (ListT f) 
Instance details

Defined in Control.Monad.Trans.List

Methods

fold :: Monoid m => ListT f m -> m #

foldMap :: Monoid m => (a -> m) -> ListT f a -> m #

foldMap' :: Monoid m => (a -> m) -> ListT f a -> m #

foldr :: (a -> b -> b) -> b -> ListT f a -> b #

foldr' :: (a -> b -> b) -> b -> ListT f a -> b #

foldl :: (b -> a -> b) -> b -> ListT f a -> b #

foldl' :: (b -> a -> b) -> b -> ListT f a -> b #

foldr1 :: (a -> a -> a) -> ListT f a -> a #

foldl1 :: (a -> a -> a) -> ListT f a -> a #

toList :: ListT f a -> [a] #

null :: ListT f a -> Bool #

length :: ListT f a -> Int #

elem :: Eq a => a -> ListT f a -> Bool #

maximum :: Ord a => ListT f a -> a #

minimum :: Ord a => ListT f a -> a #

sum :: Num a => ListT f a -> a #

product :: Num a => ListT f a -> a #

Traversable f => Traversable (ListT f) 
Instance details

Defined in Control.Monad.Trans.List

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ListT f a -> f0 (ListT f b) #

sequenceA :: Applicative f0 => ListT f (f0 a) -> f0 (ListT f a) #

mapM :: Monad m => (a -> m b) -> ListT f a -> m (ListT f b) #

sequence :: Monad m => ListT f (m a) -> m (ListT f a) #

Monad m => MonadPlus (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

mzero :: ListT m a #

mplus :: ListT m a -> ListT m a -> ListT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadRandom m => MonadRandom (ListT m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomR :: Random a => (a, a) -> ListT m a #

getRandom :: Random a => ListT m a #

getRandomRs :: Random a => (a, a) -> ListT m [a] #

getRandoms :: Random a => ListT m [a] #

MonadInterleave m => MonadInterleave (ListT m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

interleave :: ListT m a -> ListT m a #

Contravariant m => Contravariant (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

contramap :: (a -> b) -> ListT m b -> ListT m a #

(>$) :: b -> ListT m b -> ListT m a #

Eq1 m => Eq1 (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftEq :: (a -> b -> Bool) -> ListT m a -> ListT m b -> Bool #

Ord1 m => Ord1 (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftCompare :: (a -> b -> Ordering) -> ListT m a -> ListT m b -> Ordering #

Read1 m => Read1 (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ListT m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ListT m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ListT m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ListT m a] #

Show1 m => Show1 (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ListT m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ListT m a] -> ShowS #

MonadZip m => MonadZip (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

mzip :: ListT m a -> ListT m b -> ListT m (a, b) #

mzipWith :: (a -> b -> c) -> ListT m a -> ListT m b -> ListT m c #

munzip :: ListT m (a, b) -> (ListT m a, ListT m b) #

Applicative m => Alternative (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

empty :: ListT m a #

(<|>) :: ListT m a -> ListT m a -> ListT m a #

some :: ListT m a -> ListT m [a] #

many :: ListT m a -> ListT m [a] #

(Eq1 m, Eq a) => Eq (ListT m a) 
Instance details

Defined in Control.Monad.Trans.List

Methods

(==) :: ListT m a -> ListT m a -> Bool #

(/=) :: ListT m a -> ListT m a -> Bool #

(Ord1 m, Ord a) => Ord (ListT m a) 
Instance details

Defined in Control.Monad.Trans.List

Methods

compare :: ListT m a -> ListT m a -> Ordering #

(<) :: ListT m a -> ListT m a -> Bool #

(<=) :: ListT m a -> ListT m a -> Bool #

(>) :: ListT m a -> ListT m a -> Bool #

(>=) :: ListT m a -> ListT m a -> Bool #

max :: ListT m a -> ListT m a -> ListT m a #

min :: ListT m a -> ListT m a -> ListT m a #

(Read1 m, Read a) => Read (ListT m a) 
Instance details

Defined in Control.Monad.Trans.List

(Show1 m, Show a) => Show (ListT m a) 
Instance details

Defined in Control.Monad.Trans.List

Methods

showsPrec :: Int -> ListT m a -> ShowS #

show :: ListT m a -> String #

showList :: [ListT m a] -> ShowS #

mapListT :: (m [a] -> n [b]) -> ListT m a -> ListT n b #

Map between ListT computations.