module Graphics.Vty.Input.Mouse
( requestMouseEvents
, disableMouseEvents
, isMouseEvent
, classifyMouseEvent
)
where
import Graphics.Vty.Input.Events
import Graphics.Vty.Input.Classify.Types
import Graphics.Vty.Input.Classify.Parse
import Control.Monad
import Control.Monad.State
import Data.Maybe (catMaybes)
import Data.Bits ((.&.))
import qualified Data.ByteString.Char8 as BS8
import Data.ByteString.Char8 (ByteString)
requestMouseEvents :: ByteString
requestMouseEvents :: ByteString
requestMouseEvents = String -> ByteString
BS8.pack String
"\ESC[?1000h\ESC[?1002h\ESC[?1006h"
disableMouseEvents :: ByteString
disableMouseEvents :: ByteString
disableMouseEvents = String -> ByteString
BS8.pack String
"\ESC[?1000l\ESC[?1002l\ESC[?1006l"
isMouseEvent :: ByteString -> Bool
isMouseEvent :: ByteString -> Bool
isMouseEvent ByteString
s = ByteString -> Bool
isSGREvent ByteString
s Bool -> Bool -> Bool
|| ByteString -> Bool
isNormalEvent ByteString
s
isSGREvent :: ByteString -> Bool
isSGREvent :: ByteString -> Bool
isSGREvent = ByteString -> ByteString -> Bool
BS8.isPrefixOf ByteString
sgrPrefix
sgrPrefix :: ByteString
sgrPrefix :: ByteString
sgrPrefix = String -> ByteString
BS8.pack String
"\ESC[M"
isNormalEvent :: ByteString -> Bool
isNormalEvent :: ByteString -> Bool
isNormalEvent = ByteString -> ByteString -> Bool
BS8.isPrefixOf ByteString
normalPrefix
normalPrefix :: ByteString
normalPrefix :: ByteString
normalPrefix = String -> ByteString
BS8.pack String
"\ESC[<"
shiftBit :: Int
shiftBit :: Int
shiftBit = Int
4
metaBit :: Int
metaBit :: Int
metaBit = Int
8
ctrlBit :: Int
ctrlBit :: Int
ctrlBit = Int
16
buttonMask :: Int
buttonMask :: Int
buttonMask = Int
67
leftButton :: Int
leftButton :: Int
leftButton = Int
0
middleButton :: Int
middleButton :: Int
middleButton = Int
1
rightButton :: Int
rightButton :: Int
rightButton = Int
2
scrollUp :: Int
scrollUp :: Int
scrollUp = Int
64
scrollDown :: Int
scrollDown :: Int
scrollDown = Int
65
hasBitSet :: Int -> Int -> Bool
hasBitSet :: Int -> Int -> Bool
hasBitSet Int
val Int
bit = Int
val forall a. Bits a => a -> a -> a
.&. Int
bit forall a. Ord a => a -> a -> Bool
> Int
0
classifyMouseEvent :: ByteString -> KClass
classifyMouseEvent :: ByteString -> KClass
classifyMouseEvent ByteString
s = ByteString -> Parser Event -> KClass
runParser ByteString
s forall a b. (a -> b) -> a -> b
$ do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ ByteString -> Bool
isMouseEvent ByteString
s) forall a. Parser a
failParse
Char -> Parser ()
expectChar Char
'\ESC'
Char -> Parser ()
expectChar Char
'['
Char
ty <- Parser Char
readChar
case Char
ty of
Char
'<' -> Parser Event
classifySGRMouseEvent
Char
'M' -> Parser Event
classifyNormalMouseEvent
Char
_ -> forall a. Parser a
failParse
getSGRButton :: Int -> Parser Button
getSGRButton :: Int -> Parser Button
getSGRButton Int
mods =
let buttonMap :: [(Int, Button)]
buttonMap = [ (Int
leftButton, Button
BLeft)
, (Int
middleButton, Button
BMiddle)
, (Int
rightButton, Button
BRight)
, (Int
scrollUp, Button
BScrollUp)
, (Int
scrollDown, Button
BScrollDown)
]
in case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (Int
mods forall a. Bits a => a -> a -> a
.&. Int
buttonMask) [(Int, Button)]
buttonMap of
Maybe Button
Nothing -> forall a. Parser a
failParse
Just Button
b -> forall (m :: * -> *) a. Monad m => a -> m a
return Button
b
getModifiers :: Int -> [Modifier]
getModifiers :: Int -> [Modifier]
getModifiers Int
mods =
forall a. [Maybe a] -> [a]
catMaybes [ if Int
mods Int -> Int -> Bool
`hasBitSet` Int
shiftBit then forall a. a -> Maybe a
Just Modifier
MShift else forall a. Maybe a
Nothing
, if Int
mods Int -> Int -> Bool
`hasBitSet` Int
metaBit then forall a. a -> Maybe a
Just Modifier
MMeta else forall a. Maybe a
Nothing
, if Int
mods Int -> Int -> Bool
`hasBitSet` Int
ctrlBit then forall a. a -> Maybe a
Just Modifier
MCtrl else forall a. Maybe a
Nothing
]
classifyNormalMouseEvent :: Parser Event
classifyNormalMouseEvent :: Parser Event
classifyNormalMouseEvent = do
Char
statusChar <- Parser Char
readChar
Char
xCoordChar <- Parser Char
readChar
Char
yCoordChar <- Parser Char
readChar
let xCoord :: Int
xCoord = forall a. Enum a => a -> Int
fromEnum Char
xCoordChar forall a. Num a => a -> a -> a
- Int
32
yCoord :: Int
yCoord = forall a. Enum a => a -> Int
fromEnum Char
yCoordChar forall a. Num a => a -> a -> a
- Int
32
status :: Int
status = forall a. Enum a => a -> Int
fromEnum Char
statusChar
modifiers :: [Modifier]
modifiers = Int -> [Modifier]
getModifiers Int
status
let press :: Bool
press = Int
status forall a. Bits a => a -> a -> a
.&. Int
buttonMask forall a. Eq a => a -> a -> Bool
/= Int
3
case Bool
press of
Bool
True -> do
Button
button <- Int -> Parser Button
getSGRButton Int
status
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Int -> Button -> [Modifier] -> Event
EvMouseDown (Int
xCoordforall a. Num a => a -> a -> a
-Int
1) (Int
yCoordforall a. Num a => a -> a -> a
-Int
1) Button
button [Modifier]
modifiers
Bool
False -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Int -> Maybe Button -> Event
EvMouseUp (Int
xCoordforall a. Num a => a -> a -> a
-Int
1) (Int
yCoordforall a. Num a => a -> a -> a
-Int
1) forall a. Maybe a
Nothing
classifySGRMouseEvent :: Parser Event
classifySGRMouseEvent :: Parser Event
classifySGRMouseEvent = do
Int
mods <- Parser Int
readInt
Char -> Parser ()
expectChar Char
';'
Int
xCoord <- Parser Int
readInt
Char -> Parser ()
expectChar Char
';'
Int
yCoord <- Parser Int
readInt
Char
final <- Parser Char
readChar
let modifiers :: [Modifier]
modifiers = Int -> [Modifier]
getModifiers Int
mods
Button
button <- Int -> Parser Button
getSGRButton Int
mods
case Char
final of
Char
'M' -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Int -> Button -> [Modifier] -> Event
EvMouseDown (Int
xCoordforall a. Num a => a -> a -> a
-Int
1) (Int
yCoordforall a. Num a => a -> a -> a
-Int
1) Button
button [Modifier]
modifiers
Char
'm' -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Int -> Maybe Button -> Event
EvMouseUp (Int
xCoordforall a. Num a => a -> a -> a
-Int
1) (Int
yCoordforall a. Num a => a -> a -> a
-Int
1) (forall a. a -> Maybe a
Just Button
button)
Char
_ -> forall a. Parser a
failParse