affection-0.0.0.9: A simple Game Engine using SDL

Safe HaskellNone
LanguageHaskell2010

Affection.MessageBus.Class

Synopsis

Documentation

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

This typeclass defines the behaviour of a participant in the message system

Minimal complete definition

partSubscribers, partSubscribe, partUnSubscribe

Associated Types

type Mesg prt us :: * Source #

Message datatype

Methods

partSubscribers Source #

Arguments

:: prt

the Participant's subscriber storage

-> Affection us [Mesg prt us -> 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

-> (Mesg prt us -> Affection us ())

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

-> Affection us UUID

UUID of the registered subscriber Function

Subscribe to the Participant's events

partUnSubscribe Source #

Arguments

:: prt

The Participant's subscriber storage to unsubscribe from

-> UUID

The subscriber function's UUID

-> Affection us () 

Unsubscribe a Subscriber function from Participant

partEmit Source #

Arguments

:: prt

The Participant's subscriber storage

-> Mesg prt us

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 #

The UUID type. A Random instance is provided which produces version 4 UUIDs as specified in RFC 4122. The Storable and Binary instances are compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instances
Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

Data UUID 
Instance details

Defined in Data.UUID.Types.Internal

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 
Instance details

Defined in Data.UUID.Types.Internal

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 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Storable UUID 
Instance details

Defined in Data.UUID.Types.Internal

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 () #

Binary UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID 
Instance details

Defined in Data.UUID.Types.Internal

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 #