happstack-state-0.3.2: Event-based distributed state.Source codeContentsIndex
Happstack.State.ComponentSystem
Synopsis
data End = End
data h :+: t = h :+: t
class (Serialize ev, Serialize res) => UpdateEvent ev res | ev -> res
class (Serialize ev, Serialize res) => QueryEvent ev res | ev -> res
data Method st where
Update :: UpdateEvent ev res => (ev -> Update st res) -> Method st
Query :: QueryEvent ev res => (ev -> Query st res) -> Method st
methodType :: Method t -> String
class Methods a where
methods :: Proxy a -> [Method a]
data MethodMap where
MethodMap :: Component st => Map String (Method st) -> MethodMap
type ComponentTree = Map String MethodMap
type ComponentVersions = Map String [ByteString]
class (SubHandlers (Dependencies a), Serialize a) => Component a where
type Dependencies a
initialValue :: a
onLoad :: Proxy a -> IO ()
class SubHandlers a where
subHandlers :: a -> Collect ()
data Collection = Collection ComponentTree ComponentVersions [IO ()]
addItem :: MonadState Collection m => String -> MethodMap -> [ByteString] -> IO () -> m ()
type Collect = State Collection
collectHandlers :: (Methods a, Component a) => Proxy a -> (ComponentTree, ComponentVersions, [IO ()])
collectHandlers' :: (Methods a, Component a) => Proxy a -> Collect ()
dup :: String -> b
Documentation
data End Source
Equivalent of [] for type level lists. Used for Components that have no dependencies
Constructors
End
show/hide Instances
data h :+: t Source
Type level Cons for enumerating type dependencies of a Component
Constructors
h :+: t
show/hide Instances
class (Serialize ev, Serialize res) => UpdateEvent ev res | ev -> resSource
show/hide Instances
class (Serialize ev, Serialize res) => QueryEvent ev res | ev -> resSource
show/hide Instances
data Method st whereSource
Method is the actual type that all Updates and Querys eventually get lifted into via mkMethods.
Constructors
Update :: UpdateEvent ev res => (ev -> Update st res) -> Method st
Query :: QueryEvent ev res => (ev -> Query st res) -> Method st
show/hide Instances
methodType :: Method t -> StringSource
Displays the type of a Method
class Methods a whereSource
Class for enumerating the set of defined methods by the type of the state. Instances should not be defined directly, but using mkMethods
Methods
methods :: Proxy a -> [Method a]Source
data MethodMap whereSource
Constructors
MethodMap :: Component st => Map String (Method st) -> MethodMap
show/hide Instances
type ComponentTree = Map String MethodMapSource
State type -> method map
type ComponentVersions = Map String [ByteString]Source
State type -> all versions
class (SubHandlers (Dependencies a), Serialize a) => Component a whereSource
In order to be used as a part of Happstack's MACID state, a data type needs to be an instance of Component. The minimal definition is an initialValue and the type corresponding to the set of Dependencies. Note that the SubHandlers condition will be automatically met if the Dependencies is built from End and ':+:' with other instances of Component and Methods
Associated Types
type Dependencies a Source
Methods
initialValue :: aSource
onLoad :: Proxy a -> IO ()Source
class SubHandlers a whereSource
SubHandlers is used to build up the set of components corresponding to the instance type.
Methods
subHandlers :: a -> Collect ()Source
show/hide Instances
data Collection Source
Constructors
Collection ComponentTree ComponentVersions [IO ()]
addItem :: MonadState Collection m => String -> MethodMap -> [ByteString] -> IO () -> m ()Source
type Collect = State CollectionSource
collectHandlers :: (Methods a, Component a) => Proxy a -> (ComponentTree, ComponentVersions, [IO ()])Source
collectHandlers' :: (Methods a, Component a) => Proxy a -> Collect ()Source
dup :: String -> bSource
An error is thrown when this is evaluated.
Produced by Haddock version 2.4.2