kmonad-0.4.1: Advanced keyboard remapping utility

Copyright(c) David Janssen 2019
LicenseMIT
Maintainerjanssen.dhj@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

KMonad.Action

Contents

Description

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

Documentation

type KeyPred = KeyEvent -> Bool Source #

Predicate on KeyEvent's

data Catch Source #

Boolean isomorph signalling wether an event should be caught or not

Constructors

Catch 
NoCatch 
Instances
Eq Catch Source # 
Instance details

Defined in KMonad.Action

Methods

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

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

Show Catch Source # 
Instance details

Defined in KMonad.Action

Methods

showsPrec :: Int -> Catch -> ShowS #

show :: Catch -> String #

showList :: [Catch] -> ShowS #

Semigroup Catch Source # 
Instance details

Defined in KMonad.Action

Methods

(<>) :: Catch -> Catch -> Catch #

sconcat :: NonEmpty Catch -> Catch #

stimes :: Integral b => b -> Catch -> Catch #

Monoid Catch Source # 
Instance details

Defined in KMonad.Action

Methods

mempty :: Catch #

mappend :: Catch -> Catch -> Catch #

mconcat :: [Catch] -> Catch #

data Trigger Source #

The packet used to trigger a KeyFun, containing info about the event and how long since the Hook was registered.

Constructors

Trigger 

Fields

data Timeout m Source #

A Timeout value describes how long to wait and what to do upon timeout

Constructors

Timeout 

Fields

Instances
HasTimeout (Timeout m) m Source # 
Instance details

Defined in KMonad.Action

data HookLocation Source #

ADT signalling where to install a hook

Constructors

InputHook

Install the hook immediately after receiving a KeyEvent

OutputHook

Install the hook just before emitting a KeyEvent

Instances
Eq HookLocation Source # 
Instance details

Defined in KMonad.Action

Show HookLocation Source # 
Instance details

Defined in KMonad.Action

data Hook m Source #

The content for 1 key hook

Constructors

Hook 

Fields

Instances
HasHook (Hook m) m Source # 
Instance details

Defined in KMonad.Action

Methods

hook :: Lens' (Hook m) (Hook m) Source #

hTimeout :: Lens' (Hook m) (Maybe (Timeout m)) Source #

keyH :: Lens' (Hook m) (Trigger -> m Catch) Source #

Lenses

class HasHook c m | c -> m where Source #

Minimal complete definition

hook

Instances
HasHook (Hook m) m Source # 
Instance details

Defined in KMonad.Action

Methods

hook :: Lens' (Hook m) (Hook m) Source #

hTimeout :: Lens' (Hook m) (Maybe (Timeout m)) Source #

keyH :: Lens' (Hook m) (Trigger -> m Catch) Source #

class HasTimeout c m | c -> m where Source #

Minimal complete definition

timeout

Instances
HasTimeout (Timeout m) m Source # 
Instance details

Defined in KMonad.Action

Layer operations

Operations that manipulate the layer-stack

data LayerOp Source #

LayerOp describes all the different layer-manipulations that KMonad supports.

Constructors

PushLayer LayerTag

Add a layer to the top of the stack

PopLayer LayerTag

Remove the first occurence of a layer

SetBaseLayer LayerTag

Change the base-layer

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.

Methods

emit :: KeyEvent -> m () Source #

Emit a KeyEvent to the OS

pause :: Milliseconds -> m () Source #

Pause the current thread for n milliseconds

hold :: Bool -> m () Source #

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

Defined in KMonad.App

Methods

emit :: KeyEvent -> RIO e () Source #

pause :: Milliseconds -> RIO e () Source #

hold :: Bool -> RIO e () Source #

register :: HookLocation -> Hook (RIO e) -> RIO e () Source #

layerOp :: LayerOp -> RIO e () Source #

inject :: KeyEvent -> RIO e () Source #

shellCmd :: Text -> RIO e () Source #

class MonadKIO m => MonadK m where Source #

MonadKIO contains the additional bindings that get added when we are currently processing a button.

Methods

myBinding :: m Keycode Source #

Access the keycode to which the current button is bound

type AnyK a = forall m. MonadK m => m a Source #

Type alias for `any monad that can perform MonadK actions`

newtype Action Source #

A newtype wrapper used to construct MonadK actions

Constructors

Action 

Fields

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.

tHookF Source #

Arguments

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

within Source #

Arguments

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

withinHeld Source #

Arguments

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