affection-0.0.0.7: A simple Game Engine using SDL

Safe HaskellNone
LanguageHaskell2010

Affection.MessageBus.Class

Synopsis

Documentation

class (Message msg, Show msg) => Participant prt msg us where Source #

Minimal complete definition

partSubscribers, partSubscribe, partUnSubscribe

Methods

partSubscribers Source #

Arguments

:: prt

the Participant's subscriber storage

-> Affection us [msg -> Affection us ()]

List of Subscriber functions

Function to get the list of subscribers from the participant

partSubscribe Source #

Arguments

:: prt

The Participant's subscriber storage

-> (msg -> Affection us ())

What to do in case of a Message (Subscriber function)

-> Affection us (MsgId msg)

UUID of the registered subscriber Function

Subscribe to the Participant's events

partUnSubscribe Source #

Arguments

:: prt

The Participant's subscriber storage to unsubscribe from

-> MsgId msg

The subscriber function's UUID

-> Affection us () 

Unsubscribe a Subscriber function from Participant

partEmit Source #

Arguments

:: prt

The Participant's subscriber storage

-> msg

The Message to emit

-> Affection us () 

Get the Participant to emit a Message on all of its subscribers

genUUID :: Affection us UUID Source #

Helper function to generate new UUIDs

data UUID :: * #

Instances

Eq UUID 

Methods

(==) :: UUID -> UUID -> Bool

(/=) :: UUID -> UUID -> Bool

Data UUID 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID

toConstr :: UUID -> Constr

dataTypeOf :: UUID -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UUID)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID)

gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r

gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID

Ord UUID 

Methods

compare :: UUID -> UUID -> Ordering

(<) :: UUID -> UUID -> Bool

(<=) :: UUID -> UUID -> Bool

(>) :: UUID -> UUID -> Bool

(>=) :: UUID -> UUID -> Bool

max :: UUID -> UUID -> UUID

min :: UUID -> UUID -> UUID

Read UUID 

Methods

readsPrec :: Int -> ReadS UUID

readList :: ReadS [UUID]

readPrec :: ReadPrec UUID

readListPrec :: ReadPrec [UUID]

Show UUID 

Methods

showsPrec :: Int -> UUID -> ShowS

show :: UUID -> String

showList :: [UUID] -> ShowS

NFData UUID 

Methods

rnf :: UUID -> ()

Hashable UUID 

Methods

hashWithSalt :: Int -> UUID -> Int

hash :: UUID -> Int

Binary UUID 

Methods

put :: UUID -> Put

get :: Get UUID

putList :: [UUID] -> Put

Storable UUID 

Methods

sizeOf :: UUID -> Int

alignment :: UUID -> Int

peekElemOff :: Ptr UUID -> Int -> IO UUID

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO ()

peekByteOff :: Ptr b -> Int -> IO UUID

pokeByteOff :: Ptr b -> Int -> UUID -> IO ()

peek :: Ptr UUID -> IO UUID

poke :: Ptr UUID -> UUID -> IO ()

Random UUID 

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g)

random :: RandomGen g => g -> (UUID, g)

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID]

randoms :: RandomGen g => g -> [UUID]

randomRIO :: (UUID, UUID) -> IO UUID

randomIO :: IO UUID

data MsgId msg Source #

Constructors

(Message msg, Show msg) => MsgId UUID msg