{-# OPTIONS_HADDOCK hide #-}
module Graphics.Vty.Input.Classify
( classify
, KClass(..)
)
where
import Graphics.Vty.Input.Events
import Graphics.Vty.Input.Mouse
import Graphics.Vty.Input.Focus
import Graphics.Vty.Input.Paste
import Graphics.Vty.Input.Classify.Types
import Codec.Binary.UTF8.Generic (decode)
import Data.List (inits)
import qualified Data.Map as M( fromList, lookup )
import Data.Maybe ( mapMaybe )
import qualified Data.Set as S( fromList, member )
import Data.Char
import Data.Word
compile :: ClassifyMap -> [Char] -> KClass
compile table = cl' where
prefixSet = S.fromList $ concatMap (init . inits . fst) $ table
maxValidInputLength = maximum (map (length . fst) table)
eventForInput = M.fromList table
cl' [] = Prefix
cl' inputBlock = case M.lookup inputBlock eventForInput of
Just e -> Valid e []
Nothing -> case S.member inputBlock prefixSet of
True -> Prefix
False ->
let inputPrefixes = reverse $ take maxValidInputLength $ tail $ inits inputBlock
in case mapMaybe (\s -> (,) s `fmap` M.lookup s eventForInput) inputPrefixes of
(s,e) : _ -> Valid e (drop (length s) inputBlock)
[] -> Invalid
classify :: ClassifyMap -> [Char] -> KClass
classify table =
let standardClassifier = compile table
in \s -> case s of
_ | bracketedPasteStarted s ->
if bracketedPasteFinished s
then parseBracketedPaste s
else Prefix
_ | isMouseEvent s -> classifyMouseEvent s
_ | isFocusEvent s -> classifyFocusEvent s
c:cs | ord c >= 0xC2 -> classifyUtf8 c cs
_ -> standardClassifier s
classifyUtf8 :: Char -> [Char] -> KClass
classifyUtf8 c cs =
let n = utf8Length (ord c)
(codepoint,rest) = splitAt n (c:cs)
codepoint8 :: [Word8]
codepoint8 = map (fromIntegral . ord) codepoint
in case decode codepoint8 of
_ | n < length codepoint -> Prefix
Just (unicodeChar, _) -> Valid (EvKey (KChar unicodeChar) []) rest
Nothing -> Invalid
utf8Length :: (Num t, Ord a, Num a) => a -> t
utf8Length c
| c < 0x80 = 1
| c < 0xE0 = 2
| c < 0xF0 = 3
| otherwise = 4