kmonad-0.4.1: Advanced keyboard remapping utility

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

Data.LayerStack

Contents

Description

A LayerStack is a set of different mappings between keys and values, and provides functionality for keeping track of a stack of these mappings. Lookup in a LayerStack happens by checking the front-most mapping on the stack, and if that fails, descending deeper.

A LayerStack has 3 type parameters, in the documentation we will refer to those as: - l: The layer key, which is the identifier for the different layers - k: The item key, which is the per-layer identifier for different items - a: The item (value), which is the value stored for k in a particular layer

LayerStack is used to implement the basic keymap logic in KMonad, where the configuration for a keyboard is essentially a set of layers. Each layer maps keycodes to buttons, and the entire layers can be overlayed on top of eachother.

Synopsis

Basic types

 

data Layer k a Source #

A Layer is one of the maps contained inside a LayerStack

Instances
Functor (Layer k) Source # 
Instance details

Defined in Data.LayerStack

Methods

fmap :: (a -> b) -> Layer k a -> Layer k b #

(<$) :: a -> Layer k b -> Layer k a #

Foldable (Layer k) Source # 
Instance details

Defined in Data.LayerStack

Methods

fold :: Monoid m => Layer k m -> m #

foldMap :: Monoid m => (a -> m) -> Layer k a -> m #

foldr :: (a -> b -> b) -> b -> Layer k a -> b #

foldr' :: (a -> b -> b) -> b -> Layer k a -> b #

foldl :: (b -> a -> b) -> b -> Layer k a -> b #

foldl' :: (b -> a -> b) -> b -> Layer k a -> b #

foldr1 :: (a -> a -> a) -> Layer k a -> a #

foldl1 :: (a -> a -> a) -> Layer k a -> a #

toList :: Layer k a -> [a] #

null :: Layer k a -> Bool #

length :: Layer k a -> Int #

elem :: Eq a => a -> Layer k a -> Bool #

maximum :: Ord a => Layer k a -> a #

minimum :: Ord a => Layer k a -> a #

sum :: Num a => Layer k a -> a #

product :: Num a => Layer k a -> a #

Traversable (Layer k) Source # 
Instance details

Defined in Data.LayerStack

Methods

traverse :: Applicative f => (a -> f b) -> Layer k a -> f (Layer k b) #

sequenceA :: Applicative f => Layer k (f a) -> f (Layer k a) #

mapM :: Monad m => (a -> m b) -> Layer k a -> m (Layer k b) #

sequence :: Monad m => Layer k (m a) -> m (Layer k a) #

(Eq k, Eq a) => Eq (Layer k a) Source # 
Instance details

Defined in Data.LayerStack

Methods

(==) :: Layer k a -> Layer k a -> Bool #

(/=) :: Layer k a -> Layer k a -> Bool #

(Ord k, Ord a) => Ord (Layer k a) Source # 
Instance details

Defined in Data.LayerStack

Methods

compare :: Layer k a -> Layer k a -> Ordering #

(<) :: Layer k a -> Layer k a -> Bool #

(<=) :: Layer k a -> Layer k a -> Bool #

(>) :: Layer k a -> Layer k a -> Bool #

(>=) :: Layer k a -> Layer k a -> Bool #

max :: Layer k a -> Layer k a -> Layer k a #

min :: Layer k a -> Layer k a -> Layer k a #

(Show k, Show a) => Show (Layer k a) Source # 
Instance details

Defined in Data.LayerStack

Methods

showsPrec :: Int -> Layer k a -> ShowS #

show :: Layer k a -> String #

showList :: [Layer k a] -> ShowS #

mkLayer :: (Foldable t, CanKey k) => t (k, a) -> Layer k a Source #

Create a new Layer from a Foldable of key-value pairs

data LayerStack l k a Source #

A LayerStack is a named collection of maps and a sequence of maps to use for lookup.

Instances
Functor (LayerStack l k) Source # 
Instance details

Defined in Data.LayerStack

Methods

fmap :: (a -> b) -> LayerStack l k a -> LayerStack l k b #

(<$) :: a -> LayerStack l k b -> LayerStack l k a #

(Eq l, Eq k, Eq a) => Eq (LayerStack l k a) Source # 
Instance details

Defined in Data.LayerStack

Methods

(==) :: LayerStack l k a -> LayerStack l k a -> Bool #

(/=) :: LayerStack l k a -> LayerStack l k a -> Bool #

(Show l, Show k, Show a) => Show (LayerStack l k a) Source # 
Instance details

Defined in Data.LayerStack

Methods

showsPrec :: Int -> LayerStack l k a -> ShowS #

show :: LayerStack l k a -> String #

showList :: [LayerStack l k a] -> ShowS #

mkLayerStack Source #

Arguments

:: (Foldable t1, Foldable t2, CanKey k, CanKey l) 
=> t1 (l, t2 (k, a))

The alist of alists describing the mapping

-> LayerStack l k a 

Create a new LayerStack from a foldable of foldables.

items :: forall l k a k a. Lens (LayerStack l k a) (LayerStack l k a) (HashMap (l, k) a) (HashMap (l, k) a) Source #

maps :: forall l k a. Lens' (LayerStack l k a) (HashSet l) Source #

stack :: forall l k a. Lens' (LayerStack l k a) [l] Source #

Basic operations on LayerStacks

 

atKey :: (CanKey l, CanKey k) => k -> Fold (LayerStack l k a) a Source #

Return a fold of all the items currently mapped to the item-key

This can be used with toListOf to get an overview of all the items currently mapped to an item-key, or more usefully, with firstOf to simply try a lookup like this: `stack^? atKey KeyA`

inLayer :: (CanKey l, CanKey k) => l -> k -> Fold (LayerStack l k a) a Source #

Try to look up a key in a specific layer, regardless of the stack

pushLayer :: (CanKey l, CanKey k) => l -> LayerStack l k a -> Either (LayerStackError l) (LayerStack l k a) Source #

Add a layer to the front of the stack and return the new LayerStack.

If the Layer does not exist, return a LayerStackError. If the Layer is already on the stack, bring it to the front.

popLayer :: (CanKey l, CanKey k) => l -> LayerStack l k a -> Either (LayerStackError l) (LayerStack l k a) Source #

Remove a layer from the stack. If the layer index does not exist on the stack, return a LayerNotOnStack, if the layer index does not exist at all in the LayerStack, return a LayerDoesNotExist.

Things that can go wrong with LayerStacks

 

data LayerStackError l Source #

The things that can go wrong with a LayerStack

Constructors

LayerDoesNotExist l

Requested use of a non-existing layer

LayerNotOnStack l

Requested use of a non-stack layer