Copyright | (c) David Janssen 2019 |
---|---|
License | MIT |
Maintainer | janssen.dhj@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Layer k a
- mkLayer :: (Foldable t, CanKey k) => t (k, a) -> Layer k a
- data LayerStack l k a
- mkLayerStack :: (Foldable t1, Foldable t2, CanKey k, CanKey l) => t1 (l, t2 (k, a)) -> LayerStack l k a
- items :: forall l k a k a. Lens (LayerStack l k a) (LayerStack l k a) (HashMap (l, k) a) (HashMap (l, k) a)
- maps :: forall l k a. Lens' (LayerStack l k a) (HashSet l)
- stack :: forall l k a. Lens' (LayerStack l k a) [l]
- atKey :: (CanKey l, CanKey k) => k -> Fold (LayerStack l k a) a
- inLayer :: (CanKey l, CanKey k) => l -> k -> Fold (LayerStack l k a) a
- pushLayer :: (CanKey l, CanKey k) => l -> LayerStack l k a -> Either (LayerStackError l) (LayerStack l k a)
- popLayer :: (CanKey l, CanKey k) => l -> LayerStack l k a -> Either (LayerStackError l) (LayerStack l k a)
- data LayerStackError l
- = LayerDoesNotExist l
- | LayerNotOnStack l
- class AsLayerStackError r l | r -> l where
- _LayerStackError :: Prism' r (LayerStackError l)
- _LayerDoesNotExist :: Prism' r l
- _LayerNotOnStack :: Prism' r l
Basic types
A Layer
is one of the maps contained inside a LayerStack
Instances
Functor (Layer k) Source # | |
Foldable (Layer k) Source # | |
Defined in Data.LayerStack 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 # elem :: Eq a => a -> Layer k a -> Bool # maximum :: Ord a => Layer k a -> a # minimum :: Ord a => Layer k a -> a # | |
Traversable (Layer k) Source # | |
(Eq k, Eq a) => Eq (Layer k a) Source # | |
(Ord k, Ord a) => Ord (Layer k a) Source # | |
Defined in Data.LayerStack | |
(Show k, Show a) => Show (Layer k a) Source # | |
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 # | |
Defined in Data.LayerStack 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 # | |
Defined in Data.LayerStack (==) :: 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 # | |
Defined in Data.LayerStack showsPrec :: Int -> LayerStack l k a -> ShowS # show :: LayerStack l k a -> String # showList :: [LayerStack l k a] -> ShowS # |
:: (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 #
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 #
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
LayerDoesNotExist l | Requested use of a non-existing layer |
LayerNotOnStack l | Requested use of a non-stack layer |
Instances
Show l => Show (LayerStackError l) Source # | |
Defined in Data.LayerStack showsPrec :: Int -> LayerStackError l -> ShowS # show :: LayerStackError l -> String # showList :: [LayerStackError l] -> ShowS # | |
(Typeable l, Show l) => Exception (LayerStackError l) Source # | |
Defined in Data.LayerStack toException :: LayerStackError l -> SomeException # fromException :: SomeException -> Maybe (LayerStackError l) # displayException :: LayerStackError l -> String # | |
AsLayerStackError (LayerStackError l) l Source # | |
Defined in Data.LayerStack _LayerStackError :: Prism' (LayerStackError l) (LayerStackError l) Source # _LayerDoesNotExist :: Prism' (LayerStackError l) l Source # _LayerNotOnStack :: Prism' (LayerStackError l) l Source # |
class AsLayerStackError r l | r -> l where Source #
_LayerStackError :: Prism' r (LayerStackError l) Source #
_LayerDoesNotExist :: Prism' r l Source #
_LayerNotOnStack :: Prism' r l Source #
Instances
AsLayerStackError (LayerStackError l) l Source # | |
Defined in Data.LayerStack _LayerStackError :: Prism' (LayerStackError l) (LayerStackError l) Source # _LayerDoesNotExist :: Prism' (LayerStackError l) l Source # _LayerNotOnStack :: Prism' (LayerStackError l) l Source # |