From 77df1ac30fa7af5948f7ff64f5fee9aed64552b3 Mon Sep 17 00:00:00 2001 From: jao Date: Sun, 25 Nov 2018 15:10:29 +0000 Subject: Back to app/src, since it seems they're the default convention for stack --- src/lib/Xmobar/Run/Commands.hs | 72 ----------- src/lib/Xmobar/Run/EventLoop.hs | 252 ------------------------------------ src/lib/Xmobar/Run/Runnable.hs | 60 --------- src/lib/Xmobar/Run/Runnable.hs-boot | 8 -- src/lib/Xmobar/Run/Template.hs | 65 ---------- src/lib/Xmobar/Run/Types.hs | 65 ---------- 6 files changed, 522 deletions(-) delete mode 100644 src/lib/Xmobar/Run/Commands.hs delete mode 100644 src/lib/Xmobar/Run/EventLoop.hs delete mode 100644 src/lib/Xmobar/Run/Runnable.hs delete mode 100644 src/lib/Xmobar/Run/Runnable.hs-boot delete mode 100644 src/lib/Xmobar/Run/Template.hs delete mode 100644 src/lib/Xmobar/Run/Types.hs (limited to 'src/lib/Xmobar/Run') diff --git a/src/lib/Xmobar/Run/Commands.hs b/src/lib/Xmobar/Run/Commands.hs deleted file mode 100644 index 198edee..0000000 --- a/src/lib/Xmobar/Run/Commands.hs +++ /dev/null @@ -1,72 +0,0 @@ ------------------------------------------------------------------------------ --- | --- Module : Xmobar.Commands --- Copyright : (c) Andrea Rossato --- License : BSD-style (see LICENSE) --- --- Maintainer : Jose A. Ortega Ruiz --- Stability : unstable --- Portability : unportable --- --- The 'Exec' class and the 'Command' data type. --- --- The 'Exec' class rappresents the executable types, whose constructors may --- appear in the 'Config.commands' field of the 'Config.Config' data type. --- --- The 'Command' data type is for OS commands to be run by xmobar --- ------------------------------------------------------------------------------ - -module Xmobar.Run.Commands (Command (..), Exec (..)) where - -import Prelude -import Control.Exception (handle, SomeException(..)) -import Data.Char -import System.Process -import System.Exit -import System.IO (hClose) - -import Xmobar.System.Signal -import Xmobar.Utils (hGetLineSafe, tenthSeconds) - -class Show e => Exec e where - alias :: e -> String - alias e = takeWhile (not . isSpace) $ show e - rate :: e -> Int - rate _ = 10 - run :: e -> IO String - run _ = return "" - start :: e -> (String -> IO ()) -> IO () - start e cb = go - where go = run e >>= cb >> tenthSeconds (rate e) >> go - trigger :: e -> (Maybe SignalType -> IO ()) -> IO () - trigger _ sh = sh Nothing - -data Command = Com Program Args Alias Rate - | ComX Program Args String Alias Rate - deriving (Show,Read,Eq) - -type Args = [String] -type Program = String -type Alias = String -type Rate = Int - -instance Exec Command where - alias (ComX p _ _ a _) = - if p /= "" then (if a == "" then p else a) else "" - alias (Com p a al r) = alias (ComX p a "" al r) - start (Com p as al r) cb = - start (ComX p as ("Could not execute command " ++ p) al r) cb - start (ComX prog args msg _ r) cb = if r > 0 then go else exec - where go = exec >> tenthSeconds r >> go - exec = do - (i,o,e,p) <- runInteractiveProcess prog args Nothing Nothing - exit <- waitForProcess p - let closeHandles = hClose o >> hClose i >> hClose e - getL = handle (\(SomeException _) -> return "") - (hGetLineSafe o) - case exit of - ExitSuccess -> do str <- getL - closeHandles - cb str - _ -> closeHandles >> cb msg diff --git a/src/lib/Xmobar/Run/EventLoop.hs b/src/lib/Xmobar/Run/EventLoop.hs deleted file mode 100644 index a4385d1..0000000 --- a/src/lib/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/lib/Xmobar/Run/Runnable.hs b/src/lib/Xmobar/Run/Runnable.hs deleted file mode 100644 index 962166e..0000000 --- a/src/lib/Xmobar/Run/Runnable.hs +++ /dev/null @@ -1,60 +0,0 @@ -{-# LANGUAGE ExistentialQuantification, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances #-} ------------------------------------------------------------------------------ --- | --- Module : Xmobar.Runnable --- Copyright : (c) Andrea Rossato --- License : BSD-style (see LICENSE) --- --- Maintainer : Jose A. Ortega Ruiz --- Stability : unstable --- Portability : unportable --- --- The existential type to store the list of commands to be executed. --- I must thank Claus Reinke for the help in understanding the mysteries of --- reading existential types. The Read instance of Runnable must be credited to --- him. --- --- See here: --- http:\/\/www.haskell.org\/pipermail\/haskell-cafe\/2007-July\/028227.html --- ------------------------------------------------------------------------------ - -module Xmobar.Run.Runnable where - -import Control.Monad -import Text.Read -import Xmobar.Run.Types (runnableTypes) -import Xmobar.Run.Commands - -data Runnable = forall r . (Exec r, Read r, Show r) => Run r - -instance Exec Runnable where - start (Run a) = start a - alias (Run a) = alias a - trigger (Run a) = trigger a - -instance Show Runnable where - show (Run x) = show x - -instance Read Runnable where - readPrec = readRunnable - -class ReadAsAnyOf ts ex where - -- | Reads an existential type as any of hidden types ts - readAsAnyOf :: ts -> ReadPrec ex - -instance ReadAsAnyOf () ex where - readAsAnyOf ~() = mzero - -instance (Read t, Exec t, ReadAsAnyOf ts Runnable) => ReadAsAnyOf (t,ts) Runnable where - readAsAnyOf ~(t,ts) = r t `mplus` readAsAnyOf ts - where r ty = do { m <- readPrec; return (Run (m `asTypeOf` ty)) } - --- | The 'Prelude.Read' parser for the 'Runnable' existential type. It --- needs an 'Prelude.undefined' with a type signature containing the --- list of all possible types hidden within 'Runnable'. See 'Config.runnableTypes'. --- Each hidden type must have a 'Prelude.Read' instance. -readRunnable :: ReadPrec Runnable -readRunnable = prec 10 $ do - Ident "Run" <- lexP - parens $ readAsAnyOf runnableTypes diff --git a/src/lib/Xmobar/Run/Runnable.hs-boot b/src/lib/Xmobar/Run/Runnable.hs-boot deleted file mode 100644 index f272d81..0000000 --- a/src/lib/Xmobar/Run/Runnable.hs-boot +++ /dev/null @@ -1,8 +0,0 @@ -{-# LANGUAGE ExistentialQuantification #-} -module Xmobar.Run.Runnable where -import Xmobar.Run.Commands - -data Runnable = forall r . (Exec r,Read r,Show r) => Run r - -instance Read Runnable -instance Exec Runnable diff --git a/src/lib/Xmobar/Run/Template.hs b/src/lib/Xmobar/Run/Template.hs deleted file mode 100644 index 5bada89..0000000 --- a/src/lib/Xmobar/Run/Template.hs +++ /dev/null @@ -1,65 +0,0 @@ ------------------------------------------------------------------------------- --- | --- Module: Xmobar.Template --- Copyright: (c) 2018 Jose Antonio Ortega Ruiz --- License: BSD3-style (see LICENSE) --- --- Maintainer: jao@gnu.org --- Stability: unstable --- Portability: portable --- Created: Sun Nov 25, 2018 05:49 --- --- --- Handling the top-level output template --- ------------------------------------------------------------------------------- - - -module Xmobar.Run.Template(parseCommands) where - -import qualified Data.Map as Map -import Text.ParserCombinators.Parsec - -import Xmobar.Run.Commands -import Xmobar.Run.Runnable -import Xmobar.Config - --- | Parses the output template string -templateStringParser :: Config -> Parser (String,String,String) -templateStringParser c = do - s <- allTillSep c - com <- templateCommandParser c - ss <- allTillSep c - 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) - --- | Combines the template parsers -templateParser :: Config -> Parser [(String,String,String)] -templateParser = many . templateStringParser - --- | Actually runs the template parsers -parseCommands :: Config -> String -> IO [(Runnable,String,String)] -parseCommands c s = - do str <- case parse (templateParser c) "" s of - Left _ -> return [("", s, "")] - Right x -> return x - let cl = map alias (commands c) - m = Map.fromList $ zip cl (commands 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 _ _ [] = [] -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 diff --git a/src/lib/Xmobar/Run/Types.hs b/src/lib/Xmobar/Run/Types.hs deleted file mode 100644 index 4fb526a..0000000 --- a/src/lib/Xmobar/Run/Types.hs +++ /dev/null @@ -1,65 +0,0 @@ -{-# LANGUAGE TypeOperators, CPP #-} ------------------------------------------------------------------------------- --- | --- Module: Xmobar.Run.Types --- Copyright: (c) 2018 Jose Antonio Ortega Ruiz --- License: BSD3-style (see LICENSE) --- --- Maintainer: jao@gnu.org --- Stability: unstable --- Portability: portable --- Created: Sun Nov 25, 2018 07:17 --- --- --- An enumeration of all runnable types --- ------------------------------------------------------------------------------- - - -module Xmobar.Run.Types(runnableTypes) where - -import Xmobar.Run.Commands - -import {-# SOURCE #-} Xmobar.Run.Runnable() -import Xmobar.Plugins.Monitors -import Xmobar.Plugins.Date -import Xmobar.Plugins.PipeReader -import Xmobar.Plugins.BufferedPipeReader -import Xmobar.Plugins.MarqueePipeReader -import Xmobar.Plugins.CommandReader -import Xmobar.Plugins.StdinReader -import Xmobar.Plugins.XMonadLog -import Xmobar.Plugins.EWMH -import Xmobar.Plugins.Kbd -import Xmobar.Plugins.Locks - -#ifdef INOTIFY -import Xmobar.Plugins.Mail -import Xmobar.Plugins.MBox -#endif - -#ifdef DATEZONE -import Xmobar.Plugins.DateZone -#endif - --- | An alias for tuple types that is more convenient for long lists. -type a :*: b = (a, b) -infixr :*: - --- | This is the list of types that can be hidden inside --- 'Runnable.Runnable', the existential type that stores all commands --- to be executed by Xmobar. It is used by 'Runnable.readRunnable' in --- the 'Runnable.Runnable' Read instance. To install a plugin just add --- the plugin's type to the list of types (separated by ':*:') appearing in --- this function's type signature. -runnableTypes :: Command :*: Monitors :*: Date :*: PipeReader :*: - BufferedPipeReader :*: CommandReader :*: StdinReader :*: - XMonadLog :*: EWMH :*: Kbd :*: Locks :*: -#ifdef INOTIFY - Mail :*: MBox :*: -#endif -#ifdef DATEZONE - DateZone :*: -#endif - MarqueePipeReader :*: () -runnableTypes = undefined -- cgit v1.2.3