summaryrefslogtreecommitdiffhomepage
path: root/src/Xmobar/Run
diff options
context:
space:
mode:
authorjao <jao@gnu.org>2018-11-25 21:48:15 +0000
committerjao <jao@gnu.org>2018-11-25 21:48:15 +0000
commitbc27a68eb346b5e73c530f0f9c3e62e56517e225 (patch)
treed89fb49ee864ce0594d9ba2eff8836abd1e7a564 /src/Xmobar/Run
parente04d4c6eb84d5adfe62b6a538e7c4008974424b2 (diff)
downloadxmobar-bc27a68eb346b5e73c530f0f9c3e62e56517e225.tar.gz
xmobar-bc27a68eb346b5e73c530f0f9c3e62e56517e225.tar.bz2
Xmobar.App and small refactorings
Diffstat (limited to 'src/Xmobar/Run')
-rw-r--r--src/Xmobar/Run/EventLoop.hs252
-rw-r--r--src/Xmobar/Run/Template.hs57
2 files changed, 35 insertions, 274 deletions
diff --git a/src/Xmobar/Run/EventLoop.hs b/src/Xmobar/Run/EventLoop.hs
deleted file mode 100644
index a4385d1..0000000
--- a/src/Xmobar/Run/EventLoop.hs
+++ /dev/null
@@ -1,252 +0,0 @@
-{-# LANGUAGE CPP #-}
-
-------------------------------------------------------------------------------
--- |
--- Module: Xmobar.X11.EventLoop
--- Copyright: (c) 2018 Jose Antonio Ortega Ruiz
--- License: BSD3-style (see LICENSE)
---
--- Maintainer: jao@gnu.org
--- Stability: unstable
--- Portability: portable
--- Created: Sat Nov 24, 2018 19:40
---
---
--- Event loop
---
-------------------------------------------------------------------------------
-
-
-module Xmobar.Run.EventLoop (startLoop, startCommand) where
-
-import Prelude hiding (lookup)
-import Graphics.X11.Xlib hiding (textExtents, textWidth)
-import Graphics.X11.Xlib.Extras
-import Graphics.X11.Xinerama
-import Graphics.X11.Xrandr
-
-import Control.Arrow ((&&&))
-import Control.Applicative ((<$>))
-import Control.Monad.Reader
-import Control.Concurrent
-import Control.Concurrent.Async (Async, async)
-import Control.Concurrent.STM
-import Control.Exception (handle, SomeException(..))
-import Data.Bits
-import Data.Map hiding (foldr, map, filter)
-import Data.Maybe (fromJust, isJust)
-
-import Xmobar.Config
-import Xmobar.Actions
-import Xmobar.Utils
-import Xmobar.System.Signal
-import Xmobar.Run.Commands
-import Xmobar.Run.Runnable
-import Xmobar.X11.Parsers
-import Xmobar.X11.Window
-import Xmobar.X11.XUtil
-import Xmobar.X11.Draw
-import Xmobar.X11.Bitmap as Bitmap
-import Xmobar.X11.Types
-
-#ifdef XFT
-import Graphics.X11.Xft
-#endif
-
-#ifdef DBUS
-import Xmobar.System.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 ()
-startLoop xcfg@(XConf _ _ w _ _ _ _) sig vs = do
-#ifdef XFT
- xftInitFtLibrary
-#endif
- tv <- atomically $ newTVar []
- _ <- forkIO (handle (handler "checker") (checker tv [] vs sig))
-#ifdef THREADED_RUNTIME
- _ <- forkOS (handle (handler "eventer") (eventer sig))
-#else
- _ <- forkIO (handle (handler "eventer") (eventer sig))
-#endif
-#ifdef DBUS
- runIPC sig
-#endif
- eventLoop tv xcfg [] sig
- where
- handler thing (SomeException e) =
- void $ putStrLn ("Thread " ++ thing ++ " failed: " ++ show e)
- -- Reacts on events from X
- eventer signal =
- allocaXEvent $ \e -> do
- dpy <- openDisplay ""
- xrrSelectInput dpy (defaultRootWindow dpy) rrScreenChangeNotifyMask
- selectInput dpy w (exposureMask .|. structureNotifyMask .|. buttonPressMask)
-
- forever $ do
-#ifdef THREADED_RUNTIME
- nextEvent dpy e
-#else
- nextEvent' dpy e
-#endif
- ev <- getEvent e
- case ev of
- ConfigureEvent {} -> atomically $ putTMVar signal Reposition
- ExposeEvent {} -> atomically $ putTMVar signal Wakeup
- RRScreenChangeNotifyEvent {} -> atomically $ putTMVar signal Reposition
- ButtonEvent {} -> atomically $ putTMVar signal (Action (ev_button ev) (fi $ ev_x ev))
- _ -> return ()
-
--- | Send signal to eventLoop every time a var is updated
-checker :: TVar [String]
- -> [String]
- -> [[([Async ()], TVar String)]]
- -> TMVar SignalType
- -> IO ()
-checker tvar ov vs signal = do
- nval <- atomically $ do
- nv <- mapM concatV vs
- guard (nv /= ov)
- writeTVar tvar nv
- return nv
- atomically $ putTMVar signal Wakeup
- checker tvar nval vs signal
- where
- concatV = fmap concat . mapM (readTVar . snd)
-
-
--- | Continuously wait for a signal from a thread or a interrupt handler
-eventLoop :: TVar [String]
- -> XConf
- -> [([Action], Position, Position)]
- -> TMVar SignalType
- -> IO ()
-eventLoop tv xc@(XConf d r w fs vos is cfg) as signal = do
- typ <- atomically $ takeTMVar signal
- case typ of
- Wakeup -> do
- str <- updateString cfg tv
- xc' <- updateCache d w is (iconRoot cfg) str >>=
- \c -> return xc { iconS = c }
- as' <- updateActions xc r str
- runX xc' $ drawInWin r str
- eventLoop tv xc' as' signal
-
- Reposition ->
- reposWindow cfg
-
- ChangeScreen -> do
- ncfg <- updateConfigPosition cfg
- reposWindow ncfg
-
- Hide t -> hide (t*100*1000)
- Reveal t -> reveal (t*100*1000)
- Toggle t -> toggle t
-
- TogglePersistent -> eventLoop
- tv xc { config = cfg { persistent = not $ persistent cfg } } as signal
-
- Action but x -> action but x
-
- where
- isPersistent = not $ persistent cfg
-
- hide t
- | t == 0 =
- when isPersistent (hideWindow d w) >> eventLoop tv xc as signal
- | otherwise = do
- void $ forkIO
- $ threadDelay t >> atomically (putTMVar signal $ Hide 0)
- eventLoop tv xc as signal
-
- reveal t
- | t == 0 = do
- when isPersistent (showWindow r cfg d w)
- eventLoop tv xc as signal
- | otherwise = do
- void $ forkIO
- $ threadDelay t >> atomically (putTMVar signal $ Reveal 0)
- eventLoop tv xc as signal
-
- toggle t = do
- ismapped <- isMapped d w
- atomically (putTMVar signal $ if ismapped then Hide t else Reveal t)
- eventLoop tv xc as signal
-
- reposWindow rcfg = do
- r' <- repositionWin d w (head fs) rcfg
- eventLoop tv (XConf d r' w fs vos is rcfg) as signal
-
- updateConfigPosition ocfg =
- case position ocfg of
- OnScreen n o -> do
- srs <- getScreenInfo d
- return (if n == length srs
- then
- (ocfg {position = OnScreen 1 o})
- else
- (ocfg {position = OnScreen (n+1) o}))
- o -> return (ocfg {position = OnScreen 1 o})
-
- action button x = do
- mapM_ runAction $
- filter (\(Spawn b _) -> button `elem` b) $
- concatMap (\(a,_,_) -> a) $
- filter (\(_, from, to) -> x >= from && x <= to) as
- eventLoop tv xc as signal
-
--- $command
-
--- | Runs a command as an independent thread and returns its Async handles
--- and the TVar the command will be writing to.
-startCommand :: TMVar SignalType
- -> (Runnable,String,String)
- -> IO ([Async ()], TVar String)
-startCommand sig (com,s,ss)
- | alias com == "" = do var <- atomically $ newTVar is
- atomically $ writeTVar var (s ++ ss)
- return ([], var)
- | otherwise = do var <- atomically $ newTVar is
- let cb str = atomically $ writeTVar var (s ++ str ++ ss)
- a1 <- async $ start com cb
- a2 <- async $ trigger com $ maybe (return ())
- (atomically . putTMVar sig)
- return ([a1, a2], var)
- where is = s ++ "Updating..." ++ ss
-
-updateString :: Config -> TVar [String]
- -> IO [[(Widget, String, 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, String, Int, Maybe [Action])]]
- -> IO [([Action], Position, Position)]
-updateActions conf (Rectangle _ _ wid _) ~[left,center,right] = do
- let (d,fs) = (display &&& fontListS) conf
- strLn :: [(Widget, String, 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 (fs!!i) s >>= \tw -> return (a, 0, fi tw)
- getCoords (Icon s,_,_,a) = return (a, 0, fi $ iconW s)
- partCoord off xs = map (\(a, x, x') -> (fromJust a, x, x')) $
- filter (\(a, _,_) -> isJust a) $
- scanl (\(_,_,x') (a,_,w') -> (a, x', x' + w'))
- (Nothing, 0, off)
- xs
- totSLen = foldr (\(_,_,len) -> (+) len) 0
- remWidth xs = fi wid - totSLen xs
- offs = 1
- offset a xs = case a of
- C -> (remWidth xs + offs) `div` 2
- R -> remWidth xs
- L -> offs
- fmap concat $ mapM (\(a,xs) ->
- (\xs' -> partCoord (offset a xs') xs') <$> strLn xs) $
- zip [L,C,R] [left,center,right]
diff --git a/src/Xmobar/Run/Template.hs b/src/Xmobar/Run/Template.hs
index 5bada89..a544724 100644
--- a/src/Xmobar/Run/Template.hs
+++ b/src/Xmobar/Run/Template.hs
@@ -15,51 +15,64 @@
------------------------------------------------------------------------------
-module Xmobar.Run.Template(parseCommands) where
+module Xmobar.Run.Template(parseTemplate, splitTemplate) where
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec
import Xmobar.Run.Commands
import Xmobar.Run.Runnable
-import Xmobar.Config
+
+defaultAlign :: String
+defaultAlign = "}{"
+
+allTillSep :: String -> Parser String
+allTillSep = many . noneOf
-- | Parses the output template string
-templateStringParser :: Config -> Parser (String,String,String)
-templateStringParser c = do
- s <- allTillSep c
- com <- templateCommandParser c
- ss <- allTillSep c
+templateStringParser :: String -> Parser (String,String,String)
+templateStringParser sepChar = do
+ s <- allTillSep sepChar
+ com <- templateCommandParser sepChar
+ ss <- allTillSep sepChar
return (com, s, ss)
-- | Parses the command part of the template string
-templateCommandParser :: Config -> Parser String
-templateCommandParser c =
- let chr = char . head . sepChar
- in between (chr c) (chr c) (allTillSep c)
+templateCommandParser :: String -> Parser String
+templateCommandParser sepChar =
+ let chr = char (head sepChar) in between chr chr (allTillSep sepChar)
-- | Combines the template parsers
-templateParser :: Config -> Parser [(String,String,String)]
-templateParser = many . templateStringParser
+templateParser :: String -> Parser [(String,String,String)]
+templateParser s = many $ templateStringParser s
-- | Actually runs the template parsers
-parseCommands :: Config -> String -> IO [(Runnable,String,String)]
-parseCommands c s =
- do str <- case parse (templateParser c) "" s of
+parseTemplate :: [Runnable] -> String -> String -> IO [(Runnable,String,String)]
+parseTemplate c sepChar s =
+ do str <- case parse (templateParser sepChar) "" s of
Left _ -> return [("", s, "")]
Right x -> return x
- let cl = map alias (commands c)
- m = Map.fromList $ zip cl (commands c)
+ let cl = map alias c
+ m = Map.fromList $ zip cl c
return $ combine c m str
-- | Given a finite "Map" and a parsed template produce the resulting
-- output string.
-combine :: Config -> Map.Map String Runnable
- -> [(String, String, String)] -> [(Runnable,String,String)]
+combine :: [Runnable] -> Map.Map String Runnable -> [(String, String, String)]
+ -> [(Runnable,String,String)]
combine _ _ [] = []
combine c m ((ts,s,ss):xs) = (com, s, ss) : combine c m xs
where com = Map.findWithDefault dflt ts m
dflt = Run $ Com ts [] [] 10
-allTillSep :: Config -> Parser String
-allTillSep = many . noneOf . sepChar
+-- | Given an two-char alignment separator and a template string,
+-- splits it into its segments, that can then be parsed via parseCommands
+splitTemplate :: String -> String -> [String]
+splitTemplate alignSep template =
+ case break (==l) template of
+ (le,_:re) -> case break (==r) re of
+ (ce,_:ri) -> [le, ce, ri]
+ _ -> def
+ _ -> def
+ where [l, r] = if (length alignSep == 2) then alignSep else defaultAlign
+ def = [template, "", ""]