diff options
| author | Unoqwy <julien.qwy@gmail.com> | 2020-07-24 10:22:49 +0200 | 
|---|---|---|
| committer | Unoqwy <julien.qwy@gmail.com> | 2020-08-07 19:49:33 +0200 | 
| commit | afc7a9eff0c3b65b0df83e05dd90d2c2c8202a6c (patch) | |
| tree | d38323ae0487e92521fe6c4f3bc7ec943ed6211a | |
| parent | 43d1dc71f9900986168458d3af281453f41df966 (diff) | |
| download | xmobar-afc7a9eff0c3b65b0df83e05dd90d2c2c8202a6c.tar.gz xmobar-afc7a9eff0c3b65b0df83e05dd90d2c2c8202a6c.tar.bz2 | |
Refactor ColorInfo to TextRenderInfo
ColorInfo contains background offsets, it is no longer only about colors
TextRenderInfo can hold information such as color, offsets, etc
| -rw-r--r-- | src/Xmobar/App/EventLoop.hs | 6 | ||||
| -rw-r--r-- | src/Xmobar/X11/Bitmap.hs | 4 | ||||
| -rw-r--r-- | src/Xmobar/X11/Draw.hs | 10 | ||||
| -rw-r--r-- | src/Xmobar/X11/Parsers.hs | 50 | 
4 files changed, 35 insertions, 35 deletions
| diff --git a/src/Xmobar/App/EventLoop.hs b/src/Xmobar/App/EventLoop.hs index 2b33768..1c77ac1 100644 --- a/src/Xmobar/App/EventLoop.hs +++ b/src/Xmobar/App/EventLoop.hs @@ -250,17 +250,17 @@ startCommand sig (com,s,ss)      where is = s ++ "Updating..." ++ ss  updateString :: Config -> TVar [String] -                -> IO [[(Widget, ColorInfo, Int, Maybe [Action])]] +                -> IO [[(Widget, TextRenderInfo, Int, Maybe [Action])]]  updateString conf v = do    s <- readTVarIO v    let l:c:r:_ = s ++ repeat ""    liftIO $ mapM (parseString conf) [l, c, r] -updateActions :: XConf -> Rectangle -> [[(Widget, ColorInfo, Int, Maybe [Action])]] +updateActions :: XConf -> Rectangle -> [[(Widget, TextRenderInfo, Int, Maybe [Action])]]                   -> IO [([Action], Position, Position)]  updateActions conf (Rectangle _ _ wid _) ~[left,center,right] = do    let (d,fs) = (display &&& fontListS) conf -      strLn :: [(Widget, ColorInfo, Int, Maybe [Action])] -> IO [(Maybe [Action], Position, Position)] +      strLn :: [(Widget, TextRenderInfo, Int, Maybe [Action])] -> IO [(Maybe [Action], Position, Position)]        strLn  = liftIO . mapM getCoords        iconW i = maybe 0 Bitmap.width (lookup i $ iconS conf)        getCoords (Text s,_,i,a) = textWidth d (safeIndex fs i) s >>= \tw -> return (a, 0, fi tw) diff --git a/src/Xmobar/X11/Bitmap.hs b/src/Xmobar/X11/Bitmap.hs index e764384..c17f9d2 100644 --- a/src/Xmobar/X11/Bitmap.hs +++ b/src/Xmobar/X11/Bitmap.hs @@ -24,7 +24,7 @@ import System.Directory (doesFileExist)  import System.FilePath ((</>))  import System.Mem.Weak ( addFinalizer )  import Xmobar.X11.ColorCache -import Xmobar.X11.Parsers (ColorInfo(..), Widget(..)) +import Xmobar.X11.Parsers (TextRenderInfo(..), Widget(..))  import Xmobar.X11.Actions (Action)  #ifdef XPM @@ -54,7 +54,7 @@ data Bitmap = Bitmap { width  :: Dimension                       }  updateCache :: Display -> Window -> Map FilePath Bitmap -> FilePath -> -               [[(Widget, ColorInfo, Int, Maybe [Action])]] -> IO (Map FilePath Bitmap) +               [[(Widget, TextRenderInfo, Int, Maybe [Action])]] -> IO (Map FilePath Bitmap)  updateCache dpy win cache iconRoot ps = do    let paths = map (\(Icon p, _, _, _) -> p) . concatMap (filter icons) $ ps        icons (Icon _, _, _, _) = True diff --git a/src/Xmobar/X11/Draw.hs b/src/Xmobar/X11/Draw.hs index 003f579..cd74872 100644 --- a/src/Xmobar/X11/Draw.hs +++ b/src/Xmobar/X11/Draw.hs @@ -36,7 +36,7 @@ import Xmobar.X11.Types  import Xmobar.X11.Text  import Xmobar.X11.ColorCache  import Xmobar.X11.Window (drawBorder) -import Xmobar.X11.Parsers (ColorInfo(..), Widget(..)) +import Xmobar.X11.Parsers (TextRenderInfo(..), Widget(..))  import Xmobar.System.Utils (safeIndex)  #ifdef XFT @@ -48,7 +48,7 @@ fi :: (Integral a, Num b) => a -> b  fi = fromIntegral  -- | Draws in and updates the window -drawInWin :: Rectangle -> [[(Widget, ColorInfo, Int, Maybe [Action])]] -> X () +drawInWin :: Rectangle -> [[(Widget, TextRenderInfo, Int, Maybe [Action])]] -> X ()  drawInWin wr@(Rectangle _ _ wid ht) ~[left,center,right] = do    r <- ask    let (c,d) = (config &&& display) r @@ -130,7 +130,7 @@ printString dpy drw fs@(Xft fonts) _ fc bc x y ay ht s al =  -- | An easy way to print the stuff we need to print  printStrings :: Drawable -> GC -> NE.NonEmpty XFont -> [Int] -> Position -             -> Align -> [(Widget, ColorInfo, Int, Position)] -> X () +             -> Align -> [(Widget, TextRenderInfo, Int, Position)] -> X ()  printStrings _ _ _ _ _ _ [] = return ()  printStrings dr gc fontlist voffs offs a sl@((s,c,i,l):xs) = do    r <- ask @@ -144,11 +144,11 @@ printStrings dr gc fontlist voffs offs a sl@((s,c,i,l):xs) = do                   C -> (remWidth + offs) `div` 2                   R -> remWidth                   L -> offs -      (fc,bc) = case break (==',') (colorsString c) of +      (fc,bc) = case break (==',') (tColorsString c) of                   (f,',':b) -> (f, b           )                   (f,    _) -> (f, bgColor conf)    valign <- verticalOffset ht s (NE.head fontlist) (voffs !! i) conf -  let (ht',ay) = case (bgTopOffset c, bgBottomOffset c) of +  let (ht',ay) = case (tBgTopOffset c, tBgBottomOffset c) of                     (-1,_)  -> (0, -1)                     (_,-1)  -> (0, -1)                     (ot,ob) -> ((fromIntegral ht) - ot - ob, ob) diff --git a/src/Xmobar/X11/Parsers.hs b/src/Xmobar/X11/Parsers.hs index 175de8c..fded3b3 100644 --- a/src/Xmobar/X11/Parsers.hs +++ b/src/Xmobar/X11/Parsers.hs @@ -14,7 +14,7 @@  --  ----------------------------------------------------------------------------- -module Xmobar.X11.Parsers (parseString, ColorInfo(..), Widget(..)) where +module Xmobar.X11.Parsers (parseString, TextRenderInfo(..), Widget(..)) where  import Xmobar.Config.Types  import Xmobar.X11.Actions @@ -28,17 +28,17 @@ import Graphics.X11.Types (Button)  data Widget = Icon String | Text String -type AbsBgOffset = Int32 -data ColorInfo   = -       ColorInfo { colorsString   :: String -                 , bgTopOffset    :: AbsBgOffset -                 , bgBottomOffset :: AbsBgOffset -                 } deriving Show +type AbsBgOffset    = Int32 +data TextRenderInfo = +     TextRenderInfo { tColorsString   :: String +                    , tBgTopOffset    :: AbsBgOffset +                    , tBgBottomOffset :: AbsBgOffset +                    } deriving Show  type FontIndex   = Int  -- | Runs the string parser  parseString :: Config -> String -               -> IO [(Widget, ColorInfo, FontIndex, Maybe [Action])] +               -> IO [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  parseString c s =      case parse (stringParser ci 0 Nothing) "" s of        Left  _ -> return [(Text $ "Could not parse string: " ++ s @@ -46,12 +46,12 @@ parseString c s =                            , 0                            , Nothing)]        Right x -> return (concat x) -    where ci = ColorInfo (fgColor c) 0 0 +    where ci = TextRenderInfo (fgColor c) 0 0 -allParsers :: ColorInfo +allParsers :: TextRenderInfo             -> FontIndex             -> Maybe [Action] -           -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +           -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  allParsers c f a =  textParser c f a                  <|> try (iconParser c f a)                  <|> try (rawParser c f a) @@ -60,13 +60,13 @@ allParsers c f a =  textParser c f a                  <|> colorParser f a  -- | Gets the string and combines the needed parsers -stringParser :: ColorInfo -> FontIndex -> Maybe [Action] -                -> Parser [[(Widget, ColorInfo, FontIndex, Maybe [Action])]] +stringParser :: TextRenderInfo -> FontIndex -> Maybe [Action] +                -> Parser [[(Widget, TextRenderInfo, FontIndex, Maybe [Action])]]  stringParser c f a = manyTill (allParsers c f a) eof  -- | Parses a maximal string without markup. -textParser :: ColorInfo -> FontIndex -> Maybe [Action] -              -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +textParser :: TextRenderInfo -> FontIndex -> Maybe [Action] +              -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  textParser c f a = do s <- many1 $                              noneOf "<" <|>                                try (notFollowedBy' (char '<') @@ -85,10 +85,10 @@ textParser c f a = do s <- many1 $  -- string of digits (base 10) denoting the length of the raw string,  -- a literal ":" as digit-string-terminator, the raw string itself, and  -- then a literal "/>". -rawParser :: ColorInfo +rawParser :: TextRenderInfo            -> FontIndex            -> Maybe [Action] -          -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +          -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  rawParser c f a = do    string "<raw="    lenstr <- many1 digit @@ -109,15 +109,15 @@ notFollowedBy' p e = do x <- p                          notFollowedBy $ try (e >> return '*')                          return x -iconParser :: ColorInfo -> FontIndex -> Maybe [Action] -              -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +iconParser :: TextRenderInfo -> FontIndex -> Maybe [Action] +              -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  iconParser c f a = do    string "<icon="    i <- manyTill (noneOf ">") (try (string "/>"))    return [(Icon i, c, f, a)] -actionParser :: ColorInfo -> FontIndex -> Maybe [Action] -                -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +actionParser :: TextRenderInfo -> FontIndex -> Maybe [Action] +                -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  actionParser c f act = do    string "<action="    command <- choice [between (char '`') (char '`') (many1 (noneOf "`")), @@ -136,7 +136,7 @@ toButtons = map (\x -> read [x])  -- | Parsers a string wrapped in a color specification.  colorParser :: FontIndex -> Maybe [Action] -               -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +               -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  colorParser f a = do    c <- between (string "<fc=") (string ">") colors    let colorParts = break (==':') c @@ -144,13 +144,13 @@ colorParser f a = do               (top,',':btm) -> (top, btm)               (top,      _) -> (top, top)    s <- manyTill -       (allParsers (ColorInfo (fst colorParts) (fromMaybe (-1) $ readMaybe ot) (fromMaybe (-1) $ readMaybe ob)) f a) +       (allParsers (TextRenderInfo (fst colorParts) (fromMaybe (-1) $ readMaybe ot) (fromMaybe (-1) $ readMaybe ob)) f a)         (try $ string "</fc>")    return (concat s)  -- | Parsers a string wrapped in a font specification. -fontParser :: ColorInfo -> Maybe [Action] -              -> Parser [(Widget, ColorInfo, FontIndex, Maybe [Action])] +fontParser :: TextRenderInfo -> Maybe [Action] +              -> Parser [(Widget, TextRenderInfo, FontIndex, Maybe [Action])]  fontParser c a = do    f <- between (string "<fn=") (string ">") colors    s <- manyTill (allParsers c (fromMaybe 0 $ readMaybe f) a) (try $ string "</fn>") | 
