summaryrefslogtreecommitdiffhomepage
path: root/src/Plugins/Monitors
diff options
context:
space:
mode:
Diffstat (limited to 'src/Plugins/Monitors')
-rw-r--r--src/Plugins/Monitors/Common.hs45
-rw-r--r--src/Plugins/Monitors/CoreCommon.hs4
-rw-r--r--src/Plugins/Monitors/Cpu.hs4
-rw-r--r--src/Plugins/Monitors/Mpris.hs5
-rw-r--r--src/Plugins/Monitors/MultiCpu.hs4
-rw-r--r--src/Plugins/Monitors/Net.hs8
-rw-r--r--src/Plugins/Monitors/Thermal.hs4
-rw-r--r--src/Plugins/Monitors/UVMeter.hs4
-rw-r--r--src/Plugins/Monitors/Wireless.hs2
9 files changed, 32 insertions, 48 deletions
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
}