| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Util.Sources
Contents
Description
We implement the Source type and combinators for it.
Synopsis
- data Source x d
- data Client d
- staticSource :: x -> Source x d
- staticSourceIO :: IO x -> Source x d
- variableSource :: x -> IO (Source x d, (x -> (x, [d])) -> IO ())
- variableGeneralSource :: x -> IO (Source x d, Updater x d)
- data Updater x d
- applyToUpdater :: Updater x d -> (x -> (x, [d], extra)) -> IO extra
- attachClient :: Client d -> Source x d -> IO x
- map1 :: (x1 -> x2) -> Source x1 d -> Source x2 d
- map1IO :: (x1 -> IO x2) -> Source x1 d -> Source x2 d
- map2 :: (d1 -> d2) -> Source x d1 -> Source x d2
- filter2 :: (d1 -> Maybe d2) -> Source x d1 -> Source x d2
- filter2IO :: (d1 -> IO (Maybe d2)) -> Source x d1 -> Source x d2
- foldSource :: (x -> state) -> (state -> d1 -> (state, d2)) -> Source x d1 -> Source (state, x) d2
- foldSourceIO :: (x1 -> IO (state, x2)) -> (state -> d1 -> IO (state, d2)) -> Source x1 d1 -> Source (state, x2) d2
- stepSource :: (x -> d2) -> (d1 -> d2) -> Source x d1 -> Source x d2
- choose :: Source x1 d1 -> Source x2 d2 -> Source (x1, x2) (Either d1 d2)
- seqSource :: Source x1 x1 -> (x1 -> Source x2 x2) -> Source x2 x2
- flattenSource :: Source x [d] -> Source x d
- newtype SimpleSource x = SimpleSource (Source x x)
- staticSimpleSource :: x -> SimpleSource x
- staticSimpleSourceIO :: IO x -> SimpleSource x
- class HasSource hasSource x d | hasSource -> x, hasSource -> d where
- class HasSimpleSource hasSource x | hasSource -> x where
- readContents :: HasSource source x d => source -> IO x
- mkHistorySource :: (x -> d) -> Source x d -> Source x (d, d)
- mkHistorySimpleSource :: x -> SimpleSource x -> SimpleSource (x, x)
- uniqSimpleSource :: Eq x => SimpleSource x -> SimpleSource x
- pairSimpleSources :: SimpleSource x1 -> SimpleSource x2 -> SimpleSource (x1, x2)
- sequenceSimpleSource :: [SimpleSource x] -> SimpleSource [x]
- change1 :: SimpleSource x -> x -> SimpleSource x
- mapIOSeq :: SimpleSource a -> (a -> IO (SimpleSource b)) -> SimpleSource b
- addNewSourceActions :: Source x d -> (x -> IO ()) -> (d -> IO ()) -> SinkID -> ParallelExec -> IO x
- traceSimpleSource :: (a -> String) -> SimpleSource a -> SimpleSource a
- traceSource :: (a -> String) -> (d -> String) -> Source a d -> Source a d
- noLoopSimpleSource :: TSem -> ([String] -> a) -> SimpleSource a -> SimpleSource a
- mkIOSimpleSource :: IO (SimpleSource a) -> SimpleSource a
- foldSimpleSourceIO :: (x1 -> IO (state, x2)) -> (state -> x1 -> IO (state, x2)) -> SimpleSource x1 -> SimpleSource x2
Documentation
staticSource :: x -> Source x d Source #
staticSourceIO :: IO x -> Source x d Source #
applyToUpdater :: Updater x d -> (x -> (x, [d], extra)) -> IO extra Source #
foldSource :: (x -> state) -> (state -> d1 -> (state, d2)) -> Source x d1 -> Source (state, x) d2 Source #
foldSourceIO :: (x1 -> IO (state, x2)) -> (state -> d1 -> IO (state, d2)) -> Source x1 d1 -> Source (state, x2) d2 Source #
Fold a Source so that it can carry state around.
stepSource :: (x -> d2) -> (d1 -> d2) -> Source x d1 -> Source x d2 Source #
flattenSource :: Source x [d] -> Source x d Source #
A Source combinator which "flattens" lists of updates.
newtype SimpleSource x Source #
Constructors
| SimpleSource (Source x x) | 
Instances
staticSimpleSource :: x -> SimpleSource x Source #
staticSimpleSourceIO :: IO x -> SimpleSource x Source #
class HasSource hasSource x d | hasSource -> x, hasSource -> d where Source #
Minimal complete definition
Instances
class HasSimpleSource hasSource x | hasSource -> x where Source #
Minimal complete definition
Methods
toSimpleSource :: hasSource -> SimpleSource x Source #
Instances
| HasSimpleSource (SimpleSource x) x Source # | |
| Defined in Util.Sources Methods toSimpleSource :: SimpleSource x -> SimpleSource x Source # | |
| HasSimpleSource (SimpleBroadcaster x) x Source # | |
| Defined in Util.Broadcaster Methods toSimpleSource :: SimpleBroadcaster x -> SimpleSource x Source # | |
readContents :: HasSource source x d => source -> IO x Source #
Get the current contents of the source, but don't specify any other action.
mkHistorySource :: (x -> d) -> Source x d -> Source x (d, d) Source #
For each update d, pairs it with its predecessor (given first). For the very first update, a value is given based on the initial x, mapped by the given function.
mkHistorySimpleSource :: x -> SimpleSource x -> SimpleSource (x, x) Source #
Like mkHistorySource but for SimpleSource's; the x returns the initial value to compare with.
uniqSimpleSource :: Eq x => SimpleSource x -> SimpleSource x Source #
filter out consecutive duplicates
pairSimpleSources :: SimpleSource x1 -> SimpleSource x2 -> SimpleSource (x1, x2) Source #
Pair two SimpleSource's. This is probably better than using >>=, since it does not require reregistering with the second SimpleSource
sequenceSimpleSource :: [SimpleSource x] -> SimpleSource [x] Source #
Does a similar job to pairSimpleSources, so that the sources run parallel.
change1 :: SimpleSource x -> x -> SimpleSource x Source #
replaces the first value of the SimpleSource.
mapIOSeq :: SimpleSource a -> (a -> IO (SimpleSource b)) -> SimpleSource b Source #
addNewSourceActions :: Source x d -> (x -> IO ()) -> (d -> IO ()) -> SinkID -> ParallelExec -> IO x Source #
Run the specified actions for the source, using the given SinkID and in the ParallelExec thread. The x -> IO () action is guaranteed to be performed before any of the d -> IO () actions.
traceSimpleSource :: (a -> String) -> SimpleSource a -> SimpleSource a Source #
Outputs information about what comes through the source, turning it into a String with the supplied function. (This is done once for each active client.)
traceSource :: (a -> String) -> (d -> String) -> Source a d -> Source a d Source #
Outputs information about what comes through the source, turning it into a String with the supplied function. (This is done once for each active client.)
noLoopSimpleSource :: TSem -> ([String] -> a) -> SimpleSource a -> SimpleSource a Source #
Used when we are worried that a SimpleSource recursively constructed by mapIOSeq, >>= and friends may actually try to call itself, and so loop forever. The Strings identify the SimpleSource, and so the [String] is effectively a backtrace of the TSems, revealing what chain of simple sources might have caused the loop.
mkIOSimpleSource :: IO (SimpleSource a) -> SimpleSource a Source #
foldSimpleSourceIO :: (x1 -> IO (state, x2)) -> (state -> x1 -> IO (state, x2)) -> SimpleSource x1 -> SimpleSource x2 Source #
Fold a Simple Source, so that it carries state. The state is recomputed for each client.
Orphan instances
| HasSource hasSource x d => CanAddSinks hasSource x d Source # | |
| Methods addNewSink :: hasSource -> (d -> IO ()) -> IO (x, Sink d) Source # addNewSinkGeneral :: hasSource -> (d -> IO ()) -> SinkID -> IO (x, Sink d) Source # addNewSinkVeryGeneral :: hasSource -> (d -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink d) Source # addNewSinkWithInitial :: hasSource -> (x -> IO ()) -> (d -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink d) Source # addNewQuickSink :: hasSource -> (d -> IO ()) -> IO (x, Sink d) Source # addNewQuickSinkGeneral :: hasSource -> (d -> IO ()) -> SinkID -> IO (x, Sink d) Source # addOldSink :: hasSource -> Sink d -> IO x Source # | |