buster-2.5: Almost but not quite entirely unlike FRP

App.DebugEventBus

Description

Not exactly the FRP model, but rather a model of a large application with heterogenous data and many inputs and outputs. An application is in its essence a collection of widgets and behaviours and events with a bus. The bus holds events and manages the event timeline. Behaviours and widgets are continuous. Widgets applied to the bus make insertions and never deletions. Behaviours applied to the bus make insertions and deletions.

Behaviours are composable using combinators that set one Behaviour as either behind, in front, or beside another behaviour on the bus. The in front and behind combinators establish that the behaviour behind the others sees the results of the other behaviours' application to the bus. The beside combinator says that the combinators see the same bus.

Synopsis

Documentation

data TimeSpan Source

Defines the amount of time that an event exists.

Constructors

Persistent

The event exists forever

Time DiffTime

The event exists for a specified amount of real time

Iterations Int

The event exists for a certain number of samples of time from its inception.

data Diff a Source

Defines time in terms of the differences from time t0 to the next instant. This is the type returned by Behaviours to describe time directly after the Behaviour.

Constructors

Insertion (Event a)

Time t1 contains all events at time t0 plus this event.

Deletion (Event a)

Time t1 contains all events at time t0 minus this event.

InstrumentedBehaviour String 

Instances

Show (Diff a) 

data EData a Source

Defines the data attachable to events.

Instances

Eq a => Eq (EData a) 
Read a => Read (EData a) 
Show a => Show (EData a) 

safeShow :: Maybe Int -> EData a -> StringSource

Show without risking running into an unshowable type.

data Event a Source

An discrete event in time

Constructors

Event

The time of the event's inception.

Fields

ename :: String

The unique name of an event. Group + src + name = the fully qualified name FQN of the event.

group :: String

The group of an event.

timespan :: TimeSpan

The timespan from time that an event exists.

eventdata :: a

The data attached to the event.

src :: String

The behaviour or widget that assigned the event to time.

time :: UTCTime
 

Instances

Eq (Event a) 
Ord (Event a) 

data Bus a Source

The type of a discrete sample of continuous time.

Constructors

Bus 

Fields

nameMap :: Map String (Set (Event a))

The map of just Event.name to events.

srcMap :: Map String (Set (Event a))

The map of just Event.src to events.

groupMap :: Map String (Set (Event a))

The map of just Event.group to events.

fullyQualifiedMap :: Map (String, String, String) (Event a)

The map of FQNs to events.

currentProducerConsumer :: Maybe String
 
debugout :: Handle
 

Instances

Show (Bus a) 
Monoid (Bus a) 

emptyBus :: Bus aSource

The empty bus

addEvent :: Event a -> Bus a -> Bus aSource

Add an event to time within the bus

type Widget a = MVar (Bus a) -> IO ()Source

The type of widgets. A widget is an input-only way to assign Events to time. A mouse is a widget. A keyboard is a widget. A webcam is a widget, and so on.

type Future a = IO (Bus a, MVar [Diff a])Source

The type of future events.. A behaviour doesn't know about the time that it assigns events, only that they exist at some point after the time that the Behaviour sampled.

future :: Bus a -> IO [Diff a] -> Future aSource

An IO action sometime in the future.

type Behaviour a = Bus a -> Future aSource

Obtain the final value of a Future. Blocks until the value is available

The type of a Behaviour. A behaviour maps the bus to a list of differences to apply to the bus before the next Behaviour's sample of time.

passthrough :: Behaviour aSource

The null Behaviour. Samples the bus and adds and deletes nothing.

(<~<) :: Behaviour a -> Behaviour a -> Behaviour aSource

the in front of behaviour combinator. behaviour 1 is in front of behaviour 0, so behavour 0 will see the bus filtered through behaviour 1

(>~>) :: Behaviour a -> Behaviour a -> Behaviour aSource

the behind behaviour combinator. behaviour 0 is behind behaviour 1, so behaviour 0 will see the bus filtered through behaviour 1

(|~|) :: Behaviour a -> Behaviour a -> Behaviour aSource

the beside behaviour combinator. All behaviours that are side-by-side see the same bus.

bus :: [Widget a] -> IO b -> Behaviour a -> IO ()Source

An infinite loop of behaviours and widgets over time, sampled forward.

busIteration :: MVar (Bus a) -> Behaviour a -> IO ()Source

Sample time and apply the behaviour to that sample.

produce :: String -> String -> String -> TimeSpan -> a -> IO (Diff a)Source

Assign an event to time given some event data and a TimeSpan.

produce group source nm timetolive edata

produce' :: String -> String -> String -> TimeSpan -> a -> MVar (Bus a) -> IO ()Source

Assign an event to time from a widget.

produce' group source nm timetolive edata bus

consumeNamedEventsCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given name at the current time and output their deletions as Diffs as well as any additional Diffs returned by the behaviour.

modifyEventData :: Event a -> (a -> a) -> [Diff a]Source

modifyEvent :: Event a -> (Event a -> Event a) -> [Diff a]Source

consumeEventGroupCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given group at the current time and output their deletions as Diffs as well as any additional Diffs returned by the behaviour.

consumeEventsFromSourceCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given source at the current time and output their deletions as Diffs as well as any additional Diffs returned by the behaviour.

consumeFullyQualifiedEventWith :: Bus a -> String -> String -> String -> (Event a -> IO [Diff a]) -> Future aSource

Sample a single fully qualified event at the current time and output their deletions as Diffs as well as any additional Diffs returned by the behaviour. Parameter order is bus, group, source, name

pollNamedEventsCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given name and apply a Behaviour

pollNamedEventsWith :: Bus a -> String -> (Event a -> IO [Diff a]) -> Future aSource

Sample all events with a given name and apply a Behaviour to each

pollEventGroupCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given group and apply a Behaviour

pollEventGroupWith :: Bus a -> String -> (Event a -> IO [Diff a]) -> Future aSource

Sample all events with a gien group and apply a Behaviour to each.

pollEventsFromSourceCollectivelyWith :: Bus a -> String -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Sample all events with a given source and apply a Behaviour

pollEventsFromSourceWith :: Bus a -> String -> (Event a -> IO [Diff a]) -> Future aSource

Sample all events with a given source and apply a Behaviour to each.

pollFullyQualifiedEventWith :: Bus a -> String -> String -> String -> (Event a -> IO [Diff a]) -> Future aSource

Sample a single fully qualified event and output some Diffs. Parameter order is bus, group, source, name.

pollAllEventsWith :: Bus a -> (Event a -> IO [Diff a]) -> Future aSource

Apply a behaviour to all events in the bus, one event at a time.

pollAllEventsCollectivelyWith :: Bus a -> (Set (Event a) -> IO [Diff a]) -> Future aSource

Apply a behaviour to the collection of all events on the bus at once