Copyright | (c) David Janssen 2019 |
---|---|
License | MIT |
Maintainer | janssen.dhj@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
KMonad is implemented as an engine that is capable of running MonadK
actions.
The logic of various different buttons and keyboard operations are expressed in
this MonadK
. This module defines the basic types and operations that make up
MonadK
. The implementation of how KMonad implements MonadK
can be found in
the KMonad.App module.
NOTE: All of this is a bit muddled, and redoing the way hooks are handled, and the basic structuring of MonadK and MonadKIO are liable to change soon.
Synopsis
- type KeyPred = KeyEvent -> Bool
- data Catch
- data Trigger = Trigger {}
- data Timeout m = Timeout {
- _delay :: Milliseconds
- _action :: m ()
- data HookLocation
- data Hook m = Hook {}
- class HasHook c m | c -> m where
- class HasTimeout c m | c -> m where
- class HasTrigger c where
- data LayerOp
- class Monad m => MonadKIO m where
- class MonadKIO m => MonadK m where
- type AnyK a = forall m. MonadK m => m a
- newtype Action = Action {}
- my :: MonadK m => Switch -> m KeyEvent
- matchMy :: MonadK m => Switch -> m KeyPred
- after :: MonadK m => Milliseconds -> m () -> m ()
- whenDone :: MonadK m => m () -> m ()
- await :: MonadKIO m => KeyPred -> (KeyEvent -> m Catch) -> m ()
- awaitMy :: MonadK m => Switch -> m Catch -> m ()
- tHookF :: MonadK m => HookLocation -> Milliseconds -> m () -> (Trigger -> m Catch) -> m ()
- hookF :: MonadKIO m => HookLocation -> (KeyEvent -> m Catch) -> m ()
- within :: MonadK m => Milliseconds -> m KeyPred -> m () -> (Trigger -> m Catch) -> m ()
- withinHeld :: MonadK m => Milliseconds -> m KeyPred -> m () -> (Trigger -> m Catch) -> m ()
Documentation
Boolean isomorph signalling wether an event should be caught or not
The packet used to trigger a KeyFun, containing info about the event and how long since the Hook was registered.
Trigger | |
|
A Timeout
value describes how long to wait and what to do upon timeout
Timeout | |
|
data HookLocation Source #
ADT signalling where to install a hook
InputHook | Install the hook immediately after receiving a |
OutputHook | Install the hook just before emitting a |
Instances
Eq HookLocation Source # | |
Defined in KMonad.Action (==) :: HookLocation -> HookLocation -> Bool # (/=) :: HookLocation -> HookLocation -> Bool # | |
Show HookLocation Source # | |
Defined in KMonad.Action showsPrec :: Int -> HookLocation -> ShowS # show :: HookLocation -> String # showList :: [HookLocation] -> ShowS # |
The content for 1 key hook
Lenses
class HasTimeout c m | c -> m where Source #
class HasTrigger c where Source #
Layer operations
Operations that manipulate the layer-stack
LayerOp
describes all the different layer-manipulations that KMonad
supports.
MonadK
The fundamental components that make up any Button
operation.
class Monad m => MonadKIO m where Source #
MonadK
contains all the operations used to constitute button actions. It
encapsulates all the side-effects required to get everything running.
emit :: KeyEvent -> m () Source #
Emit a KeyEvent to the OS
pause :: Milliseconds -> m () Source #
Pause the current thread for n milliseconds
Pause or unpause event processing
register :: HookLocation -> Hook m -> m () Source #
Register a callback hook
layerOp :: LayerOp -> m () Source #
Run a layer-stack manipulation
inject :: KeyEvent -> m () Source #
Insert an event in the input queue
shellCmd :: Text -> m () Source #
Run a shell-command
Instances
(HasAppEnv e, HasAppCfg e, HasLogFunc e) => MonadKIO (RIO e) Source # | |
Defined in KMonad.App |
class MonadKIO m => MonadK m where Source #
MonadKIO
contains the additional bindings that get added when we are
currently processing a button.
type AnyK a = forall m. MonadK m => m a Source #
Type alias for `any monad that can perform MonadK actions`
A newtype wrapper used to construct MonadK
actions
Constituted actions
my :: MonadK m => Switch -> m KeyEvent Source #
Create a KeyEvent matching pressing or releasing of the current button.
matchMy :: MonadK m => Switch -> m KeyPred Source #
Create a KeyPred that matches the Press or Release of the current button.
after :: MonadK m => Milliseconds -> m () -> m () Source #
Perform an action after a period of time has elapsed
This is essentially just a way to perform async actions using the KMonad hook system.
whenDone :: MonadK m => m () -> m () Source #
Perform an action immediately after the current action is finished. NOTE: there is no guarantee that another event doesn't outrace this, only that it will happen as soon as the CPU gets to it.
await :: MonadKIO m => KeyPred -> (KeyEvent -> m Catch) -> m () Source #
Wait for an event to match a predicate and then execute an action
awaitMy :: MonadK m => Switch -> m Catch -> m () Source #
Execute an action on the detection of the Switch of the active button.
:: MonadK m | |
=> HookLocation | Where to install the hook |
-> Milliseconds | The timeout delay for the hook |
-> m () | The action to perform on timeout |
-> (Trigger -> m Catch) | The action to perform on trigger |
-> m () | The resulting action |
Register a hook with a timeout
hookF :: MonadKIO m => HookLocation -> (KeyEvent -> m Catch) -> m () Source #
Register a simple hook without a timeout
:: MonadK m | |
=> Milliseconds | The time within which this filter is active |
-> m KeyPred | The predicate used to find a match |
-> m () | The action to call on timeout |
-> (Trigger -> m Catch) | The action to call on a succesful match |
-> m () | The resulting action |
Try to call a function on a succesful match of a predicate within a certain time period. On a timeout, perform an action.
:: MonadK m | |
=> Milliseconds | The time within which this filter is active |
-> m KeyPred | The predicate used to find a match |
-> m () | The action to call on timeout |
-> (Trigger -> m Catch) | The action to call on a succesful match |
-> m () | The resulting action |
Like within
, but acquires a hold when starting, and releases when done