wild-bind-0.1.2.6: Dynamic key binding framework

MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellNone
LanguageHaskell2010

WildBind.Binding

Contents

Description

This module exports functions to build and manipulate Binding, an object binding input symbols to actions.

Synopsis

Types

data Action m a Source #

Action done by WildBind

Constructors

Action 

Fields

Instances
Functor m => Functor (Action m) Source # 
Instance details

Defined in WildBind.Binding

Methods

fmap :: (a -> b) -> Action m a -> Action m b #

(<$) :: a -> Action m b -> Action m a #

Show (Action m a) Source # 
Instance details

Defined in WildBind.Binding

Methods

showsPrec :: Int -> Action m a -> ShowS #

show :: Action m a -> String #

showList :: [Action m a] -> ShowS #

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 => Semigroup (Binding' bs fs i) Source #

See Monoid instance.

Instance details

Defined in WildBind.Binding

Methods

(<>) :: Binding' bs fs i -> Binding' bs fs i -> Binding' bs fs i #

sconcat :: NonEmpty (Binding' bs fs i) -> Binding' bs fs i #

stimes :: Integral b => b -> Binding' bs fs i -> Binding' bs fs i #

Ord i => Monoid (Binding' bs fs i) Source #

mempty returns a Binding where no binding is defined. mappend combines two Bindings while preserving their individual implicit states. The right-hand Binding has precedence over the left-hand one. That is, if the two Bindings both have a binding to the same key in the same front-end and back-end state, the binding from the right-hand one is used.

Instance details

Defined in WildBind.Binding

Methods

mempty :: Binding' bs fs i #

mappend :: Binding' bs fs i -> Binding' bs fs i -> Binding' bs fs i #

mconcat :: [Binding' bs fs i] -> Binding' bs fs i #

Construction

Functions to create fundamental Bindings.

To create complex Bindings, use Condition functions described below and mappend them together.

noBinding :: Binding' bs fs i Source #

A Binding' with no bindings. It's the same as mempty, except noBinding requires no context.

data Binder i v a Source #

A monad to construct Binding'. i is the input symbol, and v is supposed to be the Action bound to i.

Instances
Monad (Binder i v) Source # 
Instance details

Defined in WildBind.Binding

Methods

(>>=) :: Binder i v a -> (a -> Binder i v b) -> Binder i v b #

(>>) :: Binder i v a -> Binder i v b -> Binder i v b #

return :: a -> Binder i v a #

fail :: String -> Binder i v a #

Functor (Binder i v) Source # 
Instance details

Defined in WildBind.Binding

Methods

fmap :: (a -> b) -> Binder i v a -> Binder i v b #

(<$) :: a -> Binder i v b -> Binder i v a #

Applicative (Binder i v) Source # 
Instance details

Defined in WildBind.Binding

Methods

pure :: a -> Binder i v a #

(<*>) :: Binder i v (a -> b) -> Binder i v a -> Binder i v b #

liftA2 :: (a -> b -> c) -> Binder i v a -> Binder i v b -> Binder i v c #

(*>) :: Binder i v a -> Binder i v b -> Binder i v b #

(<*) :: Binder i v a -> Binder i v b -> Binder i v a #

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.

bindsF :: Ord i => Binder i (Action (ReaderT fs IO) r) a -> Binding' bs fs i Source #

Like binds, but this function allows actions to use the current front-end state via ReaderT.

Since: 0.1.1.0

bindsF' :: Ord i => Binder i (Action (StateT bs (ReaderT fs IO)) r) a -> Binding' bs fs i Source #

Like binds', but this function allows actions to use the current front-end state via ReaderT.

Since: 0.1.1.0

on :: i -> v -> Binder i v () Source #

Create a Binder that binds the action v to the input i.

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 IO r)] -> Binding' bs fs i Source #

Non-monadic version of binds.

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 Bindings 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.

ifFront Source #

Arguments

:: (fs -> Bool)

The predicate

-> Binding' bs fs i

Enabled if the predicate is True

-> Binding' bs fs i

Enabled if the predicate is False

-> Binding' bs fs i 

Create a binding that behaves differently for different front-end states fs.

ifBack Source #

Arguments

:: (bs -> Bool)

The predicate

-> Binding' bs fs i

Enabled if the predicate is True

-> Binding' bs fs i

Enabled if the predicate is False

-> Binding' bs fs i 

Create a binding that behaves differently for different back-end states bs.

ifBoth Source #

Arguments

:: (bs -> fs -> Bool)

The predicate

-> Binding' bs fs i

Enabled if the predicate is True

-> Binding' bs fs i

Enabled if the predicate is False

-> Binding' bs fs i 

Create a binding that behaves differently for different front-end and back-end states, fs and bs.

whenFront Source #

Arguments

:: (fs -> Bool)

The predicate.

-> Binding' bs fs i

Enabled if the predicate is True

-> Binding' bs fs i 

Add a condition on the front-end state to Binding.

whenBack Source #

Arguments

:: (bs -> Bool)

The predicate.

-> Binding' bs fs i

Enabled if the predicate is True

-> Binding' bs fs i 

Add a condition on the back-end state to Binding.

whenBoth Source #

Arguments

:: (bs -> fs -> Bool)

The predicate.

-> Binding' bs fs i

Enabled if the predicate is True.

-> Binding' bs fs i 

Add a condition on the back-end and front-end states to Binding.

Conversion

Stateful bindings

startFrom Source #

Arguments

:: bs

Initial state

-> Binding' bs fs i

Binding' with explicit state

-> Binding fs i

Binding containing the state inside

Convert Binding' to Binding by hiding the explicit state bs.

extend :: Binding fs i -> Binding' bs fs i Source #

Extend Binding to Binding'. In the result Binding', the explicit back-end state is just ignored and unmodified.

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.

convBack Source #

Arguments

:: (bs -> bs' -> bs')

A setter. It's supposed to set bs into the original bs' and return the result.

-> (bs' -> bs)

A getter. It's supposed to extract bs from bs'.

-> 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.

revise Source #

Arguments

:: (forall a. bs -> fs -> i -> Action IO a -> Maybe (Action IO a))

A function to revise the action. If it returns Nothing, the action is unbound.

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

before Source #

Arguments

:: Applicative m 
=> m b

the monadic action prepended

-> Action m a

the original Action.

-> Action m a 

Make an Action that runs the given monadic action before the original Action.

after Source #

Arguments

:: Applicative m 
=> m b

the monadic action appended.

-> Action m a

the original Action.

-> Action m a 

Make an Action that runs the given monadic action after the original Action.

justBefore :: Applicative m => m b -> Action m a -> Maybe (Action m a) Source #

Same as before, but it returns Just.

Since: 0.1.1.0

justAfter :: Applicative m => m b -> Action m a -> Maybe (Action m a) Source #

Same as after, but it returns Just.

Since: 0.1.1.0

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.