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.State
import Data.List (isPrefixOf)
import Data.Maybe (catMaybes)
import Data.Bits ((.&.))
requestMouseEvents :: String
requestMouseEvents = "\ESC[?1000h\ESC[?1002h\ESC[?1006h"
disableMouseEvents :: String
disableMouseEvents = "\ESC[?1000l\ESC[?1002l\ESC[?1006l"
isMouseEvent :: String -> Bool
isMouseEvent s = isSGREvent s || isNormalEvent s
isSGREvent :: String -> Bool
isSGREvent = isPrefixOf sgrPrefix
sgrPrefix :: String
sgrPrefix = "\ESC[M"
isNormalEvent :: String -> Bool
isNormalEvent = isPrefixOf normalPrefix
normalPrefix :: String
normalPrefix = "\ESC[<"
shiftBit :: Int
shiftBit = 4
metaBit :: Int
metaBit = 8
ctrlBit :: Int
ctrlBit = 16
buttonMask :: Int
buttonMask = 67
leftButton :: Int
leftButton = 0
middleButton :: Int
middleButton = 1
rightButton :: Int
rightButton = 2
scrollUp :: Int
scrollUp = 64
scrollDown :: Int
scrollDown = 65
hasBitSet :: Int -> Int -> Bool
hasBitSet val bit = val .&. bit > 0
classifyMouseEvent :: String -> KClass
classifyMouseEvent s = runParser s $ do
when (not $ isMouseEvent s) failParse
expectChar '\ESC'
expectChar '['
ty <- readChar
case ty of
'<' -> classifySGRMouseEvent
'M' -> classifyNormalMouseEvent
_ -> failParse
getSGRButton :: Int -> Parser Button
getSGRButton mods =
let buttonMap = [ (leftButton, BLeft)
, (middleButton, BMiddle)
, (rightButton, BRight)
, (scrollUp, BScrollUp)
, (scrollDown, BScrollDown)
]
in case lookup (mods .&. buttonMask) buttonMap of
Nothing -> failParse
Just b -> return b
getModifiers :: Int -> [Modifier]
getModifiers mods =
catMaybes [ if mods `hasBitSet` shiftBit then Just MShift else Nothing
, if mods `hasBitSet` metaBit then Just MMeta else Nothing
, if mods `hasBitSet` ctrlBit then Just MCtrl else Nothing
]
classifyNormalMouseEvent :: Parser Event
classifyNormalMouseEvent = do
statusChar <- readChar
xCoordChar <- readChar
yCoordChar <- readChar
let xCoord = fromEnum xCoordChar 32
yCoord = fromEnum yCoordChar 32
status = fromEnum statusChar
modifiers = getModifiers status
let press = status .&. buttonMask /= 3
case press of
True -> do
button <- getSGRButton status
return $ EvMouseDown (xCoord1) (yCoord1) button modifiers
False -> return $ EvMouseUp (xCoord1) (yCoord1) Nothing
classifySGRMouseEvent :: Parser Event
classifySGRMouseEvent = do
mods <- readInt
expectChar ';'
xCoord <- readInt
expectChar ';'
yCoord <- readInt
final <- readChar
let modifiers = getModifiers mods
button <- getSGRButton mods
case final of
'M' -> return $ EvMouseDown (xCoord1) (yCoord1) button modifiers
'm' -> return $ EvMouseUp (xCoord1) (yCoord1) (Just button)
_ -> failParse