Maintainer | Toshio Ito <debug.ito@gmail.com> |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
WildBind.Binding
Description
This module exports functions to build and manipulate Binding
, an
object binding input symbols to actions.
Synopsis
- data Action m a = Action {
- actDescription :: ActionDescription
- actDo :: m a
- type Binding s i = Binding' () s i
- data Binding' bs fs i
- noBinding :: Binding' bs fs i
- data Binder i v a
- binds :: Ord i => Binder i (Action IO r) a -> Binding' bs fs i
- binds' :: Ord i => Binder i (Action (StateT bs IO) r) a -> Binding' bs fs i
- bindsF :: Ord i => Binder i (Action (ReaderT fs IO) r) a -> Binding' bs fs i
- bindsF' :: Ord i => Binder i (Action (StateT bs (ReaderT fs IO)) r) a -> Binding' bs fs i
- on :: i -> v -> Binder i v ()
- run :: Functor m => (Action m () -> b) -> m a -> b
- as :: (Action m a -> b) -> ActionDescription -> Action m a -> b
- binding :: Ord i => [(i, Action IO r)] -> Binding' bs fs i
- binding' :: Ord i => [(i, Action (StateT bs IO) r)] -> Binding' bs fs i
- bindingF :: Ord i => [(i, Action (ReaderT fs IO) r)] -> Binding' bs fs i
- bindingF' :: Ord i => [(i, Action (StateT bs (ReaderT fs IO)) r)] -> Binding' bs fs i
- ifFront :: (fs -> Bool) -> Binding' bs fs i -> Binding' bs fs i -> Binding' bs fs i
- ifBack :: (bs -> Bool) -> Binding' bs fs i -> Binding' bs fs i -> Binding' bs fs i
- ifBoth :: (bs -> fs -> Bool) -> Binding' bs fs i -> Binding' bs fs i -> Binding' bs fs i
- whenFront :: (fs -> Bool) -> Binding' bs fs i -> Binding' bs fs i
- whenBack :: (bs -> Bool) -> Binding' bs fs i -> Binding' bs fs i
- whenBoth :: (bs -> fs -> Bool) -> Binding' bs fs i -> Binding' bs fs i
- startFrom :: bs -> Binding' bs fs i -> Binding fs i
- extend :: Binding fs i -> Binding' bs fs i
- convFront :: (fs -> fs') -> Binding' bs fs' i -> Binding' bs fs i
- convInput :: Ord i' => (i -> i') -> Binding' bs fs i -> Binding' bs fs i'
- convBack :: (bs -> bs' -> bs') -> (bs' -> bs) -> Binding' bs fs i -> Binding' bs' fs i
- advice :: (v -> v') -> Binder i v a -> Binder i v' a
- revise :: (forall a. bs -> fs -> i -> Action IO a -> Maybe (Action IO a)) -> Binding' bs fs i -> Binding' bs fs i
- revise' :: (forall a. bs -> fs -> i -> Action (StateT bs IO) a -> Maybe (Action (StateT bs IO) a)) -> Binding' bs fs i -> Binding' bs fs i
- before :: Applicative m => m b -> Action m a -> Action m a
- after :: Applicative m => m b -> Action m a -> Action m a
- justBefore :: Applicative m => m b -> Action m a -> Maybe (Action m a)
- justAfter :: Applicative m => m b -> Action m a -> Maybe (Action m a)
- boundAction :: Ord i => Binding s i -> s -> i -> Maybe (Action IO (Binding s i))
- boundAction' :: Ord i => Binding' bs fs i -> bs -> fs -> i -> Maybe (Action IO (Binding' bs fs i, bs))
- boundActions :: Binding s i -> s -> [(i, Action IO (Binding s i))]
- boundActions' :: Binding' bs fs i -> bs -> fs -> [(i, Action IO (Binding' bs fs i, bs))]
- boundInputs :: Binding s i -> s -> [i]
- boundInputs' :: Binding' bs fs i -> bs -> fs -> [i]
Types
Action done by WildBind
Constructors
Action | |
Fields
|
type Binding s i = Binding' () s i Source #
WildBind back-end binding between inputs and actions. s
is the
front-end state type, and i
is the input type.
data Binding' bs fs i Source #
WildBind back-end binding with both explicit and implicit
states. bs
is the explicit back-end state, fs
is the front-end
state, and i
is the input type.
You can make the explicit state bs
implicit by startFrom
function.
Instances
Ord i => Monoid (Binding' bs fs i) Source # |
|
Ord i => Semigroup (Binding' bs fs i) Source # | See Monoid instance. |
Construction
Functions to create fundamental Binding
s.
To create complex Binding
s, use Condition functions
described below and mappend
them together.
A monad to construct Binding'
. i
is the input symbol, and v
is supposed to be the Action
bound to i
.
binds :: Ord i => Binder i (Action IO r) a -> Binding' bs fs i Source #
Build a Binding
with no explicit or implicit state. The bound
actions are activated regardless of the back-end or front-end
state.
If different actions are bound to the same input, the latter action wins.
Result of action (r
) is discarded.
binds' :: Ord i => Binder i (Action (StateT bs IO) r) a -> Binding' bs fs i Source #
Build a Binding'
with an explicit state (but no implicit
state). The bound actions are activated regardless of the back-end
or front-end state.
run :: Functor m => (Action m () -> b) -> m a -> b infixl 2 Source #
Transform the given action m a
into an Action
and apply the
continuation to it. It discards the result of action (type
a
). Usually used as an operator.
as :: (Action m a -> b) -> ActionDescription -> Action m a -> b infixl 2 Source #
Transform the given continuation so that the ActionDescription
is set to the Action
passed to the continuation. Usually used as
an operator.
binding' :: Ord i => [(i, Action (StateT bs IO) r)] -> Binding' bs fs i Source #
Non-monadic version of binds'
.
bindingF :: Ord i => [(i, Action (ReaderT fs IO) r)] -> Binding' bs fs i Source #
Non-monadic version of bindsF
.
Since: 0.1.1.0
bindingF' :: Ord i => [(i, Action (StateT bs (ReaderT fs IO)) r)] -> Binding' bs fs i Source #
Non-monadic version of bindsF'
.
Since: 0.1.1.0
Condition
With these functions, you can create
Binding
s that behave differently for different front-end
and/or back-end states.
If you call the condition functions multiple times, the conditions are combined with AND logic.
Arguments
:: (fs -> Bool) | The predicate |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Create a binding that behaves differently for different front-end
states fs
.
Arguments
:: (bs -> Bool) | The predicate |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Create a binding that behaves differently for different back-end
states bs
.
Arguments
:: (bs -> fs -> Bool) | The predicate |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Create a binding that behaves differently for different front-end
and back-end states, fs
and bs
.
Arguments
:: (fs -> Bool) | The predicate. |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Add a condition on the front-end state to Binding
.
Arguments
:: (bs -> Bool) | The predicate. |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Add a condition on the back-end state to Binding
.
Arguments
:: (bs -> fs -> Bool) | The predicate. |
-> Binding' bs fs i | Enabled if the predicate is |
-> Binding' bs fs i |
Add a condition on the back-end and front-end states to
Binding
.
Conversion
Stateful bindings
Type conversion
convFront :: (fs -> fs') -> Binding' bs fs' i -> Binding' bs fs i Source #
Contramap the front-end state.
convInput :: Ord i' => (i -> i') -> Binding' bs fs i -> Binding' bs fs i' Source #
Map the front-end input.
Arguments
:: (bs -> bs' -> bs') | A setter. It's supposed to set
|
-> (bs' -> bs) | A getter. It's supposed to extract |
-> Binding' bs fs i | |
-> Binding' bs' fs i |
Convert the back-end state. Intuitively, it converts a small
state type bs
into a bigger state type bs'
, which includes
bs
.
For example, if you have a Lens'
l
, you can do
convBack (set l) (view l) b
Action conversion
advice :: (v -> v') -> Binder i v a -> Binder i v' a Source #
Transform the actions in the given Binder
.
Arguments
:: (forall a. bs -> fs -> i -> Action IO a -> Maybe (Action IO a)) | A function to revise the action. If it returns |
-> Binding' bs fs i | original binding |
-> Binding' bs fs i | revised binding |
Revise (modify) actions in the given Binding'
.
Since: 0.1.1.0
revise' :: (forall a. bs -> fs -> i -> Action (StateT bs IO) a -> Maybe (Action (StateT bs IO) a)) -> Binding' bs fs i -> Binding' bs fs i Source #
Like revise
, but this function allows revising the back-end state.
Since: 0.1.1.0
Arguments
:: Applicative m | |
=> m b | the monadic action prepended |
-> Action m a | the original |
-> Action m a |
Arguments
:: Applicative m | |
=> m b | the monadic action appended. |
-> Action m a | the original |
-> Action m a |
justBefore :: Applicative m => m b -> Action m a -> Maybe (Action m a) Source #
Execution
boundAction :: Ord i => Binding s i -> s -> i -> Maybe (Action IO (Binding s i)) Source #
Get the Action
bound to the specified state s
and input i
.
boundAction' :: Ord i => Binding' bs fs i -> bs -> fs -> i -> Maybe (Action IO (Binding' bs fs i, bs)) Source #
Get the Action
bound to the specified back-end state bs
,
front-end state fs
and input i
boundActions :: Binding s i -> s -> [(i, Action IO (Binding s i))] Source #
Get the list of all bound inputs i
and their corresponding
actions for the specified front-end state s
.
boundActions' :: Binding' bs fs i -> bs -> fs -> [(i, Action IO (Binding' bs fs i, bs))] Source #
Get the list of all bound inputs i
and their corresponding
actions for the specified back-end state bs
and front-end state
fs
.
boundInputs :: Binding s i -> s -> [i] Source #
Get the list of all bound inputs i
for the specified front-end
state s
.
boundInputs' :: Binding' bs fs i -> bs -> fs -> [i] Source #
Get the list of all bound inputs i
for the specified front-end
state fs
and the back-end state bs
.