diff options
-rw-r--r-- | Commands.hs | 14 | ||||
-rw-r--r-- | Config.hs | 25 | ||||
-rw-r--r-- | Parsers.hs | 2 | ||||
-rw-r--r-- | Plugins.hs | 13 | ||||
-rw-r--r-- | Runnable.hs-boot | 3 | ||||
-rw-r--r-- | XUtil.hsc | 10 | ||||
-rw-r--r-- | Xmobar.hs | 29 |
7 files changed, 51 insertions, 45 deletions
diff --git a/Commands.hs b/Commands.hs index 1be0677..5e03ad0 100644 --- a/Commands.hs +++ b/Commands.hs @@ -3,7 +3,7 @@ -- Module : Xmobar.Commands -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) --- +-- -- Maintainer : Andrea Rossato <andrea.rossato@unibz.it> -- Stability : unstable -- Portability : unportable @@ -13,11 +13,15 @@ -- 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 +-- The 'Command' data type is for OS commands to be run by xmobar -- ----------------------------------------------------------------------------- -module Commands where +module Commands + ( Command (..) + , Exec (..) + , tenthSeconds + ) where import Control.Concurrent import Data.Char @@ -54,12 +58,12 @@ instance Exec Command where where go = do (i,o,e,p) <- runInteractiveCommand (prog ++ concat (map (' ':) args)) exit <- waitForProcess p - let closeHandles = do + let closeHandles = do hClose o hClose i hClose e case exit of - ExitSuccess -> do + ExitSuccess -> do str <- hGetLine o closeHandles cb str @@ -12,13 +12,14 @@ -- ----------------------------------------------------------------------------- -module Config ( -- * Configuration - -- $config - Config (..) - , XPosition (..), Align (..) - , defaultConfig - , runnableTypes - ) where +module Config + ( -- * Configuration + -- $config + Config (..) + , XPosition (..), Align (..) + , defaultConfig + , runnableTypes + ) where import Commands import {-# SOURCE #-} Runnable @@ -44,7 +45,12 @@ data Config = , template :: String -- ^ The output template } deriving (Read) -data XPosition = Top | TopW Align Int | Bottom | BottomW Align Int | Static {xpos, ypos, width, height :: Int} deriving ( Read, Eq ) +data XPosition = Top + | TopW Align Int + | Bottom + | BottomW Align Int + | Static {xpos, ypos, width, height :: Int} + deriving ( Read, Eq ) data Align = L | R | C deriving ( Read, Eq ) @@ -56,8 +62,7 @@ defaultConfig = , fgColor = "#BFBFBF" , position = Top , commands = [ Run $ Date "%a %b %_d %Y * %H:%M:%S" "theDate" 10 - , Run StdinReader - ] + , Run StdinReader] , sepChar = "%" , alignSep = "}{" , template = "%StdinReader% }{ <fc=#00FF00>%uname%</fc> * <fc=#FF0000>%theDate%</fc>" @@ -79,7 +79,7 @@ templateParser = many . templateStringParser -- | Actually runs the template parsers parseTemplate :: Config -> String -> IO [(Runnable,String,String)] parseTemplate c s = - do str <- case (parse (templateParser c) "" s) of + do str <- case parse (templateParser c) "" s of Left _ -> return [("","","")] Right x -> return x let cl = map alias (commands c) @@ -3,7 +3,7 @@ -- Module : Xmobar.Plugins -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) --- +-- -- Maintainer : Andrea Rossato <andrea.rossato@unibz.it> -- Stability : unstable -- Portability : unportable @@ -14,11 +14,12 @@ -- ----------------------------------------------------------------------------- -module Plugins ( Exec (..) - , tenthSeconds - , readFileSafe - , hGetLineSafe - ) where +module Plugins + ( Exec (..) + , tenthSeconds + , readFileSafe + , hGetLineSafe + ) where import Commands import XUtil diff --git a/Runnable.hs-boot b/Runnable.hs-boot index 3c5f8db..5d5fc18 100644 --- a/Runnable.hs-boot +++ b/Runnable.hs-boot @@ -6,6 +6,3 @@ data Runnable = forall r . (Exec r,Read r,Show r) => Run r instance Read Runnable instance Exec Runnable - - - @@ -81,9 +81,9 @@ initFont d s = else #endif #ifdef UTF8 - (setupLocale >> initUtf8Font d s >>= (return . Utf8)) + (setupLocale >> initUtf8Font d s >>= return . Utf8) #else - (initCoreFont d s >>= (return . Core)) + (initCoreFont d s >>= return . Core) #endif #ifdef XFT where xftPrefix = "xft:" @@ -219,8 +219,6 @@ fi = fromIntegral foreign import ccall unsafe "locale.h setlocale" setlocale :: CInt -> CString -> IO CString -setupLocale :: IO () -setupLocale = withCString "" $ \s -> do - setlocale (#const LC_ALL) s - return () +setupLocale :: IO CString +setupLocale = withCString "" $ setlocale (#const LC_ALL) #endif @@ -13,20 +13,21 @@ -- ----------------------------------------------------------------------------- -module Xmobar (-- * Main Stuff - -- $main - X, XConf (..), runX - , eventLoop - -- * Program Execution - -- $command - , startCommand - -- * Window Management - -- $window - , createWin, updateWin - -- * Printing - -- $print - , drawInWin, printStrings - ) where +module Xmobar + ( -- * Main Stuff + -- $main + X , XConf (..), runX + , eventLoop + -- * Program Execution + -- $command + , startCommand + -- * Window Management + -- $window + , createWin, updateWin + -- * Printing + -- $print + , drawInWin, printStrings + ) where import Prelude hiding (catch) import Graphics.X11.Xlib hiding (textExtents, textWidth) |