module KMonad.Args.Parser
  ( parseTokens
  , loadTokens
  )
where
import KMonad.Prelude hiding (try, bool)
import KMonad.Args.Types
import KMonad.Keyboard
import KMonad.Keyboard.ComposeSeq
import Data.Char
import RIO.List (sortBy, find)
import qualified Data.MultiMap as Q
import qualified RIO.Text as T
import qualified Text.Megaparsec.Char.Lexer as L
parseTokens :: Text -> Either PErrors [KExpr]
parseTokens t = case runParser configP "" t  of
  Left  e -> Left $ PErrors e
  Right x -> Right x
loadTokens :: FilePath -> RIO e [KExpr]
loadTokens pth = parseTokens <$> readFileUtf8 pth >>= \case
  Left e   -> throwM e
  Right xs -> pure xs
sc :: Parser ()
sc = L.space
  space1
  (L.skipLineComment  ";;")
  (L.skipBlockComment "#|" "|#")
lexeme :: Parser a -> Parser a
lexeme = L.lexeme sc
symbol :: Text -> Parser ()
symbol = void . L.symbol sc
terminators :: String
terminators = ")\""
terminatorP :: Parser Char
terminatorP = satisfy (`elem` terminators)
word :: Parser Text
word = T.pack <$> some (satisfy wordChar)
  where wordChar c = not (isSpace c || c `elem` terminators)
terminated :: Parser a -> Parser a
terminated p = try $ p <* lookAhead (void spaceChar <|> eof <|> void terminatorP)
prefix :: Parser a -> Parser a
prefix p = try $ p <* notFollowedBy (void spaceChar <|> eof)
fromNamed :: [(Text, a)] -> Parser a
fromNamed = choice . map mkOne . srt
  where
    
    srt :: [(Text, b)] -> [(Text, b)]
    srt = sortBy . flip on fst $ \a b ->
      case compare (T.length b) (T.length a) of
        EQ -> compare a b
        x  -> x
    
    mkOne (s, x) = terminated (string s) *> pure x
paren :: Parser a -> Parser a
paren = between (symbol "(") (symbol ")")
statement :: Text -> Parser a -> Parser a
statement s = paren . (symbol s *>)
bool :: Parser Bool
bool = symbol "true" *> pure True
   <|> symbol "false" *> pure False
keycodeP :: Parser Keycode
keycodeP = fromNamed (Q.reverse keyNames ^.. Q.itemed) <?> "keycode"
numP :: Parser Int
numP = L.decimal
textP :: Parser Text
textP = do
  _ <- char '\"'
  s <- manyTill L.charLiteral (char '\"')
  pure . T.pack $ s
derefP :: Parser Text
derefP = prefix (char '@') *> word
configP :: Parser [KExpr]
configP = sc *> exprsP <* eof
exprsP :: Parser [KExpr]
exprsP = lexeme . many $ lexeme exprP
exprP :: Parser KExpr
exprP = paren . choice $
  [ try (symbol "defcfg")   *> (KDefCfg   <$> defcfgP)
  , try (symbol "defsrc")   *> (KDefSrc   <$> defsrcP)
  , try (symbol "deflayer") *> (KDefLayer <$> deflayerP)
  , try (symbol "defalias") *> (KDefAlias <$> defaliasP)
  ]
shiftedNames :: [(Text, DefButton)]
shiftedNames = let f = second $ \kc -> KAround (KEmit KeyLeftShift) (KEmit kc) in
                 map f $ cps <> num <> oth
  where
    cps = zip (map T.singleton ['A'..'Z'])
          [ KeyA, KeyB, KeyC, KeyD, KeyE, KeyF, KeyG, KeyH, KeyI, KeyJ, KeyK, KeyL, KeyM,
            KeyN, KeyO, KeyP, KeyQ, KeyR, KeyS, KeyT, KeyU, KeyV, KeyW, KeyX, KeyY, KeyZ ]
    num = zip (map T.singleton "!@#$%^&*")
          [ Key1, Key2, Key3, Key4, Key5, Key6, Key7, Key8 ]
    oth = zip (map T.singleton "<>:~\"|{}+?")
          [ KeyComma, KeyDot, KeySemicolon, KeyGrave, KeyApostrophe, KeyBackslash
          , KeyLeftBrace, KeyRightBrace, KeyEqual, KeySlash]
buttonNames :: [(Text, DefButton)]
buttonNames = shiftedNames <> escp <> util
  where
    emitS c = KAround (KEmit KeyLeftShift) (KEmit c)
    
    escp = [ ("\\(", emitS Key9), ("\\)", emitS Key0)
           , ("\\_", emitS KeyMinus), ("\\\\", KEmit KeyBackslash)]
    
    util = [ ("_", KTrans), ("XX", KBlock)
           , ("lprn", emitS Key9), ("rprn", emitS Key0)]
moddedP :: Parser DefButton
moddedP = KAround <$> prfx <*> buttonP
  where mods = [ ("S-", KeyLeftShift), ("C-", KeyLeftCtrl)
               , ("A-", KeyLeftAlt),   ("M-", KeyLeftMeta)
               , ("RS-", KeyRightShift), ("RC-", KeyRightCtrl)
               , ("RA-", KeyRightAlt),   ("RM-", KeyRightMeta)]
        prfx = choice $ map (\(t, p) -> prefix (string t) *> pure (KEmit p)) mods
pauseP :: Parser DefButton
pauseP = KPause . fromIntegral <$> (char 'P' *> numP)
rmTapMacroP :: Parser DefButton
rmTapMacroP = KTapMacro <$> (char '#' *> paren (some buttonP))
composeSeqP :: Parser [DefButton]
composeSeqP = do
  
  c <- anySingle <?> "special character"
  s <- case find (\(_, c', _) -> (c' == c)) ssComposed of
         Nothing -> fail "Unrecognized compose-char"
         Just b  -> pure $ b^._1
  
  case runParser (some buttonP) "" s of
    Left  _ -> fail "Could not parse compose sequence"
    Right b -> pure b
deadkeySeqP :: Parser [DefButton]
deadkeySeqP = do
  _ <- prefix (char '+')
  c <- satisfy (`elem` ("~'^`\"" :: String))
  case runParser buttonP "" (T.singleton c) of
    Left  _ -> fail "Could not parse deadkey sequence"
    Right b -> pure [b]
buttonP :: Parser DefButton
buttonP = (lexeme . choice . map try $
  [ statement "around"         $ KAround      <$> buttonP     <*> buttonP
  , statement "multi-tap"      $ KMultiTap    <$> timed       <*> buttonP
  , statement "tap-hold"       $ KTapHold     <$> lexeme numP <*> buttonP <*> buttonP
  , statement "tap-hold-next"  $ KTapHoldNext <$> lexeme numP <*> buttonP <*> buttonP
  , statement "tap-next-release"
    $ KTapNextRelease <$> buttonP <*> buttonP
  , statement "tap-hold-next-release"
    $ KTapHoldNextRelease <$> lexeme numP <*> buttonP <*> buttonP
  , statement "tap-next"       $ KTapNext     <$> buttonP     <*> buttonP
  , statement "layer-toggle"   $ KLayerToggle <$> word
  , statement "layer-switch"   $ KLayerSwitch <$> word
  , statement "layer-add"      $ KLayerAdd    <$> word
  , statement "layer-rem"      $ KLayerRem    <$> word
  , statement "layer-delay"    $ KLayerDelay  <$> lexeme numP <*> word
  , statement "layer-next"     $ KLayerNext   <$> word
  , statement "around-next"    $ KAroundNext  <$> buttonP
  , statement "tap-macro"      $ KTapMacro    <$> some buttonP
  , statement "cmd-button"     $ KCommand     <$> textP
  , statement "pause"          $ KPause . fromIntegral <$> numP
  , KComposeSeq <$> deadkeySeqP
  , KRef  <$> derefP
  , lexeme $ fromNamed buttonNames
  , try moddedP
  , lexeme $ try rmTapMacroP
  , lexeme $ try pauseP
  , KEmit <$> keycodeP
  , KComposeSeq <$> composeSeqP
  ]) <?> "button"
  where
    timed = many ((,) <$> lexeme numP <*> lexeme buttonP)
itokenP :: Parser IToken
itokenP = choice . map try $
  [ statement "device-file"    $ KDeviceSource <$> (T.unpack <$> textP)
  , statement "low-level-hook" $ pure KLowLevelHookSource
  , statement "iokit-name"     $ KIOKitSource <$> optional textP]
otokenP :: Parser OToken
otokenP = choice . map try $
  [ statement "uinput-sink"     $ KUinputSink <$> lexeme textP <*> optional textP
  , statement "send-event-sink" $ pure KSendEventSink
  , statement "kext"            $ pure KKextSink]
defcfgP :: Parser DefSettings
defcfgP = some (lexeme settingP)
settingP :: Parser DefSetting
settingP = let f s p = symbol s *> p in
  (lexeme . choice . map try $
    [ SIToken      <$> f "input"       itokenP
    , SOToken      <$> f "output"      otokenP
    , SCmpSeq      <$> f "cmp-seq"     buttonP
    , SInitStr     <$> f "init"        textP
    , SFallThrough <$> f "fallthrough" bool
    , SAllowCmd    <$> f "allow-cmd"   bool
    ])
defaliasP :: Parser DefAlias
defaliasP = many $ (,) <$> lexeme word <*> buttonP
defsrcP :: Parser DefSrc
defsrcP = many $ lexeme keycodeP
deflayerP :: Parser DefLayer
deflayerP = DefLayer <$> lexeme word <*> many (lexeme buttonP)