module Graphics.Vty.Config where
import Prelude hiding (catch)
import Control.Applicative hiding (many)
import Control.Exception (tryJust, catch, IOException)
import Control.Monad (void, guard)
import Control.Monad.Trans.Class
import Control.Monad.Trans.Writer
import qualified Data.ByteString as BS
import Data.Default
import Data.Monoid
import Graphics.Vty.Input.Events
import System.Directory (getAppUserDataDirectory)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)
import Text.Parsec hiding ((<|>))
import Text.Parsec.Token ( GenLanguageDef(..) )
import qualified Text.Parsec.Token as P
type InputMap = [(Maybe String, String, Event)]
data Config = Config
    { specifiedEscPeriod :: Maybe Int            
    
    , debugLog           :: Maybe FilePath
    
    
    
    
    , inputMap           :: InputMap
    } deriving (Show, Eq)
singleEscPeriod :: Config -> Int
singleEscPeriod = maybe 100000 id . specifiedEscPeriod
instance Default Config where
    def = mempty
instance Monoid Config where
    mempty = Config
        { specifiedEscPeriod = Nothing
        , debugLog           = mempty
        , inputMap           = mempty
        }
    mappend c0 c1 = Config
        
        { specifiedEscPeriod = specifiedEscPeriod c1 <|> specifiedEscPeriod c0
        
        , debugLog           = debugLog c1           <|> debugLog c0
        , inputMap           = inputMap c0           <>  inputMap c1
        }
type ConfigParser s a = ParsecT s () (Writer Config) a
userConfig :: IO Config
userConfig = do
    configFile <- (mappend <$> getAppUserDataDirectory "vty" <*> pure "/config") >>= parseConfigFile
    let maybeEnv = tryJust (guard . isDoesNotExistError) . getEnv
    overridePath <- maybeEnv "VTY_CONFIG_FILE"
    overrideConfig <- either (const $ return def) parseConfigFile overridePath
    debugLogPath <- maybeEnv "VTY_DEBUG_LOG"
    let debugLogConfig = either (const def) (\p -> def { debugLog = Just p }) debugLogPath
    return $ mconcat [configFile, overrideConfig, debugLogConfig]
parseConfigFile :: FilePath -> IO Config
parseConfigFile path = do
    catch (runParseConfig path <$> BS.readFile path)
          (\(_ :: IOException) -> return def)
runParseConfig :: Stream s (Writer Config) Char => String -> s -> Config
runParseConfig name = execWriter . runParserT parseConfig () name
configLanguage :: Stream s m Char => P.GenLanguageDef s u m
configLanguage = LanguageDef
    { commentStart = "{-"
    , commentEnd = "-}"
    , commentLine = "--"
    , nestedComments = True
    , identStart = letter <|> char '_'
    , identLetter = alphaNum <|> oneOf "_'"
    , opStart = opLetter configLanguage
    , opLetter = oneOf ":!#$%&*+./<=>?@\\^|-~"
    , reservedOpNames = []
    , reservedNames = []
    , caseSensitive = True
    }
configLexer :: Stream s m Char => P.GenTokenParser s u m
configLexer = P.makeTokenParser configLanguage
mapDecl = do
    void $ string "map"
    P.whiteSpace configLexer
    termIdent <- (char '_' >> P.whiteSpace configLexer >> return Nothing)
             <|> (Just <$> P.stringLiteral configLexer)
    bytes <- P.stringLiteral configLexer
    key <- parseKey
    modifiers <- parseModifiers
    lift $ tell $ def { inputMap = [(termIdent, bytes, EvKey key modifiers)] }
parseKey = do
    key <- P.identifier configLexer
    case key of
     "KChar" -> KChar <$> P.charLiteral configLexer
     "KFun" -> KFun . fromInteger <$> P.natural configLexer
     "KEsc" -> return KEsc
     "KBS" -> return KBS
     "KEnter" -> return KEnter
     "KLeft" -> return KLeft
     "KRight" -> return KRight
     "KUp" -> return KUp
     "KDown" -> return KDown
     "KUpLeft" -> return KUpLeft
     "KUpRight" -> return KUpRight
     "KDownLeft" -> return KDownLeft
     "KDownRight" -> return KDownRight
     "KCenter" -> return KCenter
     "KBackTab" -> return KBackTab
     "KPrtScr" -> return KPrtScr
     "KPause" -> return KPause
     "KIns" -> return KIns
     "KHome" -> return KHome
     "KPageUp" -> return KPageUp
     "KDel" -> return KDel
     "KEnd" -> return KEnd
     "KPageDown" -> return KPageDown
     "KBegin" -> return KBegin
     "KMenu" -> return KMenu
     _ -> fail $ key ++ " is not a valid key identifier"
parseModifiers = P.brackets configLexer (parseModifier `sepBy` P.symbol configLexer ",")
parseModifier = do
    m <- P.identifier configLexer
    case m of
        "KMenu" -> return MShift
        "MCtrl" -> return MCtrl
        "MMeta" -> return MMeta
        "MAlt" -> return MAlt
        _ -> fail $ m ++ " is not a valid modifier identifier"
debugLogDecl = do
    void $ string "debugLog"
    P.whiteSpace configLexer
    path <- P.stringLiteral configLexer
    lift $ tell $ def { debugLog = Just path }
ignoreLine = void $ manyTill anyChar newline
parseConfig = void $ many $ do
    P.whiteSpace configLexer
    let directives = [mapDecl, debugLogDecl]
    try (choice directives) <|> ignoreLine