diff options
| author | jao <jao@gnu.org> | 2024-03-30 18:26:01 +0000 | 
|---|---|---|
| committer | jao <jao@gnu.org> | 2024-03-30 18:26:01 +0000 | 
| commit | 30d226ba5eca8847775d03403367dee1f1e3dcfc (patch) | |
| tree | b62d0f7f176f9f2b58d66866c3c6afb581334bd6 /src/Xmobar/Plugins/Monitors | |
| parent | 3f4ae1034fe7575df05c59dd0c357fd448198594 (diff) | |
| download | xmobar-30d226ba5eca8847775d03403367dee1f1e3dcfc.tar.gz xmobar-30d226ba5eca8847775d03403367dee1f1e3dcfc.tar.bz2 | |
fix for unmet pattern matches warnings (clean build)
Diffstat (limited to 'src/Xmobar/Plugins/Monitors')
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Alsa.hs | 6 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Common/Output.hs | 20 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Disk.hs | 8 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Mem/Linux.hs | 10 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net/Linux.hs | 5 | 
5 files changed, 29 insertions, 20 deletions
| diff --git a/src/Xmobar/Plugins/Monitors/Alsa.hs b/src/Xmobar/Plugins/Monitors/Alsa.hs index dfc7329..8d02931 100644 --- a/src/Xmobar/Plugins/Monitors/Alsa.hs +++ b/src/Xmobar/Plugins/Monitors/Alsa.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Alsa --- Copyright   :  (c) 2018 Daniel Schüssler +-- Copyright   :  (c) 2018, 2024 Daniel Schüssler  -- License     :  BSD-style (see LICENSE)  --  -- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> @@ -25,6 +25,7 @@ import Control.Concurrent.Async  import Control.Exception  import Control.Monad  import Data.IORef +import Data.Maybe (fromJust)  import Data.Time.Clock  import Xmobar.Plugins.Monitors.Common  import qualified Xmobar.Plugins.Monitors.Volume as Volume; @@ -129,7 +130,8 @@ alsaReaderThread mixerName alsaCtlPath outputCallback mvar =                        {std_out = CreatePipe}        runAlsaOnce = -        withCreateProcess createProc $ \_ (Just alsaOut) _ _ -> do +        withCreateProcess createProc $ \_ out _ _ -> do +          let alsaOut = fromJust out            hSetBuffering alsaOut LineBuffering            tryPutMVar mvar () -- Refresh immediately after restarting alsactl diff --git a/src/Xmobar/Plugins/Monitors/Common/Output.hs b/src/Xmobar/Plugins/Monitors/Common/Output.hs index 2d0e194..c0a00ab 100644 --- a/src/Xmobar/Plugins/Monitors/Common/Output.hs +++ b/src/Xmobar/Plugins/Monitors/Common/Output.hs @@ -3,7 +3,7 @@  ------------------------------------------------------------------------------  -- |  -- Module: Xmobar.Plugins.Monitors.Strings --- Copyright: (c) 2018, 2019, 2020, 2022 Jose Antonio Ortega Ruiz +-- Copyright: (c) 2018, 2019, 2020, 2022, 2024 Jose Antonio Ortega Ruiz  -- License: BSD3-style (see LICENSE)  --  -- Maintainer: jao@gnu.org @@ -88,9 +88,9 @@ pShowWithColors p f x = do  pColorizeString :: (Num a, Ord a, MonadIO m) => MonitorConfig -> a -> String -> m String  pColorizeString p x s = do      let col = pSetColor p s -        [ll,hh] = map fromIntegral $ sort [pLow p, pHigh p] -- consider high < low -    pure $ head $ [col pHighColor   | x > hh ] ++ -                  [col pNormalColor | x > ll ] ++ +        cols = map fromIntegral $ sort [pLow p, pHigh p] -- consider high < low +    pure $ head $ [col pHighColor   | x > (cols !! 1) ] ++ +                  [col pNormalColor | x > head cols ] ++                    [col pLowColor    | True]  pSetColor :: MonitorConfig -> String -> PSelector (Maybe String) -> String @@ -197,9 +197,9 @@ colorizeString x s = do      h <- getConfigValue high      l <- getConfigValue low      let col = setColor s -        [ll,hh] = map fromIntegral $ sort [l, h] -- consider high < low -    head $ [col highColor   | x > hh ] ++ -           [col normalColor | x > ll ] ++ +        cols = map fromIntegral $ sort [l, h] -- consider high < low +    head $ [col highColor   | x > cols !! 1 ] ++ +           [col normalColor | x > head cols ] ++             [col lowColor    | True]  showWithColors :: (Num a, Ord a) => (a -> String) -> a -> Monitor String @@ -260,11 +260,11 @@ 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] +  let ws = sort [l, h]        bw' = if bw > 0 then bw else 10        scaled x | x == 0.0 = 0 -               | x <= ll = 1 / bw' -               | otherwise = f + logBase 2 (x / hh) / bw' +               | x <= head ws = 1 / bw' +               | otherwise = f + logBase 2 (x / ws !! 1) / bw'    return $ scaled v  showLogBar :: Float -> Float -> Monitor String diff --git a/src/Xmobar/Plugins/Monitors/Disk.hs b/src/Xmobar/Plugins/Monitors/Disk.hs index 47d1eac..95bcff6 100644 --- a/src/Xmobar/Plugins/Monitors/Disk.hs +++ b/src/Xmobar/Plugins/Monitors/Disk.hs @@ -1,7 +1,7 @@  -----------------------------------------------------------------------------  -- |  -- Module      :  Plugins.Monitors.Disk --- Copyright   :  (c) 2010, 2011, 2012, 2014, 2018, 2019 Jose A Ortega Ruiz +-- Copyright   :  (c) 2010-2012, 2014, 2018, 2019, 2024 Jose A Ortega Ruiz  -- License     :  BSD-style (see LICENSE)  --  -- Maintainer  :  Jose A Ortega Ruiz <jao@gnu.org> @@ -131,10 +131,9 @@ startDiskIO disks args rate cb = do    runM args diskIOConfig (runDiskIO dref disks) rate cb  runDiskU' :: DiskUOpts -> String -> [Integer] -> Monitor String -runDiskU' opts tmp stat = do +runDiskU' opts tmp (total:free:diff:_) = do    setConfigValue tmp template -  let [total, free, diff] = stat -      strs = map sizeToStr [free, diff] +  let strs = map sizeToStr [free, diff]        freep = if total > 0 then free * 100 `div` total else 0        fr = fromIntegral freep / 100    s <- zipWithM showWithColors' strs [freep, 100 - freep] @@ -146,6 +145,7 @@ runDiskU' opts tmp stat = do    uvb <- showVerticalBar (fromIntegral $ 100 - freep) (1 - fr)    uipat <- showIconPattern (usedIconPattern opts) (1 - fr)    parseTemplate $ [sizeToStr total] ++ s ++ sp ++ [fb,fvb,fipat,ub,uvb,uipat] +runDiskU' _ _ _ = return ""  runDiskU :: [(String, String)] -> [String] -> Monitor String  runDiskU disks argv = do diff --git a/src/Xmobar/Plugins/Monitors/Mem/Linux.hs b/src/Xmobar/Plugins/Monitors/Mem/Linux.hs index 79dcc9d..7a81c6d 100644 --- a/src/Xmobar/Plugins/Monitors/Mem/Linux.hs +++ b/src/Xmobar/Plugins/Monitors/Mem/Linux.hs @@ -25,9 +25,13 @@ parseMEM =         let content = map words $ take 8 $ lines file             info = M.fromList $ map (               \line -> (head line, (read $ line !! 1 :: Float) / 1024)) content -           [total, free, buffer, cache] = -             map (info M.!) ["MemTotal:", "MemFree:", "Buffers:", "Cached:"] -           available = M.findWithDefault (free + buffer + cache) "MemAvailable:" info +           info' x = info M.! (x ++ ":") +           total = info' "MemTotal" +           free = info' "MemFree" +           buffer = info' "Buffers" +           cache = info' "Cached" +           available = +             M.findWithDefault (free + buffer + cache) "MemAvailable:" info             used = total - available             usedratio = used / total             freeratio = free / total diff --git a/src/Xmobar/Plugins/Monitors/Net/Linux.hs b/src/Xmobar/Plugins/Monitors/Net/Linux.hs index 9306497..f9cbc28 100644 --- a/src/Xmobar/Plugins/Monitors/Net/Linux.hs +++ b/src/Xmobar/Plugins/Monitors/Net/Linux.hs @@ -47,7 +47,10 @@ isUp d = flip catchIOError (const $ return False) $ do    return $! (head . B.lines) operstate `elem` ["up", "unknown"]  readNetDev :: [String] -> IO NetDevRawTotal -readNetDev ~[d, x, y] = do +readNetDev ds = do +  let (d, x, y) = case ds of +        d':x':y':_ -> (d', x', y') +        _          -> ("", "", "")    up <- unsafeInterleaveIO $ isUp d    return $ N d (if up then ND (r x) (r y) else NI)      where r s | s == "" = 0 | 
