module System.Terminal.Decoder where
import Data.Char
import Data.Monoid ((<>))
import System.Terminal.MonadInput
import System.Terminal.MonadScreen (Position (..))
newtype Decoder = Decoder { feedDecoder :: Modifiers -> Char -> Either Decoder [Event] }
defaultDecoder :: (Modifiers -> Char -> Maybe Event) -> Decoder
defaultDecoder specialChar = defaultMode
where
defaultMode :: Decoder
defaultMode = Decoder $ \mods c-> if
| c == '\NUL' -> Right []
| c == '\ESC' -> Left escapeMode
| c <= '\US' -> Right $ [KeyEvent (CharKey (toEnum $ (+64) $ fromEnum c)) (mods <> ctrlKey)] ++ f mods c
| c < '\DEL' -> Right $ [KeyEvent (CharKey c) mods] ++ f mods c
| c < '\xA0' -> Right $ f mods c
| otherwise -> Right [KeyEvent (CharKey c) mods]
where
f mods c = maybe [] pure (specialChar mods c)
escapeMode :: Decoder
escapeMode = Decoder $ \mods c-> if
| c == '\NUL' -> Right [KeyEvent (CharKey '[') (mods <> ctrlKey), KeyEvent EscapeKey mods]
| otherwise -> Left (escapeSequenceMode c)
escapeSequenceMode :: Char -> Decoder
escapeSequenceMode c = Decoder $ \mods d-> if
| d == '\NUL' && c > '\SP' && c <= '~' -> Right [KeyEvent (CharKey c) (mods <> altKey)]
| d == '\NUL' && c >= '\xa0' -> Right [KeyEvent (CharKey c) (mods <> altKey)]
| d == '\NUL' -> Right $ case specialChar mods c of
Nothing -> []
Just ev -> case ev of
KeyEvent key m -> [KeyEvent key (mods <> m <> altKey)]
_ -> [ev]
| c == 'O' -> Right (ss3Mode mods d)
| c == '[' -> csiMode d
| otherwise -> Right []
ss3Mode :: Modifiers -> Char -> [Event]
ss3Mode mods = \case
'P' -> [KeyEvent (FunctionKey 1) mods]
'Q' -> [KeyEvent (FunctionKey 2) mods]
'R' -> [KeyEvent (FunctionKey 3) mods]
'S' -> [KeyEvent (FunctionKey 4) mods]
_ -> []
csiMode :: Char -> Either Decoder [Event]
csiMode c
| c >= '0' && c <= '?' = Left $ f (charLimit - 1) [c]
| c >= '!' && c <= '/' = Left $ g (charLimit - 1) [] [c]
| c >= '@' && c <= '~' = Right $ interpretCSI [] [] c
| otherwise = Right []
where
charLimit :: Int
charLimit = 16
f :: Int -> String -> Decoder
f 0 _ = defaultMode
f i ps = Decoder $ const $ \x-> if
| x >= '0' && x <= '?' -> Left $ f (i - 1) (x:ps)
| x >= '!' && x <= '/' -> Left $ g charLimit ps []
| x >= '@' && x <= '~' -> Right $ interpretCSI (reverse ps) [] x
| otherwise -> Right []
g :: Int -> String -> String -> Decoder
g 0 _ _ = defaultMode
g i ps is = Decoder $ const $ \x-> if
| x >= '!' && x <= '/' -> Left $ g (i - 1) ps (x:is)
| x >= '@' && x <= '~' -> Right $ interpretCSI (reverse ps) (reverse is) x
| otherwise -> Right []
interpretCSI :: String -> String -> Char -> [Event]
interpretCSI params _intermediates = \case
'$' -> [KeyEvent DeleteKey (altKey `mappend` shiftKey)]
'@' -> []
'A' -> modified $ ArrowKey Upwards
'B' -> modified $ ArrowKey Downwards
'C' -> modified $ ArrowKey Rightwards
'D' -> modified $ ArrowKey Leftwards
'E' -> modified BeginKey
'F' -> modified EndKey
'G' -> []
'H' -> modified HomeKey
'I' -> modified TabKey
'J' -> []
'K' -> []
'L' -> []
'M' -> []
'N' -> []
'O' -> []
'P' -> modified (FunctionKey 1)
'Q' -> modified (FunctionKey 2)
'R' -> modified (FunctionKey 3) ++ [DeviceEvent $ CursorPositionReport $ Position (fstNumber 1 - 1) (sndNumber 1 - 1)]
'S' -> modified (FunctionKey 4)
'T' -> []
'U' -> []
'V' -> []
'W' -> []
'X' -> []
'Y' -> []
'Z' -> [KeyEvent TabKey shiftKey]
'^' -> case params of
"2" -> [KeyEvent InsertKey ctrlKey]
"3" -> [KeyEvent DeleteKey ctrlKey]
"4" -> [KeyEvent PageUpKey ctrlKey]
"7" -> [KeyEvent PageDownKey ctrlKey]
"5" -> [KeyEvent HomeKey ctrlKey]
"6" -> [KeyEvent EndKey ctrlKey]
"11" -> [KeyEvent (FunctionKey 1) ctrlKey]
"12" -> [KeyEvent (FunctionKey 2) ctrlKey]
"13" -> [KeyEvent (FunctionKey 3) ctrlKey]
"14" -> [KeyEvent (FunctionKey 4) ctrlKey]
"15" -> [KeyEvent (FunctionKey 5) ctrlKey]
"17" -> [KeyEvent (FunctionKey 6) ctrlKey]
"18" -> [KeyEvent (FunctionKey 7) ctrlKey]
"19" -> [KeyEvent (FunctionKey 8) ctrlKey]
"20" -> [KeyEvent (FunctionKey 9) ctrlKey]
"21" -> [KeyEvent (FunctionKey 10) ctrlKey]
"23" -> [KeyEvent (FunctionKey 11) ctrlKey]
"24" -> [KeyEvent (FunctionKey 12) ctrlKey]
_ -> []
'f' -> []
'i' -> [KeyEvent PrintKey mempty]
'm' -> []
'~' -> case fstParam of
"2" -> modified InsertKey
"3" -> modified DeleteKey
"5" -> modified PageUpKey
"6" -> modified PageDownKey
"9" -> modified HomeKey
"10" -> modified EndKey
"11" -> modified (FunctionKey 1)
"12" -> modified (FunctionKey 2)
"13" -> modified (FunctionKey 3)
"14" -> modified (FunctionKey 4)
"15" -> modified (FunctionKey 5)
"17" -> modified (FunctionKey 6)
"18" -> modified (FunctionKey 7)
"19" -> modified (FunctionKey 8)
"20" -> modified (FunctionKey 9)
"21" -> modified (FunctionKey 10)
"23" -> modified (FunctionKey 11)
"24" -> modified (FunctionKey 12)
_ -> []
_ -> []
where
fstParam :: String
fstParam = takeWhile (/= ';') params
sndParam :: String
sndParam = takeWhile (/= ';') $ drop 1 $ dropWhile (/= ';') params
fstNumber :: Int -> Int
fstNumber i
| not (null fstParam) && all isDigit fstParam = read fstParam
| otherwise = i
sndNumber :: Int -> Int
sndNumber i
| not (null sndParam) && all isDigit sndParam = read sndParam
| otherwise = i
modified key = case sndParam of
"" -> [KeyEvent key mempty ]
"2" -> [KeyEvent key shiftKey ]
"3" -> [KeyEvent key altKey ]
"4" -> [KeyEvent key $ shiftKey <> altKey ]
"5" -> [KeyEvent key ctrlKey]
"6" -> [KeyEvent key $ shiftKey <> ctrlKey]
"7" -> [KeyEvent key $ altKey <> ctrlKey]
"8" -> [KeyEvent key $ shiftKey <> altKey <> ctrlKey]
_ -> []