diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/lib/Xmobar.hs | 13 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/Bitmap.hs (renamed from src/lib/Xmobar/Bitmap.hs) | 6 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/ColorCache.hs (renamed from src/lib/Xmobar/ColorCache.hs) | 6 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/Draw.hs (renamed from src/lib/Xmobar/Draw.hs) | 44 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/EventLoop.hs (renamed from src/lib/Xmobar/EventLoop.hs) | 17 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/MinXft.hsc (renamed from src/lib/Xmobar/MinXft.hsc) | 2 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/Types.hs (renamed from src/lib/Xmobar/Types.hs) | 13 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/Window.hs (renamed from src/lib/Xmobar/Window.hs) | 4 | ||||
| -rw-r--r-- | src/lib/Xmobar/X11/XUtil.hs (renamed from src/lib/Xmobar/XUtil.hs) | 37 | 
9 files changed, 67 insertions, 75 deletions
| diff --git a/src/lib/Xmobar.hs b/src/lib/Xmobar.hs index 547c549..2b160a1 100644 --- a/src/lib/Xmobar.hs +++ b/src/lib/Xmobar.hs @@ -17,10 +17,6 @@  module Xmobar (xmobar, Runnable (..), module Xmobar.Config) where -import Xmobar.EventLoop (startLoop, startCommand) -import Xmobar.Config -import Xmobar.Runnable -  import Data.Foldable (for_)  import qualified Data.Map as Map @@ -28,11 +24,14 @@ import Graphics.X11.Xlib  import Control.Concurrent.Async (Async, cancel)  import Control.Exception (bracket) +import Xmobar.Config +import Xmobar.Runnable  import Xmobar.Parsers -import Xmobar.XUtil  import Xmobar.Signal (setupSignalHandler, withDeferSignals) -import Xmobar.Window -import Xmobar.Types +import Xmobar.X11.Types +import Xmobar.X11.EventLoop (startLoop, startCommand) +import Xmobar.X11.XUtil +import Xmobar.X11.Window  splitTemplate :: Config -> [String]  splitTemplate conf = diff --git a/src/lib/Xmobar/Bitmap.hs b/src/lib/Xmobar/X11/Bitmap.hs index 314ce02..7b7afeb 100644 --- a/src/lib/Xmobar/Bitmap.hs +++ b/src/lib/Xmobar/X11/Bitmap.hs @@ -1,7 +1,7 @@  {-# LANGUAGE CPP, FlexibleContexts #-}  -----------------------------------------------------------------------------  -- | --- Module      :  Bitmap +-- Module      :  X11.Bitmap  -- Copyright   :  (C) 2013, 2015, 2017, 2018 Alexander Polakov  -- License     :  BSD3  -- @@ -11,7 +11,7 @@  --  ----------------------------------------------------------------------------- -module Xmobar.Bitmap +module Xmobar.X11.Bitmap   ( updateCache   , drawBitmap   , Bitmap(..)) where @@ -23,7 +23,7 @@ import Graphics.X11.Xlib  import System.Directory (doesFileExist)  import System.FilePath ((</>))  import System.Mem.Weak ( addFinalizer ) -import Xmobar.ColorCache +import Xmobar.X11.ColorCache  import Xmobar.Parsers (Widget(..))  import Xmobar.Actions (Action) diff --git a/src/lib/Xmobar/ColorCache.hs b/src/lib/Xmobar/X11/ColorCache.hs index f17aa0d..c5e8823 100644 --- a/src/lib/Xmobar/ColorCache.hs +++ b/src/lib/Xmobar/X11/ColorCache.hs @@ -17,12 +17,12 @@  #if defined XFT -module Xmobar.ColorCache(withColors, withDrawingColors) where +module Xmobar.X11.ColorCache(withColors, withDrawingColors) where -import Xmobar.MinXft +import Xmobar.X11.MinXft  #else -module Xmobar.ColorCache(withColors) where +module Xmobar.X11., 2018ColorCache(withColors) where  #endif diff --git a/src/lib/Xmobar/Draw.hs b/src/lib/Xmobar/X11/Draw.hs index e63cd27..3fe6f5c 100644 --- a/src/lib/Xmobar/Draw.hs +++ b/src/lib/Xmobar/X11/Draw.hs @@ -2,7 +2,7 @@  ------------------------------------------------------------------------------  -- | --- Module: Xmobar.Draw +-- Module: Xmobar.X11.Draw  -- Copyright: (c) 2018 Jose Antonio Ortega Ruiz  -- License: BSD3-style (see LICENSE)  -- @@ -17,27 +17,30 @@  ------------------------------------------------------------------------------ -module Xmobar.Draw (drawInWin) where +module Xmobar.X11.Draw (drawInWin) where  import Prelude hiding (lookup)  import Control.Monad.IO.Class  import Control.Monad.Reader +import Control.Monad (when)  import Control.Arrow ((&&&))  import Data.Map hiding (foldr, map, filter)  import Graphics.X11.Xlib hiding (textExtents, textWidth) +import Graphics.X11.Xlib.Extras  import Xmobar.Parsers (Widget(..))  import Xmobar.Actions (Action(..)) -import qualified Xmobar.Bitmap as B -import Xmobar.Types -import Xmobar.XUtil +import qualified Xmobar.X11.Bitmap as B +import Xmobar.X11.Types +import Xmobar.X11.XUtil  import Xmobar.Config -import Xmobar.ColorCache -import Xmobar.Window (drawBorder) +import Xmobar.X11.ColorCache +import Xmobar.X11.Window (drawBorder)  #ifdef XFT -import Xmobar.MinXft (drawBackground) +import Xmobar.X11.MinXft +import Graphics.X11.Xrender  #endif  fi :: (Integral a, Num b) => a -> b @@ -95,6 +98,31 @@ verticalOffset ht (Icon _) _ _ conf    | iconOffset conf > -1 = return $ fi (iconOffset conf)    | otherwise = return $ fi (ht `div` 2) - 1 +printString :: Display -> Drawable -> XFont -> GC -> String -> String +            -> Position -> Position -> String -> Int -> IO () +printString d p (Core fs) gc fc bc x y s a = do +    setFont d gc $ fontFromFontStruct fs +    withColors d [fc, bc] $ \[fc', bc'] -> do +      setForeground d gc fc' +      when (a == 255) (setBackground d gc bc') +      drawImageString d p gc x y s + +printString d p (Utf8 fs) gc fc bc x y s a = +    withColors d [fc, bc] $ \[fc', bc'] -> do +      setForeground d gc fc' +      when (a == 255) (setBackground d gc bc') +      liftIO $ wcDrawImageString d p fs gc x y s + +#ifdef XFT +printString dpy drw fs@(Xft fonts) _ fc bc x y s al = +  withDrawingColors dpy drw fc bc $ \draw fc' bc' -> do +    when (al == 255) $ do +      (a,d)  <- textExtents fs s +      gi <- xftTxtExtents' dpy fonts s +      drawXftRect draw bc' x (y - a) (1 + xglyphinfo_xOff gi) (a + d + 2) +    drawXftString' draw fc' fonts (toInteger x) (toInteger y) s +#endif +  -- | An easy way to print the stuff we need to print  printStrings :: Drawable -> GC -> [XFont] -> [Int] -> Position               -> Align -> [(Widget, String, Int, Position)] -> X () diff --git a/src/lib/Xmobar/EventLoop.hs b/src/lib/Xmobar/X11/EventLoop.hs index 00f7465..1c864c3 100644 --- a/src/lib/Xmobar/EventLoop.hs +++ b/src/lib/Xmobar/X11/EventLoop.hs @@ -2,7 +2,7 @@  ------------------------------------------------------------------------------  -- | --- Module: Xmobar.EventLoop +-- Module: Xmobar.X11.EventLoop  -- Copyright: (c) 2018 Jose Antonio Ortega Ruiz  -- License: BSD3-style (see LICENSE)  -- @@ -17,7 +17,7 @@  ------------------------------------------------------------------------------ -module Xmobar.EventLoop (startLoop, startCommand) where +module Xmobar.X11.EventLoop (startLoop, startCommand) where  import Prelude hiding (lookup)  import Graphics.X11.Xlib hiding (textExtents, textWidth) @@ -36,18 +36,18 @@ import Data.Bits  import Data.Map hiding (foldr, map, filter)  import Data.Maybe (fromJust, isJust) -import Xmobar.Bitmap as Bitmap +import Xmobar.X11.Bitmap as Bitmap +import Xmobar.X11.Types  import Xmobar.Config  import Xmobar.Parsers  import Xmobar.Commands  import Xmobar.Actions  import Xmobar.Runnable  import Xmobar.Signal -import Xmobar.Window -import Xmobar.XUtil +import Xmobar.X11.Window +import Xmobar.X11.XUtil  import Xmobar.Utils -import Xmobar.Draw -import Xmobar.Types +import Xmobar.X11.Draw  #ifdef XFT  import Graphics.X11.Xft @@ -57,6 +57,9 @@ import Graphics.X11.Xft  import Xmobar.IPC.DBus  #endif +runX :: XConf -> X () -> IO () +runX xc f = runReaderT f xc +  -- | Starts the main event loop and threads  startLoop :: XConf -> TMVar SignalType -> [[([Async ()], TVar String)]]               -> IO () diff --git a/src/lib/Xmobar/MinXft.hsc b/src/lib/Xmobar/X11/MinXft.hsc index 0bf36c7..e593da0 100644 --- a/src/lib/Xmobar/MinXft.hsc +++ b/src/lib/Xmobar/X11/MinXft.hsc @@ -20,7 +20,7 @@  {-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-} -module Xmobar.MinXft ( AXftColor +module Xmobar.X11.MinXft ( AXftColor                , AXftDraw (..)                , AXftFont                , mallocAXftColor diff --git a/src/lib/Xmobar/Types.hs b/src/lib/Xmobar/X11/Types.hs index f7c4fdf..77249b3 100644 --- a/src/lib/Xmobar/Types.hs +++ b/src/lib/Xmobar/X11/Types.hs @@ -15,18 +15,15 @@  ------------------------------------------------------------------------------ -module Xmobar.Types (X , XConf (..), runX) where +module Xmobar.X11.Types (X , XConf (..)) where  import Graphics.X11.Xlib  import Control.Monad.Reader  import Data.Map +import Xmobar.X11.Bitmap +import Xmobar.X11.XUtil  import Xmobar.Config -import Xmobar.Bitmap -import Xmobar.XUtil - - --- The Xmobar data type and basic loops and functions.  -- | The X type is a ReaderT  type X = ReaderT XConf IO @@ -41,7 +38,3 @@ data XConf =            , iconS     :: Map FilePath Bitmap            , config    :: Config            } - --- | Runs the ReaderT -runX :: XConf -> X () -> IO () -runX xc f = runReaderT f xc diff --git a/src/lib/Xmobar/Window.hs b/src/lib/Xmobar/X11/Window.hs index c8ba1bd..78f4b26 100644 --- a/src/lib/Xmobar/Window.hs +++ b/src/lib/Xmobar/X11/Window.hs @@ -13,7 +13,7 @@  --  ----------------------------------------------------------------------------- -module Xmobar.Window where +module Xmobar.X11.Window where  import Prelude  import Control.Applicative ((<$>)) @@ -29,7 +29,7 @@ import Data.Maybe (fromMaybe)  import System.Posix.Process (getProcessID)  import Xmobar.Config -import Xmobar.XUtil +import Xmobar.X11.XUtil  -- $window diff --git a/src/lib/Xmobar/XUtil.hs b/src/lib/Xmobar/X11/XUtil.hs index e70612b..6e9eb2b 100644 --- a/src/lib/Xmobar/XUtil.hs +++ b/src/lib/Xmobar/X11/XUtil.hs @@ -13,18 +13,15 @@  --  ----------------------------------------------------------------------------- -module Xmobar.XUtil -    ( XFont +module Xmobar.X11.XUtil +    ( XFont(..)      , initFont      , initCoreFont      , initUtf8Font      , textExtents      , textWidth -    , printString      ) where -import Control.Monad (when) -import Control.Monad.Trans  import Control.Exception (SomeException, handle)  import Data.List  import Foreign @@ -34,15 +31,12 @@ import Graphics.X11.Xlib.Extras  import System.Mem.Weak ( addFinalizer )  #if defined XFT -import Xmobar.MinXft +import Xmobar.X11.MinXft  import Graphics.X11.Xrender  #else  import System.IO(hPutStrLn, stderr)  #endif -import Xmobar.ColorCache - --- Hide the Core Font/Xft switching here  data XFont = Core FontStruct             | Utf8 FontSet  #ifdef XFT @@ -133,28 +127,3 @@ textExtents (Xft xftfonts) _ = do    descent <- fromIntegral `fmap` xft_descent' xftfonts    return (ascent, descent)  #endif - -printString :: Display -> Drawable -> XFont -> GC -> String -> String -            -> Position -> Position -> String -> Int -> IO () -printString d p (Core fs) gc fc bc x y s a = do -    setFont d gc $ fontFromFontStruct fs -    withColors d [fc, bc] $ \[fc', bc'] -> do -      setForeground d gc fc' -      when (a == 255) (setBackground d gc bc') -      drawImageString d p gc x y s - -printString d p (Utf8 fs) gc fc bc x y s a = -    withColors d [fc, bc] $ \[fc', bc'] -> do -      setForeground d gc fc' -      when (a == 255) (setBackground d gc bc') -      liftIO $ wcDrawImageString d p fs gc x y s - -#ifdef XFT -printString dpy drw fs@(Xft fonts) _ fc bc x y s al = -  withDrawingColors dpy drw fc bc $ \draw fc' bc' -> do -    when (al == 255) $ do -      (a,d)  <- textExtents fs s -      gi <- xftTxtExtents' dpy fonts s -      drawXftRect draw bc' x (y - a) (1 + xglyphinfo_xOff gi) (a + d + 2) -    drawXftString' draw fc' fonts (toInteger x) (toInteger y) s -#endif | 
