From 7674145b878fd315999558075edcfc5e09bdd91c Mon Sep 17 00:00:00 2001 From: jao Date: Wed, 21 Nov 2018 23:47:36 +0000 Subject: Configuration file parsing moved to app module --- app/Configuration.hs | 158 ++++++++++++++++++++++++++++++++++++++++++++++++++ app/Main.hs | 4 +- src/Xmobar/Parsers.hs | 136 +------------------------------------------ xmobar.cabal | 5 +- 4 files changed, 165 insertions(+), 138 deletions(-) create mode 100644 app/Configuration.hs diff --git a/app/Configuration.hs b/app/Configuration.hs new file mode 100644 index 0000000..db5c109 --- /dev/null +++ b/app/Configuration.hs @@ -0,0 +1,158 @@ +{-# LANGUAGE FlexibleContexts #-} + +------------------------------------------------------------------------------ +-- | +-- Module: Configuration +-- Copyright: (c) 2018 Jose Antonio Ortega Ruiz +-- License: BSD3-style (see LICENSE) +-- +-- Maintainer: jao@gnu.org +-- Stability: unstable +-- Portability: portable +-- Created: Wed Nov 21, 2018 23:13 +-- +-- +-- Parsing configuration files +-- +------------------------------------------------------------------------------ + + +module Configuration (parseConfig) where + +import Text.ParserCombinators.Parsec +import Text.ParserCombinators.Parsec.Number (int) +import Text.ParserCombinators.Parsec.Perm ((<|?>), (<$?>), permute) + +import qualified Xmobar.Config as C + +stripComments :: String -> String +stripComments = + unlines . map (drop 5 . strip False . (replicate 5 ' '++)) . lines + where strip m ('-':'-':xs) = if m then "--" ++ strip m xs else "" + strip m ('"':xs) = '"': strip (not m) xs + strip m (x:xs) = x : strip m xs + strip _ [] = [] + +-- | Parse the config, logging a list of fields that were missing and replaced +-- by the default definition. +parseConfig :: String -> Either ParseError (C.Config,[String]) +parseConfig = runParser parseConf fields "Config" . stripComments + where + parseConf = do + many space + sepEndSpc ["Config","{"] + x <- perms + eof + s <- getState + return (x,s) + + perms = permute $ C.Config + <$?> pFont <|?> pFontList <|?> pWmClass <|?> pWmName + <|?> pBgColor <|?> pFgColor + <|?> pPosition <|?> pTextOffset <|?> pTextOffsets + <|?> pIconOffset <|?> pBorder + <|?> pBdColor <|?> pBdWidth <|?> pAlpha <|?> pHideOnStart + <|?> pAllDesktops <|?> pOverrideRedirect <|?> pPickBroadest + <|?> pLowerOnStart <|?> pPersistent <|?> pIconRoot + <|?> pCommands <|?> pSepChar <|?> pAlignSep <|?> pTemplate + + + fields = [ "font", "additionalFonts","bgColor", "fgColor" + , "wmClass", "wmName", "sepChar" + , "alignSep" , "border", "borderColor" ,"template" + , "position" , "textOffset", "textOffsets", "iconOffset" + , "allDesktops", "overrideRedirect", "pickBroadest" + , "hideOnStart", "lowerOnStart", "persistent", "iconRoot" + , "alpha", "commands" + ] + + pFont = strField C.font "font" + pFontList = strListField C.additionalFonts "additionalFonts" + pWmClass = strField C.wmClass "wmClass" + pWmName = strField C.wmName "wmName" + pBgColor = strField C.bgColor "bgColor" + pFgColor = strField C.fgColor "fgColor" + pBdColor = strField C.borderColor "borderColor" + pSepChar = strField C.sepChar "sepChar" + pAlignSep = strField C.alignSep "alignSep" + pTemplate = strField C.template "template" + + pTextOffset = readField C.textOffset "textOffset" + pTextOffsets = readIntList C.textOffsets "textOffsets" + pIconOffset = readField C.iconOffset "iconOffset" + pPosition = readField C.position "position" + pHideOnStart = readField C.hideOnStart "hideOnStart" + pLowerOnStart = readField C.lowerOnStart "lowerOnStart" + pPersistent = readField C.persistent "persistent" + pBorder = readField C.border "border" + pBdWidth = readField C.borderWidth "borderWidth" + pAllDesktops = readField C.allDesktops "allDesktops" + pOverrideRedirect = readField C.overrideRedirect "overrideRedirect" + pPickBroadest = readField C.pickBroadest "pickBroadest" + pIconRoot = readField C.iconRoot "iconRoot" + pAlpha = readField C.alpha "alpha" + + pCommands = field C.commands "commands" readCommands + + staticPos = do string "Static" + wrapSkip (string "{") + p <- many (noneOf "}") + wrapSkip (string "}") + string "," + return ("Static {" ++ p ++ "}") + tillFieldEnd = staticPos <|> many (noneOf ",}\n\r") + + commandsEnd = wrapSkip (string "]") >> (string "}" <|> notNextRun) + notNextRun = do {string "," + ; notFollowedBy $ wrapSkip $ string "Run" + ; return "," + } + readCommands = manyTill anyChar (try commandsEnd) >>= + read' commandsErr . flip (++) "]" + strField e n = field e n strMulti + + strMulti = scan '"' + where + scan lead = do + spaces + char lead + s <- manyTill anyChar (rowCont <|> unescQuote) + (char '"' >> return s) <|> fmap (s ++) (scan '\\') + rowCont = try $ char '\\' >> string "\n" + unescQuote = lookAhead (noneOf "\\") >> lookAhead (string "\"") + + strListField e n = field e n strList + strList = do + spaces + char '[' + list <- sepBy (strMulti >>= \x -> spaces >> return x) (char ',') + spaces + char ']' + return list + + wrapSkip x = many space >> x >>= \r -> many space >> return r + sepEndSpc = mapM_ (wrapSkip . try . string) + fieldEnd = many $ space <|> oneOf ",}" + field e n c = (,) (e C.defaultConfig) $ + updateState (filter (/= n)) >> sepEndSpc [n,"="] >> + wrapSkip c >>= \r -> fieldEnd >> return r + readField a n = field a n $ tillFieldEnd >>= read' n + + readIntList d n = field d n intList + intList = do + spaces + char '[' + list <- sepBy (spaces >> int >>= \x-> spaces >> return x) (char ',') + spaces + char ']' + return list + + read' d s = case reads s of + [(x, _)] -> return x + _ -> fail $ "error reading the " ++ d ++ " field: " ++ s + +commandsErr :: String +commandsErr = "commands: this usually means that a command could not" ++ + "\nbe parsed." ++ + "\nThe error could be located at the begining of the command" ++ + "\nwhich follows the offending one." diff --git a/app/Main.hs b/app/Main.hs index 646ae11..c96c47e 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -29,7 +29,6 @@ import Data.Foldable (for_) import Data.List (intercalate) import qualified Data.Map as Map -import Paths_xmobar (version) import Data.Version (showVersion) import Graphics.X11.Xlib import System.Console.GetOpt @@ -45,6 +44,9 @@ import Text.Read (readMaybe) import Xmobar.Signal (setupSignalHandler, withDeferSignals) +import Paths_xmobar (version) +import Configuration + -- $main -- | The main entry point diff --git a/src/Xmobar/Parsers.hs b/src/Xmobar/Parsers.hs index d76f8f7..33afd09 100644 --- a/src/Xmobar/Parsers.hs +++ b/src/Xmobar/Parsers.hs @@ -1,4 +1,5 @@ {-# LANGUAGE FlexibleContexts #-} + ----------------------------------------------------------------------------- -- | -- Module : Xmobar.Parsers @@ -16,7 +17,6 @@ module Xmobar.Parsers ( parseString , parseTemplate - , parseConfig , Widget(..) ) where @@ -28,8 +28,6 @@ import Xmobar.Actions import Control.Monad (guard, mzero) import qualified Data.Map as Map import Text.ParserCombinators.Parsec -import Text.ParserCombinators.Parsec.Number (int) -import Text.ParserCombinators.Parsec.Perm import Graphics.X11.Types (Button) data Widget = Icon String | Text String @@ -190,135 +188,3 @@ combine c m ((ts,s,ss):xs) = (com, s, ss) : combine c m xs allTillSep :: Config -> Parser String allTillSep = many . noneOf . sepChar - -stripComments :: String -> String -stripComments = - unlines . map (drop 5 . strip False . (replicate 5 ' '++)) . lines - where strip m ('-':'-':xs) = if m then "--" ++ strip m xs else "" - strip m ('"':xs) = '"': strip (not m) xs - strip m (x:xs) = x : strip m xs - strip _ [] = [] - --- | Parse the config, logging a list of fields that were missing and replaced --- by the default definition. -parseConfig :: String -> Either ParseError (Config,[String]) -parseConfig = runParser parseConf fields "Config" . stripComments - where - parseConf = do - many space - sepEndSpc ["Config","{"] - x <- perms - eof - s <- getState - return (x,s) - - perms = permute $ Config - <$?> pFont <|?> pFontList <|?> pWmClass <|?> pWmName - <|?> pBgColor <|?> pFgColor - <|?> pPosition <|?> pTextOffset <|?> pTextOffsets - <|?> pIconOffset <|?> pBorder - <|?> pBdColor <|?> pBdWidth <|?> pAlpha <|?> pHideOnStart - <|?> pAllDesktops <|?> pOverrideRedirect <|?> pPickBroadest - <|?> pLowerOnStart <|?> pPersistent <|?> pIconRoot - <|?> pCommands <|?> pSepChar <|?> pAlignSep <|?> pTemplate - - - fields = [ "font", "additionalFonts","bgColor", "fgColor" - , "wmClass", "wmName", "sepChar" - , "alignSep" , "border", "borderColor" ,"template" - , "position" , "textOffset", "textOffsets", "iconOffset" - , "allDesktops", "overrideRedirect", "pickBroadest" - , "hideOnStart", "lowerOnStart", "persistent", "iconRoot" - , "alpha", "commands" - ] - - pFont = strField font "font" - pFontList = strListField additionalFonts "additionalFonts" - pWmClass = strField wmClass "wmClass" - pWmName = strField wmName "wmName" - pBgColor = strField bgColor "bgColor" - pFgColor = strField fgColor "fgColor" - pBdColor = strField borderColor "borderColor" - pSepChar = strField sepChar "sepChar" - pAlignSep = strField alignSep "alignSep" - pTemplate = strField template "template" - - pTextOffset = readField textOffset "textOffset" - pTextOffsets = readIntList textOffsets "textOffsets" - pIconOffset = readField iconOffset "iconOffset" - pPosition = readField position "position" - pHideOnStart = readField hideOnStart "hideOnStart" - pLowerOnStart = readField lowerOnStart "lowerOnStart" - pPersistent = readField persistent "persistent" - pBorder = readField border "border" - pBdWidth = readField borderWidth "borderWidth" - pAllDesktops = readField allDesktops "allDesktops" - pOverrideRedirect = readField overrideRedirect "overrideRedirect" - pPickBroadest = readField pickBroadest "pickBroadest" - pIconRoot = readField iconRoot "iconRoot" - pAlpha = readField alpha "alpha" - - pCommands = field commands "commands" readCommands - - staticPos = do string "Static" - wrapSkip (string "{") - p <- many (noneOf "}") - wrapSkip (string "}") - string "," - return ("Static {" ++ p ++ "}") - tillFieldEnd = staticPos <|> many (noneOf ",}\n\r") - - commandsEnd = wrapSkip (string "]") >> (string "}" <|> notNextRun) - notNextRun = do {string "," - ; notFollowedBy $ wrapSkip $ string "Run" - ; return "," - } - readCommands = manyTill anyChar (try commandsEnd) >>= - read' commandsErr . flip (++) "]" - strField e n = field e n strMulti - - strMulti = scan '"' - where - scan lead = do - spaces - char lead - s <- manyTill anyChar (rowCont <|> unescQuote) - (char '"' >> return s) <|> fmap (s ++) (scan '\\') - rowCont = try $ char '\\' >> string "\n" - unescQuote = lookAhead (noneOf "\\") >> lookAhead (string "\"") - - strListField e n = field e n strList - strList = do - spaces - char '[' - list <- sepBy (strMulti >>= \x -> spaces >> return x) (char ',') - spaces - char ']' - return list - - wrapSkip x = many space >> x >>= \r -> many space >> return r - sepEndSpc = mapM_ (wrapSkip . try . string) - fieldEnd = many $ space <|> oneOf ",}" - field e n c = (,) (e defaultConfig) $ - updateState (filter (/= n)) >> sepEndSpc [n,"="] >> - wrapSkip c >>= \r -> fieldEnd >> return r - readField a n = field a n $ tillFieldEnd >>= read' n - - readIntList d n = field d n intList - intList = do - spaces - char '[' - list <- sepBy (spaces >> int >>= \x-> spaces >> return x) (char ',') - spaces - char ']' - return list - - read' d s = case reads s of - [(x, _)] -> return x - _ -> fail $ "error reading the " ++ d ++ " field: " ++ s - -commandsErr :: String -commandsErr = "commands: this usually means that a command could not" ++ - "\nbe parsed." ++ - "\nThe error could be located at the begining of the command" ++ - "\nwhich follows the offending one." diff --git a/xmobar.cabal b/xmobar.cabal index ecd0f4b..89f7997 100644 --- a/xmobar.cabal +++ b/xmobar.cabal @@ -158,7 +158,6 @@ library X11 >= 1.6.1, mtl >= 2.1 && < 2.3, parsec == 3.1.*, - parsec-numbers >= 0.1.0, stm >= 2.3 && < 2.6, async @@ -246,7 +245,7 @@ library executable xmobar hs-source-dirs: app main-is: Main.hs - other-modules: Paths_xmobar + other-modules: Paths_xmobar, Configuration build-depends: base, containers, async, @@ -254,6 +253,8 @@ executable xmobar directory, filepath, unix, + parsec, + parsec-numbers >= 0.1.0, xmobar ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind -- cgit v1.2.3