summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@ing.unitn.it>2008-04-29 14:59:53 +0200
committerAndrea Rossato <andrea.rossato@ing.unitn.it>2008-04-29 14:59:53 +0200
commit4b73d3043896c2d759a60894bdfdadbc10d93bf4 (patch)
tree5ff75f2b73efa0f590e04a9b693606c2b8499814
parent661ba1eaf6f10dad7dcff79a326ebb5d22d012c6 (diff)
downloadxmobar-4b73d3043896c2d759a60894bdfdadbc10d93bf4.tar.gz
xmobar-4b73d3043896c2d759a60894bdfdadbc10d93bf4.tar.bz2
style, pointfree and trailing spaces0.9_release
darcs-hash:20080429125953-d6583-02a6653c15d3166ad264c45ec44082bdae30260e.gz
-rw-r--r--Commands.hs14
-rw-r--r--Config.hs25
-rw-r--r--Parsers.hs2
-rw-r--r--Plugins.hs13
-rw-r--r--Runnable.hs-boot3
-rw-r--r--XUtil.hsc10
-rw-r--r--Xmobar.hs29
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
diff --git a/Config.hs b/Config.hs
index a1e6a2b..9dbd9e0 100644
--- a/Config.hs
+++ b/Config.hs
@@ -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>"
diff --git a/Parsers.hs b/Parsers.hs
index 4c9cc8e..5c086ff 100644
--- a/Parsers.hs
+++ b/Parsers.hs
@@ -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)
diff --git a/Plugins.hs b/Plugins.hs
index d6952b4..07541c7 100644
--- a/Plugins.hs
+++ b/Plugins.hs
@@ -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
-
-
-
diff --git a/XUtil.hsc b/XUtil.hsc
index 10d5995..e6de33c 100644
--- a/XUtil.hsc
+++ b/XUtil.hsc
@@ -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
diff --git a/Xmobar.hs b/Xmobar.hs
index 594da82..fdc2446 100644
--- a/Xmobar.hs
+++ b/Xmobar.hs
@@ -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)