diff options
| -rw-r--r-- | .hlint.yaml | 68 | ||||
| -rw-r--r-- | src/Bitmap.hs | 7 | ||||
| -rw-r--r-- | src/Environment.hs | 2 | ||||
| -rw-r--r-- | src/IWlib.hsc | 4 | ||||
| -rw-r--r-- | src/Localize.hsc | 2 | ||||
| -rw-r--r-- | src/Main.hs | 10 | ||||
| -rw-r--r-- | src/MinXft.hsc | 6 | ||||
| -rw-r--r-- | src/Parsers.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/BufferedPipeReader.hs | 1 | ||||
| -rw-r--r-- | src/Plugins/Date.hs | 3 | ||||
| -rw-r--r-- | src/Plugins/EWMH.hs | 12 | ||||
| -rw-r--r-- | src/Plugins/Kbd.hsc | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors.hs | 8 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Common.hs | 45 | ||||
| -rw-r--r-- | src/Plugins/Monitors/CoreCommon.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Cpu.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Mpris.hs | 5 | ||||
| -rw-r--r-- | src/Plugins/Monitors/MultiCpu.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Net.hs | 8 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Thermal.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/UVMeter.hs | 4 | ||||
| -rw-r--r-- | src/Plugins/Monitors/Wireless.hs | 2 | ||||
| -rw-r--r-- | src/Window.hs | 4 | ||||
| -rw-r--r-- | src/XUtil.hsc | 13 | ||||
| -rw-r--r-- | src/Xmobar.hs | 4 | 
25 files changed, 140 insertions, 92 deletions
| diff --git a/.hlint.yaml b/.hlint.yaml new file mode 100644 index 0000000..b68de82 --- /dev/null +++ b/.hlint.yaml @@ -0,0 +1,68 @@ +# HLint configuration file +# https://github.com/ndmitchell/hlint +########################## + +# This file contains a template configuration file, which is typically +# placed as .hlint.yaml in the root of your project + + +# Warnings currently triggered by your code +- ignore: {name: "Use module export list"} +- ignore: {name: "Redundant True guards"} +- ignore: {name: "Use <$>"} +- ignore: {name: "Use uncurry"} +- ignore: {name: "Reduce duplication"} + + +# Specify additional command line arguments +# +# - arguments: [--color, --cpp-simple, -XQuasiQuotes] + + +# Control which extensions/flags/modules/functions can be used +# +# - extensions: +#   - default: false # all extension are banned by default +#   - name: [PatternGuards, ViewPatterns] # only these listed extensions can be used +#   - {name: CPP, within: CrossPlatform} # CPP can only be used in a given module +# +# - flags: +#   - {name: -w, within: []} # -w is allowed nowhere +# +# - modules: +#   - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set' +#   - {name: Control.Arrow, within: []} # Certain modules are banned entirely +# +# - functions: +#   - {name: unsafePerformIO, within: []} # unsafePerformIO can only appear in no modules + + +# Add custom hints for this project +# +# Will suggest replacing "wibbleMany [myvar]" with "wibbleOne myvar" +# - error: {lhs: "wibbleMany [x]", rhs: wibbleOne x} + + +# Turn on hints that are off by default +# +# Ban "module X(module X) where", to require a real export list +# - warn: {name: Use explicit module export list} +# +# Replace a $ b $ c with a . b $ c +# - group: {name: dollar, enabled: true} +# +# Generalise map to fmap, ++ to <> +# - group: {name: generalise, enabled: true} + + +# Ignore some builtin hints +# - ignore: {name: Use let} +# - ignore: {name: Use const, within: SpecialModule} # Only within certain modules + + +# Define some custom infix operators +# - fixity: infixr 3 ~^#^~ + + +# To generate a suitable file for HLint do: +# $ hlint --default > .hlint.yaml diff --git a/src/Bitmap.hs b/src/Bitmap.hs index 0f0c746..1acc0b7 100644 --- a/src/Bitmap.hs +++ b/src/Bitmap.hs @@ -2,7 +2,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Bitmap --- Copyright   :  (C) 2013, 2015 Alexander Polakov +-- Copyright   :  (C) 2013, 2015, 2017 Alexander Polakov  -- License     :  BSD3  --  -- Maintainer  :  jao@gnu.org @@ -86,8 +86,7 @@ loadBitmap d w p = do      exist <- doesFileExist p      if exist         then do -            res <- runExceptT $ -                    tryXBM +            res <- runExceptT $ tryXBM  #ifdef XPM                  <|> tryXPM  #endif @@ -121,7 +120,7 @@ drawBitmap d p gc fc bc x y i =          y' = 1 + y - fromIntegral h `div` 2      setForeground d gc fc'      setBackground d gc bc' -    case (shapePixmap i) of +    case shapePixmap i of           Nothing -> return ()           Just mask -> setClipOrigin d gc x y' >> setClipMask d gc mask      case bitmapType i of diff --git a/src/Environment.hs b/src/Environment.hs index 120dac6..1b7e48c 100644 --- a/src/Environment.hs +++ b/src/Environment.hs @@ -11,7 +11,7 @@  -- A function to expand environment variables in strings  --  ----------------------------------------------------------------------------- -module Environment where +module Environment(expandEnv) where  import Control.Applicative  ((<$>))  import Data.Maybe           (fromMaybe) diff --git a/src/IWlib.hsc b/src/IWlib.hsc index 5f7754d..b244510 100644 --- a/src/IWlib.hsc +++ b/src/IWlib.hsc @@ -56,7 +56,7 @@ getWirelessInfo iface =      str <- c_iw_stats i istr stats rng 1      rgr <- c_iw_range i istr rng      c_iw_close i -    if (bcr < 0) then return WirelessInfo { wiEssid = "", wiQuality = 0 } else +    if bcr < 0 then return WirelessInfo { wiEssid = "", wiQuality = 0 } else        do hase <- (#peek struct wireless_config, has_essid) wc :: IO CInt           eon <- (#peek struct wireless_config, essid_on) wc :: IO CInt           essid <- if hase /= 0 && eon /= 0 then @@ -70,6 +70,6 @@ getWirelessInfo iface =                     return $ fromIntegral qualv / mxv                else return 0           let qv = round (100 * (q :: Double)) -         return $ WirelessInfo { wiEssid = essid, wiQuality = min 100 qv } +         return WirelessInfo { wiEssid = essid, wiQuality = min 100 qv }      where xqual p = let qp = (#ptr struct iw_param, value) p in              (#peek struct iw_quality, qual) qp :: IO CChar diff --git a/src/Localize.hsc b/src/Localize.hsc index b3f7d53..34d0fd9 100644 --- a/src/Localize.hsc +++ b/src/Localize.hsc @@ -50,7 +50,7 @@ getLangInfo item = do    itemStr <- nl_langinfo item  #ifdef UTF8    str <- peekCString itemStr -  return $ if (isUTF8Encoded str) then decodeString str else str +  return $ if isUTF8Encoded str then decodeString str else str  #else    peekCString itemStr  #endif diff --git a/src/Main.hs b/src/Main.hs index 0596600..288939d 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -37,7 +37,7 @@ import System.Exit  import System.Environment  import System.FilePath ((</>))  import System.Posix.Files -import Control.Monad (unless, liftM) +import Control.Monad (unless)  import Text.Read (readMaybe)  import Signal (setupSignalHandler) @@ -96,13 +96,13 @@ xdgConfigDir :: IO String  xdgConfigDir = do env <- getEnvironment                    case lookup "XDG_CONFIG_HOME" env of                         Just val -> return val -                       Nothing  -> liftM (</> ".config") getHomeDirectory +                       Nothing  -> fmap (</> ".config") getHomeDirectory  xmobarConfigDir :: IO FilePath -xmobarConfigDir = liftM (</> "xmobar") xdgConfigDir +xmobarConfigDir = fmap (</> "xmobar") xdgConfigDir  getXdgConfigFile :: IO FilePath -getXdgConfigFile = liftM (</> "xmobarrc") xmobarConfigDir +getXdgConfigFile = fmap (</> "xmobarrc") xmobarConfigDir  -- | Read default configuration file or load the default config  readDefaultConfig :: IO (Config,[String]) @@ -231,7 +231,7 @@ doOpts conf (o:oo) =                          "specified with the -" ++ c:" option\n")          readStr str = [x | (x,t) <- reads str, ("","") <- lex t]          doOpts' opts = doOpts opts oo -        readPosition string =  +        readPosition string =              case readMaybe string of                  Just x  -> doOpts' (conf { position = x })                  Nothing -> do diff --git a/src/MinXft.hsc b/src/MinXft.hsc index 148efe7..b64a8b8 100644 --- a/src/MinXft.hsc +++ b/src/MinXft.hsc @@ -1,7 +1,7 @@  ------------------------------------------------------------------------------  -- |  -- Module: MinXft --- Copyright: (c) 2012, 2014, 2015 Jose Antonio Ortega Ruiz +-- Copyright: (c) 2012, 2014, 2015, 2017 Jose Antonio Ortega Ruiz  --            (c) Clemens Fruhwirth <clemens@endorphin.org> 2007  -- License: BSD3-style (see LICENSE)  -- @@ -179,7 +179,7 @@ drawXftString' d c fs x y string = do      mapM_ (\(f, s, _, xo, yo) -> drawXftString d c f (x+xo) (y+yo) s) chunks  -- Split string and determine fonts/offsets for individual parts -getChunks :: Display -> [AXftFont] -> [Char] -> +getChunks :: Display -> [AXftFont] -> String ->               IO [(AXftFont, String, XGlyphInfo, Integer, Integer)]  getChunks disp fts str = do      chunks <- getFonts disp fts str @@ -253,7 +253,7 @@ instance Storable XRenderPictureAttributes where      sizeOf _ = #{size XRenderPictureAttributes}      alignment _ = alignment (undefined :: CInt)      peek _ = return XRenderPictureAttributes -    poke p XRenderPictureAttributes = do +    poke p XRenderPictureAttributes =          memset p 0 #{size XRenderPictureAttributes}  -- | Convenience function, gives us an XRender handle to a traditional diff --git a/src/Parsers.hs b/src/Parsers.hs index 25d215b..5f5949c 100644 --- a/src/Parsers.hs +++ b/src/Parsers.hs @@ -25,7 +25,7 @@ import Runnable  import Commands  import Actions -import Control.Monad (guard, mzero, liftM) +import Control.Monad (guard, mzero)  import qualified Data.Map as Map  import Text.ParserCombinators.Parsec  import Text.ParserCombinators.Parsec.Perm @@ -276,7 +276,7 @@ parseConfig = runParser parseConf fields "Config" . stripComments                  spaces                  char lead                  s <- manyTill anyChar (rowCont <|> unescQuote) -                (char '"' >> return s) <|> liftM (s ++) (scan '\\') +                (char '"' >> return s) <|> fmap (s ++) (scan '\\')              rowCont    = try $ char '\\' >> string "\n"              unescQuote = lookAhead (noneOf "\\") >> lookAhead (string "\"") diff --git a/src/Plugins/BufferedPipeReader.hs b/src/Plugins/BufferedPipeReader.hs index b6cad9d..eeb330b 100644 --- a/src/Plugins/BufferedPipeReader.hs +++ b/src/Plugins/BufferedPipeReader.hs @@ -27,6 +27,7 @@ import Signal  data BufferedPipeReader = BufferedPipeReader String [(Int, Bool, String)]      deriving (Read, Show) +{-# NOINLINE signal #-}  signal :: MVar SignalType  signal = unsafePerformIO newEmptyMVar diff --git a/src/Plugins/Date.hs b/src/Plugins/Date.hs index cd688e6..b2d32da 100644 --- a/src/Plugins/Date.hs +++ b/src/Plugins/Date.hs @@ -24,7 +24,6 @@ import Plugins  #if ! MIN_VERSION_time(1,5,0)  import System.Locale  #endif -import Control.Monad (liftM)  import Data.Time  data Date = Date String String Int @@ -36,4 +35,4 @@ instance Exec Date where      rate  (Date _ _ r) = r  date :: String -> IO String -date format = liftM (formatTime defaultTimeLocale format) getZonedTime +date format = fmap (formatTime defaultTimeLocale format) getZonedTime diff --git a/src/Plugins/EWMH.hs b/src/Plugins/EWMH.hs index c014aec..63395f0 100644 --- a/src/Plugins/EWMH.hs +++ b/src/Plugins/EWMH.hs @@ -150,13 +150,13 @@ getAtom s = do  windowProperty32 :: String -> Window -> M (Maybe [CLong])  windowProperty32 s w = do -    (C {display}) <- ask +    C {display} <- ask      a <- getAtom s      liftIO $ getWindowProperty32 display a w  windowProperty8 :: String -> Window -> M (Maybe [CChar])  windowProperty8 s w = do -    (C {display}) <- ask +    C {display} <- ask      a <- getAtom s      liftIO $ getWindowProperty8 display a w @@ -190,21 +190,21 @@ type Updater = Window -> M ()  updateCurrentDesktop, updateDesktopNames, updateActiveWindow :: Updater  updateCurrentDesktop _ = do -    (C {root}) <- ask +    C {root} <- ask      mwp <- windowProperty32 "_NET_CURRENT_DESKTOP" root      case mwp of          Just [x] -> modify (\s -> s { currentDesktop = x })          _        -> return ()  updateActiveWindow _ = do -    (C {root}) <- ask +    C {root} <- ask      mwp <- windowProperty32 "_NET_ACTIVE_WINDOW" root      case mwp of          Just [x] -> modify (\s -> s { activeWindow = fromIntegral x })          _        -> return ()  updateDesktopNames _ = do -    (C {root}) <- ask +    C {root} <- ask      mwp <- windowProperty8 "_NET_DESKTOP_NAMES" root      case mwp of          Just xs -> modify (\s -> s { desktopNames = parse xs }) @@ -219,7 +219,7 @@ updateDesktopNames _ = do      parse = split . decodeCChar  updateClientList _ = do -    (C {root}) <- ask +    C {root} <- ask      mwp <- windowProperty32 "_NET_CLIENT_LIST" root      case mwp of          Just xs -> do diff --git a/src/Plugins/Kbd.hsc b/src/Plugins/Kbd.hsc index 59854f5..c582634 100644 --- a/src/Plugins/Kbd.hsc +++ b/src/Plugins/Kbd.hsc @@ -380,7 +380,7 @@ instance Exec Kbd where          dpy <- openDisplay ""          -- initial set of layout -        cb =<< (getKbdLay dpy opts) +        cb =<< getKbdLay dpy opts          -- enable listing for          -- group changes @@ -391,7 +391,7 @@ instance Exec Kbd where          allocaXEvent $ \e -> forever $ do              nextEvent' dpy e              _ <- getEvent e -            cb =<< (getKbdLay dpy opts) +            cb =<< getKbdLay dpy opts          closeDisplay dpy          return () diff --git a/src/Plugins/Monitors.hs b/src/Plugins/Monitors.hs index 84eceb2..43068be 100644 --- a/src/Plugins/Monitors.hs +++ b/src/Plugins/Monitors.hs @@ -3,7 +3,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Xmobar.Plugins.Monitors --- Copyright   :  (c) 2010, 2011, 2012, 2013 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2017 Jose Antonio Ortega Ruiz  --                (c) 2007-10 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -114,15 +114,15 @@ instance Exec Monitors where      alias (Cpu _ _) = "cpu"      alias (MultiCpu _ _) = "multicpu"      alias (Battery _ _) = "battery" -    alias (BatteryP {})= "battery" +    alias BatteryP {} = "battery"      alias (BatteryN _ _ _ a)= a      alias (Brightness _ _) = "bright"      alias (CpuFreq _ _) = "cpufreq"      alias (TopProc _ _) = "top"      alias (TopMem _ _) = "topmem"      alias (CoreTemp _ _) = "coretemp" -    alias (DiskU {}) = "disku" -    alias (DiskIO {}) = "diskio" +    alias DiskU {} = "disku" +    alias DiskIO {} = "diskio"      alias (Uptime _ _) = "uptime"      alias (CatInt n _ _ _) = "cat" ++ show n  #ifdef UVMETER diff --git a/src/Plugins/Monitors/Common.hs b/src/Plugins/Monitors/Common.hs index ef509e9..5f088cf 100644 --- a/src/Plugins/Monitors/Common.hs +++ b/src/Plugins/Monitors/Common.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Common --- Copyright   :  (c) 2010, 2011, 2013, 2016 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2010, 2011, 2013, 2016, 2017 Jose Antonio Ortega Ruiz  --                (c) 2007-2010 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -296,7 +296,7 @@ templateStringParser =         ; return (s, com, ss)         }      where -      nonPlaceHolder = liftM concat . many $ +      nonPlaceHolder = fmap concat . many $                         many1 (noneOf "<") <|> colorSpec <|> iconSpec  -- | Recognizes color specification and returns it unchanged @@ -365,7 +365,7 @@ type IconPattern = Int -> String  parseIconPattern :: String -> IconPattern  parseIconPattern path =      let spl = splitOnPercent path -    in \i -> concat $ intersperse (show i) spl +    in \i -> intercalate (show i) spl    where splitOnPercent [] = [[]]          splitOnPercent ('%':'%':xs) = [] : splitOnPercent xs          splitOnPercent (x:xs) = @@ -466,7 +466,7 @@ showPercentsWithColors fs =       zipWithM (showWithColors . const) fstrs (map (*100) fs)  showPercentWithColors :: Float -> Monitor String -showPercentWithColors f = liftM head $ showPercentsWithColors [f] +showPercentWithColors f = fmap head $ showPercentsWithColors [f]  showPercentBar :: Float -> Float -> Monitor String  showPercentBar v x = do @@ -495,37 +495,22 @@ showVerticalBar v x = colorizeString v [convert $ 100 * x]            | otherwise = chr t            where t = 9600 + (round val `div` 12) -showLogBar :: Float -> Float -> Monitor String -showLogBar f v = -  let intConfig c = fromIntegral `fmap` getConfigValue c -  in do -    h <- intConfig high -    l <- intConfig low -    bw <- intConfig barWidth -    let [ll, hh] = sort [l, h] -        choose x | x == 0.0 = 0 -                 | x <= ll = 1 / bw -                 | otherwise = f + logBase 2 (x / hh) / bw -    showPercentBar v $ choose v - -showLogVBar :: Float -> Float -> Monitor String -showLogVBar f v = do +logScaling :: Float -> Float -> Monitor Float +logScaling f v = do    h <- fromIntegral `fmap` getConfigValue high    l <- fromIntegral `fmap` getConfigValue low    bw <- fromIntegral `fmap` getConfigValue barWidth    let [ll, hh] = sort [l, h] -      choose x | x == 0.0 = 0 +      scaled x | x == 0.0 = 0                 | x <= ll = 1 / bw                 | otherwise = f + logBase 2 (x / hh) / bw -  showVerticalBar v $ choose v +  return $ scaled v + +showLogBar :: Float -> Float -> Monitor String +showLogBar f v = logScaling f v >>= showPercentBar v + +showLogVBar :: Float -> Float -> Monitor String +showLogVBar f v = logScaling f v >>= showPercentBar v  showLogIconPattern :: Maybe IconPattern -> Float -> Float -> Monitor String -showLogIconPattern str f v = do -  h <- fromIntegral `fmap` getConfigValue high -  l <- fromIntegral `fmap` getConfigValue low -  bw <- fromIntegral `fmap` getConfigValue barWidth -  let [ll, hh] = sort [l, h] -      choose x | x == 0.0 = 0 -               | x <= ll = 1 / bw -               | otherwise = f + logBase 2 (x / hh) / bw -  showIconPattern str $ choose v +showLogIconPattern str f v = logScaling f v >>= showIconPattern str diff --git a/src/Plugins/Monitors/CoreCommon.hs b/src/Plugins/Monitors/CoreCommon.hs index 943f491..2c10c70 100644 --- a/src/Plugins/Monitors/CoreCommon.hs +++ b/src/Plugins/Monitors/CoreCommon.hs @@ -29,7 +29,7 @@ checkedDataRetrieval :: (Ord a, Num a)                       => String -> [[String]] -> Maybe (String, String -> Int)                       -> (Double -> a) -> (a -> String) -> Monitor String  checkedDataRetrieval msg paths lbl trans fmt = -  liftM (fromMaybe msg . listToMaybe . catMaybes) $ +  fmap (fromMaybe msg . listToMaybe . catMaybes) $      mapM (\p -> retrieveData p lbl trans fmt) paths  retrieveData :: (Ord a, Num a) @@ -127,7 +127,7 @@ findFilesAndLabel path lbl  =  catMaybes  -- | Function to read the contents of the given file(s)  readFiles :: (String, Either Int (String, String -> Int))            -> Monitor (Int, String) -readFiles (fval, flbl) = (,) <$> either return (\(f, ex) -> liftM ex +readFiles (fval, flbl) = (,) <$> either return (\(f, ex) -> fmap ex                                                              $ io $ readFile f) flbl                               <*> io (readFile fval) diff --git a/src/Plugins/Monitors/Cpu.hs b/src/Plugins/Monitors/Cpu.hs index 7fed989..0dba92a 100644 --- a/src/Plugins/Monitors/Cpu.hs +++ b/src/Plugins/Monitors/Cpu.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Cpu --- Copyright   :  (c) 2011 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2011, 2017 Jose Antonio Ortega Ruiz  --                (c) 2007-2010 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -20,7 +20,7 @@ import qualified Data.ByteString.Lazy.Char8 as B  import Data.IORef (IORef, newIORef, readIORef, writeIORef)  import System.Console.GetOpt -data CpuOpts = CpuOpts +newtype CpuOpts = CpuOpts    { loadIconPattern :: Maybe IconPattern    } diff --git a/src/Plugins/Monitors/Mpris.hs b/src/Plugins/Monitors/Mpris.hs index 200e9f7..0228c8e 100644 --- a/src/Plugins/Monitors/Mpris.hs +++ b/src/Plugins/Monitors/Mpris.hs @@ -78,6 +78,7 @@ mprisConfig = mkMConfig "<artist> - <title>"                  , "title", "tracknumber" , "composer", "genre"                  ] +{-# NOINLINE dbusClient #-}  dbusClient :: DC.Client  dbusClient = unsafePerformIO DC.connectSession @@ -106,7 +107,7 @@ unpackMetadata xs =                   TypeVariant -> unpack $ fromVar v                   TypeStructure _ ->                     let x = structureItems (fromVar v) in -                     if x == [] then [] else unpack (head x) +                     if null x then [] else unpack (head x)                   _ -> []  getMetadata :: (MprisVersion a) => a -> DC.Client -> String -> IO [(String, Variant)] @@ -141,5 +142,5 @@ makeList version md = map getStr (fieldsList version) where                                             _ -> (show::Int64 -> String) num                              TypeArray TypeString ->                                let x = arrayItems (fromVar v) in -                                if x == [] then "" else fromVar (head x) +                                if null x then "" else fromVar (head x)                              _ -> "" diff --git a/src/Plugins/Monitors/MultiCpu.hs b/src/Plugins/Monitors/MultiCpu.hs index f0cdec4..b290690 100644 --- a/src/Plugins/Monitors/MultiCpu.hs +++ b/src/Plugins/Monitors/MultiCpu.hs @@ -96,10 +96,10 @@ formatCpu opts i xs                        return (b:h:d:ps)    where tryString            | i == 0 = loadIconPattern opts -          | i <= length (loadIconPatterns opts) = Just $ (loadIconPatterns opts) !! (i - 1) +          | i <= length (loadIconPatterns opts) = Just $ loadIconPatterns opts !! (i - 1)            | otherwise = Nothing -splitEvery :: (Eq a) => Int -> [a] -> [[a]] +splitEvery :: Int -> [a] -> [[a]]  splitEvery n = unfoldr (\x -> if null x then Nothing else Just $ splitAt n x)  groupData :: [String] -> [[String]] diff --git a/src/Plugins/Monitors/Net.hs b/src/Plugins/Monitors/Net.hs index 7df8889..a8c2951 100644 --- a/src/Plugins/Monitors/Net.hs +++ b/src/Plugins/Monitors/Net.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Net --- Copyright   :  (c) 2011, 2012, 2013, 2014 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017 Jose Antonio Ortega Ruiz  --                (c) 2007-2010 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -82,8 +82,8 @@ instance Ord num => Ord (NetDev num) where      compare NA _               = LT      compare _  NA              = GT      compare (NI _) (NI _)      = EQ -    compare (NI _) (ND {})     = LT -    compare (ND {}) (NI _)     = GT +    compare (NI _) ND {}       = LT +    compare ND {} (NI _)     = GT      compare (ND _ x1 y1) (ND _ x2 y2) =          if downcmp /= EQ             then downcmp @@ -189,7 +189,7 @@ runNets refs argv = do    dev <- io $ parseActive refs    opts <- io $ parseOpts argv    printNet opts dev -    where parseActive refs' = liftM selectActive (parseNets refs')  +    where parseActive refs' = fmap selectActive (parseNets refs')            selectActive = maximum  startNet :: String -> [String] -> Int -> (String -> IO ()) -> IO () diff --git a/src/Plugins/Monitors/Thermal.hs b/src/Plugins/Monitors/Thermal.hs index 6013511..5a97152 100644 --- a/src/Plugins/Monitors/Thermal.hs +++ b/src/Plugins/Monitors/Thermal.hs @@ -14,7 +14,6 @@  module Plugins.Monitors.Thermal where -import Control.Monad (liftM)  import qualified Data.ByteString.Lazy.Char8 as B  import Plugins.Monitors.Common  import System.Posix.Files (fileExist) @@ -34,8 +33,7 @@ runThermal args = do          file = "/proc/acpi/thermal_zone/" ++ zone ++ "/temperature"      exists <- io $ fileExist file      if exists -        then do number <- io $ liftM ((read :: String -> Int) . stringParser (1, 0)) (B.readFile file) +        then do number <- io $ fmap ((read :: String -> Int) . stringParser (1, 0)) (B.readFile file)                  thermal <- showWithColors show number                  parseTemplate [  thermal ]          else return $ "Thermal (" ++ zone ++ "): N/A" - diff --git a/src/Plugins/Monitors/UVMeter.hs b/src/Plugins/Monitors/UVMeter.hs index 5fa0b82..b0f5ac3 100644 --- a/src/Plugins/Monitors/UVMeter.hs +++ b/src/Plugins/Monitors/UVMeter.hs @@ -31,7 +31,7 @@ uvConfig = mkMConfig         ["station"                               -- available replacements         ] -data UvInfo = UV { index :: String } +newtype UvInfo = UV { index :: String }      deriving (Show)  uvURL :: String @@ -86,7 +86,7 @@ runUVMeter (s:_) = do  type AttrName  = String  type AttrValue = String -data Attribute = Attribute (AttrName, AttrValue) +newtype Attribute = Attribute (AttrName, AttrValue)      deriving (Show)  data XML = Element String [Attribute] [XML] diff --git a/src/Plugins/Monitors/Wireless.hs b/src/Plugins/Monitors/Wireless.hs index b1e3c7e..26ded2d 100644 --- a/src/Plugins/Monitors/Wireless.hs +++ b/src/Plugins/Monitors/Wireless.hs @@ -19,7 +19,7 @@ import System.Console.GetOpt  import Plugins.Monitors.Common  import IWlib -data WirelessOpts = WirelessOpts +newtype WirelessOpts = WirelessOpts    { qualityIconPattern :: Maybe IconPattern    } diff --git a/src/Window.hs b/src/Window.hs index 3c3981e..11ea82e 100644 --- a/src/Window.hs +++ b/src/Window.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Window --- Copyright   :  (c) 2011-16 Jose A. Ortega Ruiz +-- Copyright   :  (c) 2011-17 Jose A. Ortega Ruiz  --             :  (c) 2012 Jochen Keil  -- License     :  BSD-style (see LICENSE)  -- @@ -197,7 +197,7 @@ showWindow r c d w = do  isMapped :: Display -> Window -> IO Bool  isMapped d w = ism <$> getWindowAttributes d w -    where ism (WindowAttributes { wa_map_state = wms }) = wms /= waIsUnmapped +    where ism WindowAttributes { wa_map_state = wms } = wms /= waIsUnmapped  borderOffset :: (Integral a) => Border -> Int -> a  borderOffset b lw = diff --git a/src/XUtil.hsc b/src/XUtil.hsc index e63c9cb..9063147 100644 --- a/src/XUtil.hsc +++ b/src/XUtil.hsc @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  XUtil --- Copyright   :  (C) 2011, 2012, 2013, 2014, 2015 Jose Antonio Ortega Ruiz +-- Copyright   :  (C) 2011, 2012, 2013, 2014, 2015, 2017 Jose Antonio Ortega Ruiz  --                (C) 2007 Andrea Rossato  -- License     :  BSD3  -- @@ -11,8 +11,6 @@  --  ----------------------------------------------------------------------------- -{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-} -  module XUtil      ( XFont      , initFont @@ -130,8 +128,7 @@ initXftFont :: Display -> String -> IO [AXftFont]  initXftFont d s = do    setupLocale    let fontNames = wordsBy (== ',') (drop 4 s) -  fonts <- mapM openFont fontNames -  return fonts +  mapM openFont fontNames    where      openFont fontName = do          f <- openAXftFont d (defaultScreenOfDisplay d) fontName @@ -160,7 +157,7 @@ textExtents (Core fs) s = do  textExtents (Utf8 fs) s = do    let (_,rl)  = wcTextExtents fs s        ascent  = fi $ - (rect_y rl) -      descent = fi $ rect_height rl + (fi $ rect_y rl) +      descent = fi $ rect_height rl + fi (rect_y rl)    return (ascent, descent)  #ifdef XFT  textExtents (Xft xftfonts) _ = do @@ -185,8 +182,8 @@ printString d p (Utf8 fs) gc fc bc x y s a =        io $ wcDrawImageString d p fs gc x y s  #ifdef XFT -printString dpy drw fs@(Xft fonts) _ fc bc x y s al = do -  withDrawingColors dpy drw fc bc $ \draw -> \fc' -> \bc' -> do +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 diff --git a/src/Xmobar.hs b/src/Xmobar.hs index 5e44f62..c6e16a6 100644 --- a/src/Xmobar.hs +++ b/src/Xmobar.hs @@ -2,7 +2,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Xmobar --- Copyright   :  (c) 2011, 2012, 2013, 2014, 2015 Jose Antonio Ortega Ruiz +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2015, 2017 Jose Antonio Ortega Ruiz  --                (c) 2007 Andrea Rossato  -- License     :  BSD-style (see LICENSE)  -- @@ -107,7 +107,7 @@ startLoop xcfg@(XConf _ _ w _ _ _) sig vs = do      eventLoop tv xcfg [] sig    where      handler thing (SomeException e) = -      void $ putStrLn ("Thread " ++ thing ++ " failed: " ++ (show e)) +      void $ putStrLn ("Thread " ++ thing ++ " failed: " ++ show e)      -- Reacts on events from X      eventer signal =        allocaXEvent $ \e -> do | 
