{-# LANGUAGE DeriveAnyClass #-}
module KMonad.Keyboard
(
Switch(..)
, KeyEvent
, switch
, keycode
, mkKeyEvent
, mkPress
, mkRelease
, KeyPred
, isPress
, isRelease
, isKeycode
, isPressOf
, isReleaseOf
, LayerTag
, LMap
, module KMonad.Keyboard.Keycode
)
where
import KMonad.Prelude
import KMonad.Keyboard.Keycode
import qualified Data.LayerStack as Ls
data Switch
= Press
| Release
deriving (Switch -> Switch -> Bool
(Switch -> Switch -> Bool)
-> (Switch -> Switch -> Bool) -> Eq Switch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Switch -> Switch -> Bool
$c/= :: Switch -> Switch -> Bool
== :: Switch -> Switch -> Bool
$c== :: Switch -> Switch -> Bool
Eq, Eq Switch
Eq Switch =>
(Switch -> Switch -> Ordering)
-> (Switch -> Switch -> Bool)
-> (Switch -> Switch -> Bool)
-> (Switch -> Switch -> Bool)
-> (Switch -> Switch -> Bool)
-> (Switch -> Switch -> Switch)
-> (Switch -> Switch -> Switch)
-> Ord Switch
Switch -> Switch -> Bool
Switch -> Switch -> Ordering
Switch -> Switch -> Switch
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Switch -> Switch -> Switch
$cmin :: Switch -> Switch -> Switch
max :: Switch -> Switch -> Switch
$cmax :: Switch -> Switch -> Switch
>= :: Switch -> Switch -> Bool
$c>= :: Switch -> Switch -> Bool
> :: Switch -> Switch -> Bool
$c> :: Switch -> Switch -> Bool
<= :: Switch -> Switch -> Bool
$c<= :: Switch -> Switch -> Bool
< :: Switch -> Switch -> Bool
$c< :: Switch -> Switch -> Bool
compare :: Switch -> Switch -> Ordering
$ccompare :: Switch -> Switch -> Ordering
$cp1Ord :: Eq Switch
Ord, Int -> Switch -> ShowS
[Switch] -> ShowS
Switch -> String
(Int -> Switch -> ShowS)
-> (Switch -> String) -> ([Switch] -> ShowS) -> Show Switch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Switch] -> ShowS
$cshowList :: [Switch] -> ShowS
show :: Switch -> String
$cshow :: Switch -> String
showsPrec :: Int -> Switch -> ShowS
$cshowsPrec :: Int -> Switch -> ShowS
Show, Int -> Switch
Switch -> Int
Switch -> [Switch]
Switch -> Switch
Switch -> Switch -> [Switch]
Switch -> Switch -> Switch -> [Switch]
(Switch -> Switch)
-> (Switch -> Switch)
-> (Int -> Switch)
-> (Switch -> Int)
-> (Switch -> [Switch])
-> (Switch -> Switch -> [Switch])
-> (Switch -> Switch -> [Switch])
-> (Switch -> Switch -> Switch -> [Switch])
-> Enum Switch
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Switch -> Switch -> Switch -> [Switch]
$cenumFromThenTo :: Switch -> Switch -> Switch -> [Switch]
enumFromTo :: Switch -> Switch -> [Switch]
$cenumFromTo :: Switch -> Switch -> [Switch]
enumFromThen :: Switch -> Switch -> [Switch]
$cenumFromThen :: Switch -> Switch -> [Switch]
enumFrom :: Switch -> [Switch]
$cenumFrom :: Switch -> [Switch]
fromEnum :: Switch -> Int
$cfromEnum :: Switch -> Int
toEnum :: Int -> Switch
$ctoEnum :: Int -> Switch
pred :: Switch -> Switch
$cpred :: Switch -> Switch
succ :: Switch -> Switch
$csucc :: Switch -> Switch
Enum, (forall x. Switch -> Rep Switch x)
-> (forall x. Rep Switch x -> Switch) -> Generic Switch
forall x. Rep Switch x -> Switch
forall x. Switch -> Rep Switch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Switch x -> Switch
$cfrom :: forall x. Switch -> Rep Switch x
Generic, Int -> Switch -> Int
Switch -> Int
(Int -> Switch -> Int) -> (Switch -> Int) -> Hashable Switch
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Switch -> Int
$chash :: Switch -> Int
hashWithSalt :: Int -> Switch -> Int
$chashWithSalt :: Int -> Switch -> Int
Hashable)
data KeyEvent = KeyEvent
{ KeyEvent -> Switch
_switch :: Switch
, KeyEvent -> Keycode
_keycode :: Keycode
} deriving (KeyEvent -> KeyEvent -> Bool
(KeyEvent -> KeyEvent -> Bool)
-> (KeyEvent -> KeyEvent -> Bool) -> Eq KeyEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyEvent -> KeyEvent -> Bool
$c/= :: KeyEvent -> KeyEvent -> Bool
== :: KeyEvent -> KeyEvent -> Bool
$c== :: KeyEvent -> KeyEvent -> Bool
Eq, Int -> KeyEvent -> ShowS
[KeyEvent] -> ShowS
KeyEvent -> String
(Int -> KeyEvent -> ShowS)
-> (KeyEvent -> String) -> ([KeyEvent] -> ShowS) -> Show KeyEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyEvent] -> ShowS
$cshowList :: [KeyEvent] -> ShowS
show :: KeyEvent -> String
$cshow :: KeyEvent -> String
showsPrec :: Int -> KeyEvent -> ShowS
$cshowsPrec :: Int -> KeyEvent -> ShowS
Show, (forall x. KeyEvent -> Rep KeyEvent x)
-> (forall x. Rep KeyEvent x -> KeyEvent) -> Generic KeyEvent
forall x. Rep KeyEvent x -> KeyEvent
forall x. KeyEvent -> Rep KeyEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeyEvent x -> KeyEvent
$cfrom :: forall x. KeyEvent -> Rep KeyEvent x
Generic, Int -> KeyEvent -> Int
KeyEvent -> Int
(Int -> KeyEvent -> Int) -> (KeyEvent -> Int) -> Hashable KeyEvent
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: KeyEvent -> Int
$chash :: KeyEvent -> Int
hashWithSalt :: Int -> KeyEvent -> Int
$chashWithSalt :: Int -> KeyEvent -> Int
Hashable)
makeLenses ''KeyEvent
instance Display KeyEvent where
textDisplay :: KeyEvent -> Text
textDisplay a :: KeyEvent
a = Switch -> Text
forall a. Show a => a -> Text
tshow (KeyEvent
aKeyEvent -> Getting Switch KeyEvent Switch -> Switch
forall s a. s -> Getting a s a -> a
^.Getting Switch KeyEvent Switch
Lens' KeyEvent Switch
switch) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Keycode -> Text
forall a. Display a => a -> Text
textDisplay (KeyEvent
aKeyEvent -> Getting Keycode KeyEvent Keycode -> Keycode
forall s a. s -> Getting a s a -> a
^.Getting Keycode KeyEvent Keycode
Lens' KeyEvent Keycode
keycode)
instance Ord KeyEvent where
a :: KeyEvent
a compare :: KeyEvent -> KeyEvent -> Ordering
`compare` b :: KeyEvent
b = case (KeyEvent
aKeyEvent -> Getting Switch KeyEvent Switch -> Switch
forall s a. s -> Getting a s a -> a
^.Getting Switch KeyEvent Switch
Lens' KeyEvent Switch
switch) Switch -> Switch -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` (KeyEvent
bKeyEvent -> Getting Switch KeyEvent Switch -> Switch
forall s a. s -> Getting a s a -> a
^.Getting Switch KeyEvent Switch
Lens' KeyEvent Switch
switch) of
EQ -> (KeyEvent
aKeyEvent -> Getting Keycode KeyEvent Keycode -> Keycode
forall s a. s -> Getting a s a -> a
^.Getting Keycode KeyEvent Keycode
Lens' KeyEvent Keycode
keycode) Keycode -> Keycode -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` (KeyEvent
bKeyEvent -> Getting Keycode KeyEvent Keycode -> Keycode
forall s a. s -> Getting a s a -> a
^.Getting Keycode KeyEvent Keycode
Lens' KeyEvent Keycode
keycode)
x :: Ordering
x -> Ordering
x
mkKeyEvent :: Switch -> Keycode -> KeyEvent
mkKeyEvent :: Switch -> Keycode -> KeyEvent
mkKeyEvent = Switch -> Keycode -> KeyEvent
KeyEvent
mkPress :: Keycode -> KeyEvent
mkPress :: Keycode -> KeyEvent
mkPress = Switch -> Keycode -> KeyEvent
KeyEvent Switch
Press
mkRelease :: Keycode -> KeyEvent
mkRelease :: Keycode -> KeyEvent
mkRelease = Switch -> Keycode -> KeyEvent
KeyEvent Switch
Release
type KeyPred = KeyEvent -> Bool
isPress :: KeyPred
isPress :: KeyEvent -> Bool
isPress = (Switch -> Switch -> Bool
forall a. Eq a => a -> a -> Bool
== Switch
Press) (Switch -> Bool) -> (KeyEvent -> Switch) -> KeyEvent -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Switch KeyEvent Switch -> KeyEvent -> Switch
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Switch KeyEvent Switch
Lens' KeyEvent Switch
switch
isRelease :: KeyPred
isRelease :: KeyEvent -> Bool
isRelease = Bool -> Bool
not (Bool -> Bool) -> (KeyEvent -> Bool) -> KeyEvent -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyEvent -> Bool
isPress
isKeycode :: Keycode -> KeyPred
isKeycode :: Keycode -> KeyEvent -> Bool
isKeycode c :: Keycode
c = (Keycode -> Keycode -> Bool
forall a. Eq a => a -> a -> Bool
== Keycode
c) (Keycode -> Bool) -> (KeyEvent -> Keycode) -> KeyEvent -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Keycode KeyEvent Keycode -> KeyEvent -> Keycode
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Keycode KeyEvent Keycode
Lens' KeyEvent Keycode
keycode
isReleaseOf :: Keycode -> KeyPred
isReleaseOf :: Keycode -> KeyEvent -> Bool
isReleaseOf = KeyEvent -> KeyEvent -> Bool
forall a. Eq a => a -> a -> Bool
(==) (KeyEvent -> KeyEvent -> Bool)
-> (Keycode -> KeyEvent) -> Keycode -> KeyEvent -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Keycode -> KeyEvent
mkRelease
isPressOf :: Keycode -> KeyPred
isPressOf :: Keycode -> KeyEvent -> Bool
isPressOf = KeyEvent -> KeyEvent -> Bool
forall a. Eq a => a -> a -> Bool
(==) (KeyEvent -> KeyEvent -> Bool)
-> (Keycode -> KeyEvent) -> Keycode -> KeyEvent -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Keycode -> KeyEvent
mkPress
type LayerTag = Text
type LMap a = Ls.LayerStack LayerTag Keycode a