diff options
Diffstat (limited to 'src/Xmobar/Plugins/Monitors')
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Batt.hs | 186 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Batt/Common.hs | 57 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Batt/FreeBSD.hs | 46 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Batt/Linux.hs | 130 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Cpu.hs | 102 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Cpu/Common.hs | 25 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Cpu/FreeBSD.hs | 49 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Cpu/Linux.hs | 61 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Mem.hs | 61 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Mem/FreeBSD.hs | 45 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Mem/Linux.hs | 33 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net.hs | 171 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net.hsc | 334 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net/Common.hs | 50 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net/FreeBSD.hsc | 118 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net/Linux.hs | 69 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Swap.hs | 55 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hs | 41 | ||||
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Swap/Linux.hs | 35 | 
19 files changed, 966 insertions, 702 deletions
| diff --git a/src/Xmobar/Plugins/Monitors/Batt.hs b/src/Xmobar/Plugins/Monitors/Batt.hs index af932ae..52600d8 100644 --- a/src/Xmobar/Plugins/Monitors/Batt.hs +++ b/src/Xmobar/Plugins/Monitors/Batt.hs @@ -17,44 +17,18 @@  module Xmobar.Plugins.Monitors.Batt ( battConfig, runBatt, runBatt' ) where -import System.Process (system) -import Control.Monad (void, unless) +import Xmobar.Plugins.Monitors.Batt.Common (BattOpts(..) +                                           , Result(..) +                                           , Status(..))  import Xmobar.Plugins.Monitors.Common -import Control.Exception (SomeException, handle) -import System.FilePath ((</>)) -import System.IO (IOMode(ReadMode), hGetLine, withFile) -import System.Posix.Files (fileExist) -#ifdef FREEBSD -import System.BSD.Sysctl (sysctlReadInt) -#endif  import System.Console.GetOpt -import Data.List (sort, sortBy, group) -import Data.Maybe (fromMaybe) -import Data.Ord (comparing) -import Text.Read (readMaybe) -data BattOpts = BattOpts -  { onString :: String -  , offString :: String -  , idleString :: String -  , posColor :: Maybe String -  , lowWColor :: Maybe String -  , mediumWColor :: Maybe String -  , highWColor :: Maybe String -  , lowThreshold :: Float -  , highThreshold :: Float -  , onLowAction :: Maybe String -  , actionThreshold :: Float -  , onlineFile :: FilePath -  , scale :: Float -  , onIconPattern :: Maybe IconPattern -  , offIconPattern :: Maybe IconPattern -  , idleIconPattern :: Maybe IconPattern -  , lowString :: String -  , mediumString :: String -  , highString :: String -  , incPerc :: Bool -  } +#if defined(freebsd_HOST_OS) +import qualified Xmobar.Plugins.Monitors.Batt.FreeBSD as MB +#else +import qualified Xmobar.Plugins.Monitors.Batt.Linux as MB +#endif +  defaultOpts :: BattOpts  defaultOpts = BattOpts @@ -108,34 +82,11 @@ options =    , Option "" ["highs"] (ReqArg (\x o -> o { highString = x }) "") ""    ] -data Status = Charging | Discharging | Full | Idle | Unknown deriving (Read, Eq) --- Result perc watts time-seconds Status -data Result = Result Float Float Float Status | NA - -sysDir :: FilePath -sysDir = "/sys/class/power_supply" -  battConfig :: IO MConfig  battConfig = mkMConfig         "Batt: <watts>, <left>% / <timeleft>" -- template         ["leftbar", "leftvbar", "left", "acstatus", "timeleft", "watts", "leftipat"] -- replacements -data Files = Files -  { fFull :: String -  , fNow :: String -  , fVoltage :: String -  , fCurrent :: String -  , fStatus :: String -  , isCurrent :: Bool -  } | NoFiles deriving Eq - -data Battery = Battery -  { full :: !Float -  , now :: !Float -  , power :: !Float -  , status :: !String -  } -  data BatteryStatus    = BattHigh    | BattMedium @@ -153,130 +104,13 @@ getBattStatus charge opts   where     c = 100 * min 1 charge -maybeAlert :: BattOpts -> Float -> IO () -maybeAlert opts left = -  case onLowAction opts of -    Nothing -> return () -    Just x -> unless (isNaN left || actionThreshold opts < 100 * left) -                $ void $ system x - --- | FreeBSD battery query -#ifdef FREEBSD -battStatusFbsd :: Int -> Status -battStatusFbsd x -  | x == 1 = Discharging -  | x == 2 = Charging -  | otherwise = Unknown - -readBatteriesFbsd :: BattOpts -> IO Result -readBatteriesFbsd opts = do -  lf <- sysctlReadInt "hw.acpi.battery.life" -  rt <- sysctlReadInt "hw.acpi.battery.rate" -  tm <- sysctlReadInt "hw.acpi.battery.time" -  st <- sysctlReadInt "hw.acpi.battery.state" -  acline <- sysctlReadInt "hw.acpi.acline" -  let p = fromIntegral lf / 100 -      w = fromIntegral rt -      t = fromIntegral tm * 60 -      ac = acline == 1 -      -- battery full when rate is 0 and on ac. -      sts = if (w == 0 && ac) then Full else (battStatusFbsd $ fromIntegral st) -  unless ac (maybeAlert opts p) -  return (Result p w t sts) - -#else --- | query linux battery -safeFileExist :: String -> String -> IO Bool -safeFileExist d f = handle noErrors $ fileExist (d </> f) -  where noErrors = const (return False) :: SomeException -> IO Bool - -batteryFiles :: String -> IO Files -batteryFiles bat = -  do is_charge <- exists "charge_now" -     is_energy <- if is_charge then return False else exists "energy_now" -     is_power <- exists "power_now" -     plain <- exists (if is_charge then "charge_full" else "energy_full") -     let cf = if is_power then "power_now" else "current_now" -         sf = if plain then "" else "_design" -     return $ case (is_charge, is_energy) of -       (True, _) -> files "charge" cf sf is_power -       (_, True) -> files "energy" cf sf is_power -       _ -> NoFiles -  where prefix = sysDir </> bat -        exists = safeFileExist prefix -        files ch cf sf ip = Files { fFull = prefix </> ch ++ "_full" ++ sf -                                  , fNow = prefix </> ch ++ "_now" -                                  , fCurrent = prefix </> cf -                                  , fVoltage = prefix </> "voltage_now" -                                  , fStatus = prefix </> "status" -                                  , isCurrent = not ip} - -haveAc :: FilePath -> IO Bool -haveAc f = -  handle onError $ withFile (sysDir </> f) ReadMode (fmap (== "1") . hGetLine) -  where onError = const (return False) :: SomeException -> IO Bool - -readBattery :: Float -> Files -> IO Battery -readBattery _ NoFiles = return $ Battery 0 0 0 "Unknown" -readBattery sc files = -    do a <- grab $ fFull files -       b <- grab $ fNow files -       d <- grab $ fCurrent files -       s <- grabs $ fStatus files -       let sc' = if isCurrent files then sc / 10 else sc -           a' = max a b -- sometimes the reported max charge is lower than -       return $ Battery (3600 * a' / sc') -- wattseconds -                        (3600 * b / sc') -- wattseconds -                        (abs d / sc') -- watts -                        s -- string: Discharging/Charging/Full -    where grab f = handle onError $ withFile f ReadMode (fmap read . hGetLine) -          onError = const (return (-1)) :: SomeException -> IO Float -          grabs f = handle onError' $ withFile f ReadMode hGetLine -          onError' = const (return "Unknown") :: SomeException -> IO String - --- sortOn is only available starting at ghc 7.10 -sortOn :: Ord b => (a -> b) -> [a] -> [a] -sortOn f = -  map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x)) - -mostCommonDef :: Eq a => a -> [a] -> a -mostCommonDef x xs = head $ last $ [x] : sortOn length (group xs) - -readBatteriesLinux :: BattOpts -> [Files] -> IO Result -readBatteriesLinux opts bfs = -    do let bfs' = filter (/= NoFiles) bfs -       bats <- mapM (readBattery (scale opts)) (take 3 bfs') -       ac <- haveAc (onlineFile opts) -       let sign = if ac then 1 else -1 -           ft = sum (map full bats) -           left = if ft > 0 then sum (map now bats) / ft else 0 -           watts = sign * sum (map power bats) -           time = if watts == 0 then 0 else max 0 (sum $ map time' bats) -           mwatts = if watts == 0 then 1 else sign * watts -           time' b = (if ac then full b - now b else now b) / mwatts -           statuses :: [Status] -           statuses = map (fromMaybe Unknown . readMaybe) -                          (sort (map status bats)) -           acst = mostCommonDef Unknown $ filter (Unknown/=) statuses -           racst | acst /= Unknown = acst -                 | time == 0 = Idle -                 | ac = Charging -                 | otherwise = Discharging -       unless ac (maybeAlert opts left) -       return $ if isNaN left then NA else Result left watts time racst -#endif -  runBatt :: [String] -> Monitor String  runBatt = runBatt' ["BAT", "BAT0", "BAT1", "BAT2"]  runBatt' :: [String] -> [String] -> Monitor String  runBatt' bfs args = do    opts <- io $ parseOptsWith options defaultOpts args -#ifdef FREEBSD -  c <- io $ readBatteriesFbsd opts -#else -  c <- io $ readBatteriesLinux opts =<< mapM batteryFiles bfs -#endif +  c <- io $ MB.readBatteries opts bfs    formatResult c opts  formatResult :: Result -> BattOpts -> Monitor String diff --git a/src/Xmobar/Plugins/Monitors/Batt/Common.hs b/src/Xmobar/Plugins/Monitors/Batt/Common.hs new file mode 100644 index 0000000..3262b78 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Batt/Common.hs @@ -0,0 +1,57 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Batt.Common +-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2015, 2016, 2018, 2019 Jose A Ortega +--                (c) 2010 Andrea Rossato, Petr Rockai +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A battery monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Batt.Common (BattOpts(..) +                                           , Result(..) +                                           , Status(..) +                                           , maybeAlert) where + +import System.Process (system) +import Control.Monad (unless, void) +import Xmobar.Plugins.Monitors.Common + +data Status = Charging | Discharging | Full | Idle | Unknown deriving (Read, Eq) +-- Result perc watts time-seconds Status +data Result = Result Float Float Float Status | NA + +data BattOpts = BattOpts +  { onString :: String +  , offString :: String +  , idleString :: String +  , posColor :: Maybe String +  , lowWColor :: Maybe String +  , mediumWColor :: Maybe String +  , highWColor :: Maybe String +  , lowThreshold :: Float +  , highThreshold :: Float +  , onLowAction :: Maybe String +  , actionThreshold :: Float +  , onlineFile :: FilePath +  , scale :: Float +  , onIconPattern :: Maybe IconPattern +  , offIconPattern :: Maybe IconPattern +  , idleIconPattern :: Maybe IconPattern +  , lowString :: String +  , mediumString :: String +  , highString :: String +  , incPerc :: Bool +  } + +maybeAlert :: BattOpts -> Float -> IO () +maybeAlert opts left = +  case onLowAction opts of +    Nothing -> return () +    Just x -> unless (isNaN left || actionThreshold opts < 100 * left) +                $ void $ system x diff --git a/src/Xmobar/Plugins/Monitors/Batt/FreeBSD.hs b/src/Xmobar/Plugins/Monitors/Batt/FreeBSD.hs new file mode 100644 index 0000000..2bb8618 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Batt/FreeBSD.hs @@ -0,0 +1,46 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Batt.FreeBSD +-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2015, 2016, 2018, 2019 Jose A Ortega +--                (c) 2010 Andrea Rossato, Petr Rockai +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A battery monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Batt.FreeBSD (readBatteries) where + +import Xmobar.Plugins.Monitors.Batt.Common (BattOpts(..) +                                           , Result(..) +                                           , Status(..) +                                           , maybeAlert) + +import Control.Monad (unless) +import System.BSD.Sysctl (sysctlReadInt) + +battStatus :: Int -> Status +battStatus x +  | x == 1 = Discharging +  | x == 2 = Charging +  | otherwise = Unknown + +readBatteries :: BattOpts -> [String] -> IO Result +readBatteries opts _ = do +  lf <- sysctlReadInt "hw.acpi.battery.life" +  rt <- sysctlReadInt "hw.acpi.battery.rate" +  tm <- sysctlReadInt "hw.acpi.battery.time" +  st <- sysctlReadInt "hw.acpi.battery.state" +  acline <- sysctlReadInt "hw.acpi.acline" +  let p = fromIntegral lf / 100 +      w = fromIntegral rt +      t = fromIntegral tm * 60 +      ac = acline == 1 +      -- battery full when rate is 0 and on ac. +      sts = if w == 0 && ac then Full else battStatus $ fromIntegral st +  unless ac (maybeAlert opts p) +  return (Result p w t sts) diff --git a/src/Xmobar/Plugins/Monitors/Batt/Linux.hs b/src/Xmobar/Plugins/Monitors/Batt/Linux.hs new file mode 100644 index 0000000..454e7e9 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Batt/Linux.hs @@ -0,0 +1,130 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Batt.Linux +-- Copyright   :  (c) 2010, 2011, 2012, 2013, 2015, 2016, 2018, 2019 Jose A Ortega +--                (c) 2010 Andrea Rossato, Petr Rockai +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A battery monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Batt.Linux (readBatteries) where + +import Xmobar.Plugins.Monitors.Batt.Common (BattOpts(..) +                                           , Result(..) +                                           , Status(..) +                                           , maybeAlert) + +import Control.Monad (unless) +import Control.Exception (SomeException, handle) +import System.FilePath ((</>)) +import System.IO (IOMode(ReadMode), hGetLine, withFile) +import System.Posix.Files (fileExist) +import Data.List (sort, sortBy, group) +import Data.Maybe (fromMaybe) +import Data.Ord (comparing) +import Text.Read (readMaybe) + +data Files = Files +  { fFull :: String +  , fNow :: String +  , fVoltage :: String +  , fCurrent :: String +  , fStatus :: String +  , isCurrent :: Bool +  } | NoFiles deriving Eq + +data Battery = Battery +  { full :: !Float +  , now :: !Float +  , power :: !Float +  , status :: !String +  } + +sysDir :: FilePath +sysDir = "/sys/class/power_supply" + +safeFileExist :: String -> String -> IO Bool +safeFileExist d f = handle noErrors $ fileExist (d </> f) +  where noErrors = const (return False) :: SomeException -> IO Bool + +batteryFiles :: String -> IO Files +batteryFiles bat = +  do is_charge <- exists "charge_now" +     is_energy <- if is_charge then return False else exists "energy_now" +     is_power <- exists "power_now" +     plain <- exists (if is_charge then "charge_full" else "energy_full") +     let cf = if is_power then "power_now" else "current_now" +         sf = if plain then "" else "_design" +     return $ case (is_charge, is_energy) of +       (True, _) -> files "charge" cf sf is_power +       (_, True) -> files "energy" cf sf is_power +       _ -> NoFiles +  where prefix = sysDir </> bat +        exists = safeFileExist prefix +        files ch cf sf ip = Files { fFull = prefix </> ch ++ "_full" ++ sf +                                  , fNow = prefix </> ch ++ "_now" +                                  , fCurrent = prefix </> cf +                                  , fVoltage = prefix </> "voltage_now" +                                  , fStatus = prefix </> "status" +                                  , isCurrent = not ip} + +haveAc :: FilePath -> IO Bool +haveAc f = +  handle onError $ withFile (sysDir </> f) ReadMode (fmap (== "1") . hGetLine) +  where onError = const (return False) :: SomeException -> IO Bool + +readBattery :: Float -> Files -> IO Battery +readBattery _ NoFiles = return $ Battery 0 0 0 "Unknown" +readBattery sc files = +    do a <- grab $ fFull files +       b <- grab $ fNow files +       d <- grab $ fCurrent files +       s <- grabs $ fStatus files +       let sc' = if isCurrent files then sc / 10 else sc +           a' = max a b -- sometimes the reported max charge is lower than +       return $ Battery (3600 * a' / sc') -- wattseconds +                        (3600 * b / sc') -- wattseconds +                        (abs d / sc') -- watts +                        s -- string: Discharging/Charging/Full +    where grab f = handle onError $ withFile f ReadMode (fmap read . hGetLine) +          onError = const (return (-1)) :: SomeException -> IO Float +          grabs f = handle onError' $ withFile f ReadMode hGetLine +          onError' = const (return "Unknown") :: SomeException -> IO String + +-- sortOn is only available starting at ghc 7.10 +sortOn :: Ord b => (a -> b) -> [a] -> [a] +sortOn f = +  map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x)) + +mostCommonDef :: Eq a => a -> [a] -> a +mostCommonDef x xs = head $ last $ [x] : sortOn length (group xs) + +readBatteries :: BattOpts -> [String] -> IO Result +readBatteries opts bfs = +    do bfs' <- mapM batteryFiles bfs +       let bfs'' = filter (/= NoFiles) bfs' +       bats <- mapM (readBattery (scale opts)) (take 3 bfs'') +       ac <- haveAc (onlineFile opts) +       let sign = if ac then 1 else -1 +           ft = sum (map full bats) +           left = if ft > 0 then sum (map now bats) / ft else 0 +           watts = sign * sum (map power bats) +           time = if watts == 0 then 0 else max 0 (sum $ map time' bats) +           mwatts = if watts == 0 then 1 else sign * watts +           time' b = (if ac then full b - now b else now b) / mwatts +           statuses :: [Status] +           statuses = map (fromMaybe Unknown . readMaybe) +                          (sort (map status bats)) +           acst = mostCommonDef Unknown $ filter (Unknown/=) statuses +           racst | acst /= Unknown = acst +                 | time == 0 = Idle +                 | ac = Charging +                 | otherwise = Discharging +       unless ac (maybeAlert opts left) +       return $ if isNaN left then NA else Result left watts time racst diff --git a/src/Xmobar/Plugins/Monitors/Cpu.hs b/src/Xmobar/Plugins/Monitors/Cpu.hs index cf1b1ec..d74e45c 100644 --- a/src/Xmobar/Plugins/Monitors/Cpu.hs +++ b/src/Xmobar/Plugins/Monitors/Cpu.hs @@ -20,22 +20,25 @@ module Xmobar.Plugins.Monitors.Cpu    ( startCpu    , runCpu    , cpuConfig -  , CpuDataRef +  , MC.CpuDataRef    , CpuOpts    , CpuArguments -  , parseCpu +  , MC.parseCpu    , getArguments    ) where  import Xmobar.Plugins.Monitors.Common -import qualified Data.ByteString.Lazy.Char8 as B -import Data.IORef (IORef, newIORef, readIORef, writeIORef) -#ifdef FREEBSD -import System.BSD.Sysctl (sysctlPeekArray) -#endif +import Data.IORef (newIORef)  import System.Console.GetOpt  import Xmobar.App.Timer (doEveryTenthSeconds)  import Control.Monad (void) +import Xmobar.Plugins.Monitors.Cpu.Common (CpuData(..)) + +#if defined(freebsd_HOST_OS) +import qualified Xmobar.Plugins.Monitors.Cpu.FreeBSD as MC +#else +import qualified Xmobar.Plugins.Monitors.Cpu.Linux as MC +#endif  newtype CpuOpts = CpuOpts    { loadIconPattern :: Maybe IconPattern @@ -94,83 +97,6 @@ cpuConfig =      , iowaitField      ] -data CpuData = CpuData { -      cpuUser :: !Float, -      cpuNice :: !Float, -      cpuSystem :: !Float, -      cpuIdle :: !Float, -      cpuIowait :: !Float, -      cpuTotal :: !Float -    } - -#ifdef FREEBSD --- kern.cp_time data from the previous iteration for computing the difference -type CpuDataRef = IORef [Word] - -cpuData :: IO [Word] -cpuData = sysctlPeekArray "kern.cp_time" :: IO [Word] - -parseCpu :: CpuDataRef -> IO CpuData -parseCpu cref = do -    prev <- readIORef cref -    curr <- cpuData -    writeIORef cref curr -    let diff = map fromIntegral $ zipWith (-) curr prev -        user = diff !! 0 -        nice = diff !! 1 -        system = diff !! 2 -        intr = diff !! 3 -        idle = diff !! 4 -        total = user + nice + system + intr + idle -    return CpuData -      { cpuUser = user/total -      , cpuNice = nice/total -      , cpuSystem = (system+intr)/total -      , cpuIdle = idle/total -      , cpuIowait = 0 -      , cpuTotal = user/total -      } -#else -type CpuDataRef = IORef [Int] - --- Details about the fields here: https://www.kernel.org/doc/Documentation/filesystems/proc.txt -cpuData :: IO [Int] -cpuData = cpuParser <$> B.readFile "/proc/stat" - -readInt :: B.ByteString -> Int -readInt bs = case B.readInt bs of -               Nothing -> 0 -               Just (i, _) -> i - -cpuParser :: B.ByteString -> [Int] -cpuParser = map readInt . tail . B.words . head . B.lines - -convertToCpuData :: [Float] -> CpuData -convertToCpuData (u:n:s:ie:iw:_) = -  CpuData -    { cpuUser = u -    , cpuNice = n -    , cpuSystem = s -    , cpuIdle = ie -    , cpuIowait = iw -    , cpuTotal = sum [u, n, s] -    } -convertToCpuData args = error $ "convertToCpuData: Unexpected list" <> show args - -parseCpu :: CpuDataRef -> IO CpuData -parseCpu cref = -    do a <- readIORef cref -       b <- cpuData -       writeIORef cref b -       let dif = zipWith (-) b a -           tot = fromIntegral $ sum dif -           safeDiv n = case tot of -                         0 -> 0 -                         v -> fromIntegral n / v -           percent = map safeDiv dif -       return $ convertToCpuData percent -#endif -  data Field = Field {        fieldName :: !String,        fieldCompute :: !ShouldCompute @@ -235,7 +161,7 @@ optimizeAllTemplate args@CpuArguments {..} =  data CpuArguments =    CpuArguments -    { cpuDataRef :: !CpuDataRef +    { cpuDataRef :: !MC.CpuDataRef      , cpuParams :: !MonitorConfig      , cpuArgs :: ![String]      , cpuOpts :: !CpuOpts @@ -247,9 +173,9 @@ data CpuArguments =  getArguments :: [String] -> IO CpuArguments  getArguments cpuArgs = do -  initCpuData <- cpuData +  initCpuData <- MC.cpuData    cpuDataRef <- newIORef initCpuData -  void $ parseCpu cpuDataRef +  void $ MC.parseCpu cpuDataRef    cpuParams <- computeMonitorConfig cpuArgs cpuConfig    cpuInputTemplate <- runTemplateParser cpuParams    cpuAllTemplate <- runExportParser (pExport cpuParams) @@ -270,7 +196,7 @@ getArguments cpuArgs = do  runCpu :: CpuArguments -> IO String  runCpu args@CpuArguments {..} = do -  cpuValue <- parseCpu cpuDataRef +  cpuValue <- MC.parseCpu cpuDataRef    temMonitorValues <- formatCpu args cpuValue    let templateInput =          TemplateInput diff --git a/src/Xmobar/Plugins/Monitors/Cpu/Common.hs b/src/Xmobar/Plugins/Monitors/Cpu/Common.hs new file mode 100644 index 0000000..ccec535 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Cpu/Common.hs @@ -0,0 +1,25 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Cpu.Common +-- Copyright   :  (c) 2011, 2017 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A cpu monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Cpu.Common (CpuData(..)) where + +data CpuData = CpuData { +      cpuUser :: !Float, +      cpuNice :: !Float, +      cpuSystem :: !Float, +      cpuIdle :: !Float, +      cpuIowait :: !Float, +      cpuTotal :: !Float +    } diff --git a/src/Xmobar/Plugins/Monitors/Cpu/FreeBSD.hs b/src/Xmobar/Plugins/Monitors/Cpu/FreeBSD.hs new file mode 100644 index 0000000..7cb711a --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Cpu/FreeBSD.hs @@ -0,0 +1,49 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Cpu.FreeBSD +-- Copyright   :  (c) 2011, 2017 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A cpu monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Cpu.FreeBSD (parseCpu +                                           , CpuDataRef +                                           , cpuData) where + +import Xmobar.Plugins.Monitors.Cpu.Common (CpuData(..)) +import Data.IORef (IORef, readIORef, writeIORef) +import System.BSD.Sysctl (sysctlPeekArray) + +-- kern.cp_time data from the previous iteration for computing the difference +type CpuDataRef = IORef [Word] + +cpuData :: IO [Word] +cpuData = sysctlPeekArray "kern.cp_time" :: IO [Word] + +parseCpu :: CpuDataRef -> IO CpuData +parseCpu cref = do +    prev <- readIORef cref +    curr <- cpuData +    writeIORef cref curr +    let diff = map fromIntegral $ zipWith (-) curr prev +        user = head diff +        nice = diff !! 1 +        system = diff !! 2 +        intr = diff !! 3 +        idle = diff !! 4 +        total = user + nice + system + intr + idle +    return CpuData +      { cpuUser = user/total +      , cpuNice = nice/total +      , cpuSystem = (system+intr)/total +      , cpuIdle = idle/total +      , cpuIowait = 0 +      , cpuTotal = user/total +      } diff --git a/src/Xmobar/Plugins/Monitors/Cpu/Linux.hs b/src/Xmobar/Plugins/Monitors/Cpu/Linux.hs new file mode 100644 index 0000000..39baea6 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Cpu/Linux.hs @@ -0,0 +1,61 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Cpu.Linux +-- Copyright   :  (c) 2011, 2017 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A cpu monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Cpu.Linux (parseCpu +                                         , CpuDataRef +                                         , cpuData) where + +import Xmobar.Plugins.Monitors.Cpu.Common (CpuData(..)) +import qualified Data.ByteString.Lazy.Char8 as B +import Data.IORef (IORef, readIORef, writeIORef) + +type CpuDataRef = IORef [Int] + +-- Details about the fields here: https://www.kernel.org/doc/Documentation/filesystems/proc.txt +cpuData :: IO [Int] +cpuData = cpuParser <$> B.readFile "/proc/stat" + +readInt :: B.ByteString -> Int +readInt bs = case B.readInt bs of +               Nothing -> 0 +               Just (i, _) -> i + +cpuParser :: B.ByteString -> [Int] +cpuParser = map readInt . tail . B.words . head . B.lines + +convertToCpuData :: [Float] -> CpuData +convertToCpuData (u:n:s:ie:iw:_) = +  CpuData +    { cpuUser = u +    , cpuNice = n +    , cpuSystem = s +    , cpuIdle = ie +    , cpuIowait = iw +    , cpuTotal = sum [u, n, s] +    } +convertToCpuData args = error $ "convertToCpuData: Unexpected list" <> show args + +parseCpu :: CpuDataRef -> IO CpuData +parseCpu cref = +    do a <- readIORef cref +       b <- cpuData +       writeIORef cref b +       let dif = zipWith (-) b a +           tot = fromIntegral $ sum dif +           safeDiv n = case tot of +                         0 -> 0 +                         v -> fromIntegral n / v +           percent = map safeDiv dif +       return $ convertToCpuData percent diff --git a/src/Xmobar/Plugins/Monitors/Mem.hs b/src/Xmobar/Plugins/Monitors/Mem.hs index 6f3e383..6a863ce 100644 --- a/src/Xmobar/Plugins/Monitors/Mem.hs +++ b/src/Xmobar/Plugins/Monitors/Mem.hs @@ -17,12 +17,14 @@ module Xmobar.Plugins.Monitors.Mem (memConfig, runMem, totalMem, usedMem) where  import Xmobar.Plugins.Monitors.Common  import System.Console.GetOpt -#ifdef FREEBSD -import System.BSD.Sysctl (sysctlReadUInt) + +#if defined(freebsd_HOST_OS) +import qualified Xmobar.Plugins.Monitors.Mem.FreeBSD as MM  #else -import qualified Data.Map as M +import qualified Xmobar.Plugins.Monitors.Mem.Linux as MM  #endif +  data MemOpts = MemOpts    { usedIconPattern :: Maybe IconPattern    , freeIconPattern :: Maybe IconPattern @@ -54,58 +56,11 @@ memConfig = mkMConfig          "usedratio", "freeratio", "availableratio",          "total", "free", "buffer", "cache", "available", "used"] -- available replacements -#ifdef FREEBSD -parseMEM :: IO [Float] -parseMEM = do stats <- mapM sysctlReadUInt [ -                "vm.stats.vm.v_page_size" -                , "vm.stats.vm.v_page_count" -                , "vm.stats.vm.v_free_count" -                , "vm.stats.vm.v_active_count" -                , "vm.stats.vm.v_inactive_count" -                , "vm.stats.vm.v_wire_count" -                , "vm.stats.vm.v_cache_count"] - -              let [ pagesize, totalpages, freepages, activepages, inactivepages, wiredpages, cachedpages ] = fmap fromIntegral stats -                  usedpages = activepages + wiredpages + cachedpages -                  availablepages = inactivepages + cachedpages + freepages -                  bufferedpages = activepages + inactivepages + wiredpages - -                  available = availablepages * pagesize -                  used = usedpages * pagesize -                  free = freepages * pagesize -                  cache = cachedpages * pagesize -                  buffer = bufferedpages * pagesize -                  total = totalpages * pagesize - -                  usedratio = usedpages / totalpages -                  freeratio = freepages / totalpages -                  availableratio = availablepages / totalpages - -              return [usedratio, freeratio, availableratio, total, free, buffer, cache, available, used] - -#else -fileMEM :: IO String -fileMEM = readFile "/proc/meminfo" - -parseMEM :: IO [Float] -parseMEM = -    do file <- fileMEM -       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 -           used = total - available -           usedratio = used / total -           freeratio = free / total -           availableratio = available / total -       return [usedratio, freeratio, availableratio, total, free, buffer, cache, available, used] -#endif -  totalMem :: IO Float -totalMem = fmap ((*1024) . (!!1)) parseMEM +totalMem = fmap ((*1024) . (!!1)) MM.parseMEM  usedMem :: IO Float -usedMem = fmap ((*1024) . (!!6)) parseMEM +usedMem = fmap ((*1024) . (!!6)) MM.parseMEM  formatMem :: MemOpts -> [Float] -> Monitor [String]  formatMem opts (r:fr:ar:xs) = @@ -120,7 +75,7 @@ formatMem _ _ = replicate 10 `fmap` getConfigValue naString  runMem :: [String] -> Monitor String  runMem argv = -    do m <- io parseMEM +    do m <- io MM.parseMEM         opts <- io $ parseOptsWith options defaultOpts argv         l <- formatMem opts m         parseTemplate l diff --git a/src/Xmobar/Plugins/Monitors/Mem/FreeBSD.hs b/src/Xmobar/Plugins/Monitors/Mem/FreeBSD.hs new file mode 100644 index 0000000..787cace --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Mem/FreeBSD.hs @@ -0,0 +1,45 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Mem.FreeBSD +-- Copyright   :  (c) Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A memory monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Mem.FreeBSD (parseMEM) where + +import System.BSD.Sysctl (sysctlReadUInt) + +parseMEM :: IO [Float] +parseMEM = do stats <- mapM sysctlReadUInt [ +                "vm.stats.vm.v_page_size" +                , "vm.stats.vm.v_page_count" +                , "vm.stats.vm.v_free_count" +                , "vm.stats.vm.v_active_count" +                , "vm.stats.vm.v_inactive_count" +                , "vm.stats.vm.v_wire_count" +                , "vm.stats.vm.v_cache_count"] + +              let [ pagesize, totalpages, freepages, activepages, inactivepages, wiredpages, cachedpages ] = fmap fromIntegral stats +                  usedpages = activepages + wiredpages + cachedpages +                  availablepages = inactivepages + cachedpages + freepages +                  bufferedpages = activepages + inactivepages + wiredpages + +                  available = availablepages * pagesize +                  used = usedpages * pagesize +                  free = freepages * pagesize +                  cache = cachedpages * pagesize +                  buffer = bufferedpages * pagesize +                  total = totalpages * pagesize + +                  usedratio = usedpages / totalpages +                  freeratio = freepages / totalpages +                  availableratio = availablepages / totalpages + +              return [usedratio, freeratio, availableratio, total, free, buffer, cache, available, used] diff --git a/src/Xmobar/Plugins/Monitors/Mem/Linux.hs b/src/Xmobar/Plugins/Monitors/Mem/Linux.hs new file mode 100644 index 0000000..9e48d22 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Mem/Linux.hs @@ -0,0 +1,33 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Mem.Linux +-- Copyright   :  (c) Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A memory monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Mem.Linux (parseMEM) where + +import qualified Data.Map as M + +fileMEM :: IO String +fileMEM = readFile "/proc/meminfo" + +parseMEM :: IO [Float] +parseMEM = +    do file <- fileMEM +       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 +           used = total - available +           usedratio = used / total +           freeratio = free / total +           availableratio = available / total +       return [usedratio, freeratio, availableratio, total, free, buffer, cache, available, used] diff --git a/src/Xmobar/Plugins/Monitors/Net.hs b/src/Xmobar/Plugins/Monitors/Net.hs new file mode 100644 index 0000000..23b3dc3 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Net.hs @@ -0,0 +1,171 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Net +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017, 2020 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A net device monitor for Xmobar +-- + +----------------------------------------------------------------------------- + +{-# LANGUAGE CPP #-} + +module Xmobar.Plugins.Monitors.Net ( +                        startNet +                      , startDynNet +                      ) where + +import Xmobar.Plugins.Monitors.Common +import Xmobar.Plugins.Monitors.Net.Common (NetDev(..), NetDevInfo(..), NetDevRate, NetDevRef) +import Data.IORef (newIORef, readIORef, writeIORef) +import Data.Time.Clock (getCurrentTime, diffUTCTime) +import System.Console.GetOpt + +#if defined(freebsd_HOST_OS) +import qualified Xmobar.Plugins.Monitors.Net.FreeBSD as MN +#else +import qualified Xmobar.Plugins.Monitors.Net.Linux as MN +#endif + +import Control.Monad (forM) + +type DevList = [String] + +parseDevList :: String -> DevList +parseDevList = splitOnComma +  where splitOnComma [] = [[]] +        splitOnComma (',':xs) = [] : splitOnComma xs +        splitOnComma (x:xs) = +           let rest = splitOnComma xs +           in (x : head rest) : tail rest + +data NetOpts = NetOpts +  { rxIconPattern :: Maybe IconPattern +  , txIconPattern :: Maybe IconPattern +  , onlyDevList :: Maybe DevList +  , upIndicator :: String +  } + +defaultOpts :: NetOpts +defaultOpts = NetOpts +  { rxIconPattern = Nothing +  , txIconPattern = Nothing +  , onlyDevList = Nothing +  , upIndicator = "+" +  } + +options :: [OptDescr (NetOpts -> NetOpts)] +options = +  [ Option "" ["rx-icon-pattern"] (ReqArg (\x o -> +     o { rxIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["tx-icon-pattern"] (ReqArg (\x o -> +     o { txIconPattern = Just $ parseIconPattern x }) "") "" +  , Option "" ["up"] (ReqArg (\x o -> o { upIndicator = x }) "") "" +  , Option "" ["devices"] (ReqArg (\x o -> +     o { onlyDevList = Just $ parseDevList x }) "") "" +  ] + +data UnitPerSec = Bs | KBs | MBs | GBs deriving (Eq,Enum,Ord) +data NetValue = NetValue Float UnitPerSec deriving (Eq,Show) + +instance Show UnitPerSec where +    show Bs  = "B/s" +    show KBs = "KB/s" +    show MBs = "MB/s" +    show GBs = "GB/s" + +netConfig :: IO MConfig +netConfig = mkMConfig +    "<dev>: <rx>KB|<tx>KB"      -- template +    ["dev", "rx", "tx", "rxbar", "rxvbar", "rxipat", "txbar", "txvbar", "txipat", "up"]     -- available replacements + +formatNet :: Maybe IconPattern -> Float -> Monitor (String, String, String, String) +formatNet mipat d = do +    s <- getConfigValue useSuffix +    dd <- getConfigValue decDigits +    let str True v = showDigits dd d' ++ show u +            where (NetValue d' u) = byteNetVal v +        str False v = showDigits dd $ v / 1024 +    b <- showLogBar 0.9 d +    vb <- showLogVBar 0.9 d +    ipat <- showLogIconPattern mipat 0.9 d +    x <- showWithColors (str s) d +    return (x, b, vb, ipat) + +printNet :: NetOpts -> NetDevRate -> Monitor String +printNet opts nd = +  case nd of +    N d (ND r t) -> do +        (rx, rb, rvb, ripat) <- formatNet (rxIconPattern opts) r +        (tx, tb, tvb, tipat) <- formatNet (txIconPattern opts) t +        parseTemplate [d,rx,tx,rb,rvb,ripat,tb,tvb,tipat, upIndicator opts] +    N _ NI -> return "" +    NA -> getConfigValue naString + +parseNet :: NetDevRef -> String -> IO NetDevRate +parseNet nref nd = do +  (n0, t0) <- readIORef nref +  n1 <- MN.findNetDev nd +  t1 <- getCurrentTime +  writeIORef nref (n1, t1) +  let scx = realToFrac (diffUTCTime t1 t0) +      scx' = if scx > 0 then scx else 1 +      rate da db = takeDigits 2 $ fromIntegral (db - da) / scx' +      diffRate (N d (ND ra ta)) (N _ (ND rb tb)) = N d (ND (rate ra rb) (rate ta tb)) +      diffRate (N d NI) _ = N d NI +      diffRate _ (N d NI) = N d NI +      diffRate _ _ = NA +  return $ diffRate n0 n1 + +runNet :: NetDevRef -> String -> [String] -> Monitor String +runNet nref i argv = do +  dev <- io $ parseNet nref i +  opts <- io $ parseOptsWith options defaultOpts argv +  printNet opts dev + +parseNets :: [(NetDevRef, String)] -> IO [NetDevRate] +parseNets = mapM $ uncurry parseNet + +runNets :: [(NetDevRef, String)] -> [String] -> Monitor String +runNets refs argv = do +  opts <- io $ parseOptsWith options defaultOpts argv +  dev <- io $ parseActive $ filterRefs opts refs +  printNet opts dev +    where parseActive refs' = fmap selectActive (parseNets refs') +          refInDevList opts' (_, refname') = case onlyDevList opts' of +            Just theList -> refname' `elem` theList +            Nothing -> True +          filterRefs opts' refs' = case filter (refInDevList opts') refs' of +            [] -> refs' +            xs -> xs +          selectActive = maximum + +startNet :: String -> [String] -> Int -> (String -> IO ()) -> IO () +startNet i a r cb = do +  t0 <- getCurrentTime +  nref <- newIORef (NA, t0) +  _ <- parseNet nref i +  runM a netConfig (runNet nref i) r cb + +startDynNet :: [String] -> Int -> (String -> IO ()) -> IO () +startDynNet a r cb = do +  devs <- MN.existingDevs +  refs <- forM devs $ \d -> do +            t <- getCurrentTime +            nref <- newIORef (NA, t) +            _ <- parseNet nref d +            return (nref, d) +  runM a netConfig (runNets refs) r cb + +byteNetVal :: Float -> NetValue +byteNetVal v +    | v < 1024**1 = NetValue v Bs +    | v < 1024**2 = NetValue (v/1024**1) KBs +    | v < 1024**3 = NetValue (v/1024**2) MBs +    | otherwise   = NetValue (v/1024**3) GBs diff --git a/src/Xmobar/Plugins/Monitors/Net.hsc b/src/Xmobar/Plugins/Monitors/Net.hsc deleted file mode 100644 index 53a1a9e..0000000 --- a/src/Xmobar/Plugins/Monitors/Net.hsc +++ /dev/null @@ -1,334 +0,0 @@ ------------------------------------------------------------------------------ --- | --- Module      :  Plugins.Monitors.Net --- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017, 2020 Jose Antonio Ortega Ruiz ---                (c) 2007-2010 Andrea Rossato --- License     :  BSD-style (see LICENSE) --- --- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> --- Stability   :  unstable --- Portability :  unportable --- --- A net device monitor for Xmobar --- - ------------------------------------------------------------------------------ - -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ForeignFunctionInterface #-} -{-# LANGUAGE CPP #-} -{-# LANGUAGE CApiFFI #-} - -module Xmobar.Plugins.Monitors.Net ( -                        startNet -                      , startDynNet -                      ) where - -import Xmobar.Plugins.Monitors.Common - -import Data.IORef (IORef, newIORef, readIORef, writeIORef) -import Data.Time.Clock (UTCTime, getCurrentTime, diffUTCTime) -import Data.Word (Word64) -import System.Console.GetOpt - -#ifdef FREEBSD -import Control.Monad (forM) -import Foreign (Int32, plusPtr) -import Foreign.C.Types (CUIntMax, CUChar) -import Foreign.C.String (peekCString) -import Foreign.ForeignPtr () -import Foreign.Storable (Storable, alignment, sizeOf, peek, poke) -import System.BSD.Sysctl (OID, sysctlPrepareOid, sysctlReadInt, sysctlPeek) -#else -import Control.Monad (forM, filterM) -import System.Directory (getDirectoryContents, doesFileExist) -import System.FilePath ((</>)) -import System.IO.Error (catchIOError) -import System.IO.Unsafe (unsafeInterleaveIO) - -import qualified Data.ByteString.Char8 as B -#endif - -type DevList = [String] - -parseDevList :: String -> DevList -parseDevList = splitOnComma -  where splitOnComma [] = [[]] -        splitOnComma (',':xs) = [] : splitOnComma xs -        splitOnComma (x:xs) = -           let rest = splitOnComma xs -           in (x : head rest) : tail rest - -data NetOpts = NetOpts -  { rxIconPattern :: Maybe IconPattern -  , txIconPattern :: Maybe IconPattern -  , onlyDevList :: Maybe DevList -  , upIndicator :: String -  } - -defaultOpts :: NetOpts -defaultOpts = NetOpts -  { rxIconPattern = Nothing -  , txIconPattern = Nothing -  , onlyDevList = Nothing -  , upIndicator = "+" -  } - -options :: [OptDescr (NetOpts -> NetOpts)] -options = -  [ Option "" ["rx-icon-pattern"] (ReqArg (\x o -> -     o { rxIconPattern = Just $ parseIconPattern x }) "") "" -  , Option "" ["tx-icon-pattern"] (ReqArg (\x o -> -     o { txIconPattern = Just $ parseIconPattern x }) "") "" -  , Option "" ["up"] (ReqArg (\x o -> o { upIndicator = x }) "") "" -  , Option "" ["devices"] (ReqArg (\x o -> -     o { onlyDevList = Just $ parseDevList x }) "") "" -  ] - -data UnitPerSec = Bs | KBs | MBs | GBs deriving (Eq,Enum,Ord) -data NetValue = NetValue Float UnitPerSec deriving (Eq,Show) - -instance Show UnitPerSec where -    show Bs  = "B/s" -    show KBs = "KB/s" -    show MBs = "MB/s" -    show GBs = "GB/s" - -data NetDev num = N String (NetDevInfo num) | NA deriving (Eq,Show,Read) -data NetDevInfo num = NI | ND num num deriving (Eq,Show,Read) - -type NetDevRawTotal = NetDev Word64 -type NetDevRate = NetDev Float - -type NetDevRef = IORef (NetDevRawTotal, UTCTime) - --- The more information available, the better. --- Note that names don't matter. Therefore, if only the names differ, --- a compare evaluates to EQ while (==) evaluates to False. -instance Ord num => Ord (NetDev num) where -    compare NA NA             = EQ -    compare NA _              = LT -    compare _  NA             = GT -    compare (N _ i1) (N _ i2) = i1 `compare` i2 - -instance Ord num => Ord (NetDevInfo num) where -    compare NI NI                 = EQ -    compare NI ND {}              = LT -    compare ND {} NI              = GT -    compare (ND x1 y1) (ND x2 y2) = x1 `compare` x2 <> y1 `compare` y2 - -netConfig :: IO MConfig -netConfig = mkMConfig -    "<dev>: <rx>KB|<tx>KB"      -- template -    ["dev", "rx", "tx", "rxbar", "rxvbar", "rxipat", "txbar", "txvbar", "txipat", "up"]     -- available replacements - - -#ifdef FREEBSD - -#include <sys/sysctl.h> -#include <net/if.h> -#include <net/if_mib.h> - -data IfData = IfData { -  name :: String -  , txBytes :: CUIntMax -  , rxBytes :: CUIntMax -  , isUp :: Bool -  } -  deriving (Show, Read, Eq) - -instance Storable IfData where -  alignment _ = #{alignment struct ifmibdata} -  sizeOf _    = #{size struct ifmibdata} -  peek ptr    = do -    cname <- peekCString (ptr `plusPtr` (#offset struct ifmibdata, ifmd_name)) -    tx <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_obytes)) :: IO CUIntMax -    rx <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_ibytes)) :: IO CUIntMax -    state <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_link_state)) :: IO CUChar -    return $ IfData {name = cname, txBytes = tx, rxBytes = rx, isUp = up state} -      where -        up state = state == (#const LINK_STATE_UP) -        ifmd_data_ptr p = p `plusPtr` (#offset struct ifmibdata, ifmd_data) - -  poke _ _    = pure () - -getNetIfCountOID :: IO OID -getNetIfCountOID = sysctlPrepareOid [ -  #const CTL_NET -  , #const PF_LINK -  , #const NETLINK_GENERIC -  , #const IFMIB_SYSTEM -  , #const IFMIB_IFCOUNT] - -getNetIfDataOID :: Int32 -> IO OID -getNetIfDataOID i = sysctlPrepareOid [ -  #const CTL_NET -  , #const PF_LINK -  , #const NETLINK_GENERIC -  , #const IFMIB_IFDATA -  , i -  , #const IFDATA_GENERAL] - -getNetIfCount :: IO Int32 -getNetIfCount = do -  oid <- getNetIfCountOID -  sysctlReadInt oid - -getNetIfData :: Int32 -> IO IfData -getNetIfData i = do -  oid <- getNetIfDataOID i -  res <- sysctlPeek oid :: IO IfData -  return res - -getAllNetworkData :: IO [IfData] -getAllNetworkData = do -  count <- getNetIfCount -  result <- mapM getNetIfData [1..count] -  return $ result - -existingDevs :: IO [String] -existingDevs = getAllNetworkData >>= (\xs -> return $ filter (/= "lo0") $ fmap name xs) - -convertIfDataToNetDev :: IfData -> IO NetDevRawTotal -convertIfDataToNetDev ifData = do -  let up = isUp ifData -      rx = fromInteger . toInteger $ rxBytes ifData -      tx = fromInteger . toInteger $ txBytes ifData -      d = name ifData -  return $ N d (if up then ND rx tx else NI) - -netConvertIfDataToNetDev :: [IfData] -> IO [NetDevRawTotal] -netConvertIfDataToNetDev = mapM convertIfDataToNetDev - -findNetDev :: String -> IO NetDevRawTotal -findNetDev dev = do -  nds <- getAllNetworkData >>= netConvertIfDataToNetDev -  case filter isDev nds of -    x:_ -> return x -    _ -> return NA -  where isDev (N d _) = d == dev -        isDev NA = False - -#else -operstateDir :: String -> FilePath -operstateDir d = "/sys/class/net" </> d </> "operstate" - -existingDevs :: IO [String] -existingDevs = getDirectoryContents "/sys/class/net" >>= filterM isDev -  where isDev d | d `elem` excludes = return False -                | otherwise = doesFileExist (operstateDir d) -        excludes = [".", "..", "lo"] - -isUp :: String -> IO Bool -isUp d = flip catchIOError (const $ return False) $ do -  operstate <- B.readFile (operstateDir d) -  return $! (head . B.lines) operstate `elem` ["up", "unknown"] - -readNetDev :: [String] -> IO NetDevRawTotal -readNetDev ~[d, x, y] = do -  up <- unsafeInterleaveIO $ isUp d -  return $ N d (if up then ND (r x) (r y) else NI) -    where r s | s == "" = 0 -              | otherwise = read s - -netParser :: B.ByteString -> IO [NetDevRawTotal] -netParser = mapM (readNetDev . splitDevLine) . readDevLines -  where readDevLines = drop 2 . B.lines -        splitDevLine = map B.unpack . selectCols . filter (not . B.null) . B.splitWith (`elem` [' ',':']) -        selectCols cols = map (cols!!) [0,1,9] - -findNetDev :: String -> IO NetDevRawTotal -findNetDev dev = do -  nds <- B.readFile "/proc/net/dev" >>= netParser -  case filter isDev nds of -    x:_ -> return x -    _ -> return NA -  where isDev (N d _) = d == dev -        isDev NA = False - -#endif - -formatNet :: Maybe IconPattern -> Float -> Monitor (String, String, String, String) -formatNet mipat d = do -    s <- getConfigValue useSuffix -    dd <- getConfigValue decDigits -    let str True v = showDigits dd d' ++ show u -            where (NetValue d' u) = byteNetVal v -        str False v = showDigits dd $ v / 1024 -    b <- showLogBar 0.9 d -    vb <- showLogVBar 0.9 d -    ipat <- showLogIconPattern mipat 0.9 d -    x <- showWithColors (str s) d -    return (x, b, vb, ipat) - -printNet :: NetOpts -> NetDevRate -> Monitor String -printNet opts nd = -  case nd of -    N d (ND r t) -> do -        (rx, rb, rvb, ripat) <- formatNet (rxIconPattern opts) r -        (tx, tb, tvb, tipat) <- formatNet (txIconPattern opts) t -        parseTemplate [d,rx,tx,rb,rvb,ripat,tb,tvb,tipat, upIndicator opts] -    N _ NI -> return "" -    NA -> getConfigValue naString - -parseNet :: NetDevRef -> String -> IO NetDevRate -parseNet nref nd = do -  (n0, t0) <- readIORef nref -  n1 <- findNetDev nd -  t1 <- getCurrentTime -  writeIORef nref (n1, t1) -  let scx = realToFrac (diffUTCTime t1 t0) -      scx' = if scx > 0 then scx else 1 -      rate da db = takeDigits 2 $ fromIntegral (db - da) / scx' -      diffRate (N d (ND ra ta)) (N _ (ND rb tb)) = N d (ND (rate ra rb) (rate ta tb)) -      diffRate (N d NI) _ = N d NI -      diffRate _ (N d NI) = N d NI -      diffRate _ _ = NA -  return $ diffRate n0 n1 - -runNet :: NetDevRef -> String -> [String] -> Monitor String -runNet nref i argv = do -  dev <- io $ parseNet nref i -  opts <- io $ parseOptsWith options defaultOpts argv -  printNet opts dev - -parseNets :: [(NetDevRef, String)] -> IO [NetDevRate] -parseNets = mapM $ uncurry parseNet - -runNets :: [(NetDevRef, String)] -> [String] -> Monitor String -runNets refs argv = do -  opts <- io $ parseOptsWith options defaultOpts argv -  dev <- io $ parseActive $ filterRefs opts refs -  printNet opts dev -    where parseActive refs' = fmap selectActive (parseNets refs') -          refInDevList opts' (_, refname') = case onlyDevList opts' of -            Just theList -> refname' `elem` theList -            Nothing -> True -          filterRefs opts' refs' = case filter (refInDevList opts') refs' of -            [] -> refs' -            xs -> xs -          selectActive = maximum - -startNet :: String -> [String] -> Int -> (String -> IO ()) -> IO () -startNet i a r cb = do -  t0 <- getCurrentTime -  nref <- newIORef (NA, t0) -  _ <- parseNet nref i -  runM a netConfig (runNet nref i) r cb - -startDynNet :: [String] -> Int -> (String -> IO ()) -> IO () -startDynNet a r cb = do -  devs <- existingDevs -  refs <- forM devs $ \d -> do -            t <- getCurrentTime -            nref <- newIORef (NA, t) -            _ <- parseNet nref d -            return (nref, d) -  runM a netConfig (runNets refs) r cb - -byteNetVal :: Float -> NetValue -byteNetVal v -    | v < 1024**1 = NetValue v Bs -    | v < 1024**2 = NetValue (v/1024**1) KBs -    | v < 1024**3 = NetValue (v/1024**2) MBs -    | otherwise   = NetValue (v/1024**3) GBs diff --git a/src/Xmobar/Plugins/Monitors/Net/Common.hs b/src/Xmobar/Plugins/Monitors/Net/Common.hs new file mode 100644 index 0000000..16ed865 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Net/Common.hs @@ -0,0 +1,50 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Net.Common +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017, 2020 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A net device monitor for Xmobar +-- + +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Net.Common ( +                        NetDev(..) +                      , NetDevInfo(..) +                      , NetDevRawTotal +                      , NetDevRate +                      , NetDevRef +                      ) where + +import Data.IORef (IORef) +import Data.Time.Clock (UTCTime) +import Data.Word (Word64) + +data NetDev num = N String (NetDevInfo num) | NA deriving (Eq,Show,Read) +data NetDevInfo num = NI | ND num num deriving (Eq,Show,Read) + +type NetDevRawTotal = NetDev Word64 +type NetDevRate = NetDev Float + +type NetDevRef = IORef (NetDevRawTotal, UTCTime) + +-- The more information available, the better. +-- Note that names don't matter. Therefore, if only the names differ, +-- a compare evaluates to EQ while (==) evaluates to False. +instance Ord num => Ord (NetDev num) where +    compare NA NA             = EQ +    compare NA _              = LT +    compare _  NA             = GT +    compare (N _ i1) (N _ i2) = i1 `compare` i2 + +instance Ord num => Ord (NetDevInfo num) where +    compare NI NI                 = EQ +    compare NI ND {}              = LT +    compare ND {} NI              = GT +    compare (ND x1 y1) (ND x2 y2) = x1 `compare` x2 <> y1 `compare` y2 diff --git a/src/Xmobar/Plugins/Monitors/Net/FreeBSD.hsc b/src/Xmobar/Plugins/Monitors/Net/FreeBSD.hsc new file mode 100644 index 0000000..ab446e3 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Net/FreeBSD.hsc @@ -0,0 +1,118 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE CApiFFI #-} + +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Net.FreeBSD +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017, 2020 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A net device monitor for Xmobar +-- + +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Net.FreeBSD ( +  existingDevs +  , findNetDev +  ) where + +import Xmobar.Plugins.Monitors.Net.Common (NetDevRawTotal, NetDev(..), NetDevInfo(..)) +import Control.Exception (catch, SomeException(..)) +import Foreign (Int32, plusPtr) +import Foreign.C.Types (CUIntMax, CUChar) +import Foreign.C.String (peekCString) +import Foreign.ForeignPtr () +import Foreign.Storable (Storable, alignment, sizeOf, peek, poke) +import System.BSD.Sysctl (OID, sysctlPrepareOid, sysctlReadInt, sysctlPeek) + +#include <sys/sysctl.h> +#include <net/if.h> +#include <net/if_mib.h> + +data IfData = AvailableIfData { +  name :: String +  , txBytes :: CUIntMax +  , rxBytes :: CUIntMax +  , isUp :: Bool +  } | NotAvailableIfData +  deriving (Show, Read, Eq) + +instance Storable IfData where +  alignment _ = #{alignment struct ifmibdata} +  sizeOf _    = #{size struct ifmibdata} +  peek ptr    = do +    cname <- peekCString (ptr `plusPtr` (#offset struct ifmibdata, ifmd_name)) +    tx <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_obytes)) :: IO CUIntMax +    rx <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_ibytes)) :: IO CUIntMax +    state <- peek ((ifmd_data_ptr ptr) `plusPtr` (#offset struct if_data, ifi_link_state)) :: IO CUChar +    return $ AvailableIfData {name = cname, txBytes = tx, rxBytes = rx, isUp = up state} +      where +        up state = state == (#const LINK_STATE_UP) +        ifmd_data_ptr p = p `plusPtr` (#offset struct ifmibdata, ifmd_data) + +  poke _ _    = pure () + +getNetIfCountOID :: IO OID +getNetIfCountOID = sysctlPrepareOid [ +  #const CTL_NET +  , #const PF_LINK +  , #const NETLINK_GENERIC +  , #const IFMIB_SYSTEM +  , #const IFMIB_IFCOUNT] + +getNetIfDataOID :: Int32 -> IO OID +getNetIfDataOID i = sysctlPrepareOid [ +  #const CTL_NET +  , #const PF_LINK +  , #const NETLINK_GENERIC +  , #const IFMIB_IFDATA +  , i +  , #const IFDATA_GENERAL] + +getNetIfCount :: IO Int32 +getNetIfCount = do +  oid <- getNetIfCountOID +  sysctlReadInt oid + +getNetIfData :: Int32 -> IO IfData +getNetIfData i = do +  oid <- getNetIfDataOID i +  res <- catch (sysctlPeek oid) (\(SomeException _) -> return NotAvailableIfData) +  return res + +getAllNetworkData :: IO [IfData] +getAllNetworkData = do +  count <- getNetIfCount +  result <- mapM getNetIfData [1..count] +  return result + +existingDevs :: IO [String] +existingDevs = getAllNetworkData >>= (\xs -> return $ filter (/= "lo0") $ fmap name xs) + +convertIfDataToNetDev :: IfData -> IO NetDevRawTotal +convertIfDataToNetDev ifData = do +  let up = isUp ifData +      rx = fromInteger . toInteger $ rxBytes ifData +      tx = fromInteger . toInteger $ txBytes ifData +      d = name ifData +  return $ N d (if up then ND rx tx else NI) + +netConvertIfDataToNetDev :: [IfData] -> IO [NetDevRawTotal] +netConvertIfDataToNetDev = mapM convertIfDataToNetDev + +findNetDev :: String -> IO NetDevRawTotal +findNetDev dev = do +  nds <- getAllNetworkData >>= netConvertIfDataToNetDev +  case filter isDev nds of +    x:_ -> return x +    _ -> return NA +  where isDev (N d _) = d == dev +        isDev NA = False diff --git a/src/Xmobar/Plugins/Monitors/Net/Linux.hs b/src/Xmobar/Plugins/Monitors/Net/Linux.hs new file mode 100644 index 0000000..9306497 --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Net/Linux.hs @@ -0,0 +1,69 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Net.Linux +-- Copyright   :  (c) 2011, 2012, 2013, 2014, 2017, 2020 Jose Antonio Ortega Ruiz +--                (c) 2007-2010 Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A net device monitor for Xmobar +-- + +----------------------------------------------------------------------------- + +{-# LANGUAGE OverloadedStrings #-} + +module Xmobar.Plugins.Monitors.Net.Linux ( +  existingDevs +  , findNetDev +  ) where + +import Xmobar.Plugins.Monitors.Net.Common (NetDevRawTotal, NetDev(..), NetDevInfo(..)) + +import Control.Monad (filterM) +import System.Directory (getDirectoryContents, doesFileExist) +import System.FilePath ((</>)) +import System.IO.Error (catchIOError) +import System.IO.Unsafe (unsafeInterleaveIO) + +import qualified Data.ByteString.Char8 as B + + +operstateDir :: String -> FilePath +operstateDir d = "/sys/class/net" </> d </> "operstate" + +existingDevs :: IO [String] +existingDevs = getDirectoryContents "/sys/class/net" >>= filterM isDev +  where isDev d | d `elem` excludes = return False +                | otherwise = doesFileExist (operstateDir d) +        excludes = [".", "..", "lo"] + +isUp :: String -> IO Bool +isUp d = flip catchIOError (const $ return False) $ do +  operstate <- B.readFile (operstateDir d) +  return $! (head . B.lines) operstate `elem` ["up", "unknown"] + +readNetDev :: [String] -> IO NetDevRawTotal +readNetDev ~[d, x, y] = do +  up <- unsafeInterleaveIO $ isUp d +  return $ N d (if up then ND (r x) (r y) else NI) +    where r s | s == "" = 0 +              | otherwise = read s + +netParser :: B.ByteString -> IO [NetDevRawTotal] +netParser = mapM (readNetDev . splitDevLine) . readDevLines +  where readDevLines = drop 2 . B.lines +        splitDevLine = map B.unpack . selectCols . filter (not . B.null) . B.splitWith (`elem` [' ',':']) +        selectCols cols = map (cols!!) [0,1,9] + +findNetDev :: String -> IO NetDevRawTotal +findNetDev dev = do +  nds <- B.readFile "/proc/net/dev" >>= netParser +  case filter isDev nds of +    x:_ -> return x +    _ -> return NA +  where isDev (N d _) = d == dev +        isDev NA = False diff --git a/src/Xmobar/Plugins/Monitors/Swap.hs b/src/Xmobar/Plugins/Monitors/Swap.hs index ca46010..e8b2f54 100644 --- a/src/Xmobar/Plugins/Monitors/Swap.hs +++ b/src/Xmobar/Plugins/Monitors/Swap.hs @@ -17,10 +17,10 @@ module Xmobar.Plugins.Monitors.Swap where  import Xmobar.Plugins.Monitors.Common -#ifdef FREEBSD -import System.BSD.Sysctl (sysctlReadUInt, sysctlReadULong) +#if defined(freebsd_HOST_OS) +import qualified Xmobar.Plugins.Monitors.Swap.FreeBSD as MS  #else -import qualified Data.ByteString.Lazy.Char8 as B +import qualified Xmobar.Plugins.Monitors.Swap.Linux as MS  #endif  swapConfig :: IO MConfig @@ -28,53 +28,6 @@ swapConfig = mkMConfig          "Swap: <usedratio>%"                    -- template          ["usedratio", "total", "used", "free"] -- available replacements -#ifdef FREEBSD - -isEnabled :: IO Bool -isEnabled = do -  enabled <- sysctlReadUInt "vm.swap_enabled" -  return $ enabled == 1 - -parseMEM' :: Bool -> IO [Float] -parseMEM' False = return $ [] -parseMEM' True = do -  swapIn <- sysctlReadUInt "vm.stats.vm.v_swapin" -  swapTotal <- sysctlReadULong "vm.swap_total" -  let tot = toInteger swapTotal -      free = tot - (toInteger swapIn) - -  return $ res (fromInteger tot) (fromInteger free) -  where -    res :: Float -> Float -> [Float] -    res _ 0 = [] -    res tot free = [(tot - free) / tot, tot, tot - free, free] - -parseMEM :: IO [Float] -parseMEM = do -  enabled <- isEnabled -  parseMEM' enabled - -#else -fileMEM :: IO B.ByteString -fileMEM = B.readFile "/proc/meminfo" - -parseMEM :: IO [Float] -parseMEM = -    do file <- fileMEM -       let li i l -               | l /= [] = head l !! i -               | otherwise = B.empty -           fs s l -               | null l    = False -               | otherwise = head l == B.pack s -           get_data s = flip (/) 1024 . read . B.unpack . li 1 . filter (fs s) -           st   = map B.words . B.lines $ file -           tot  = get_data "SwapTotal:" st -           free = get_data "SwapFree:" st -       return [(tot - free) / tot, tot, tot - free, free] - -#endif -  formatSwap :: [Float] -> Monitor [String]  formatSwap (r:xs) = do    d <- getConfigValue decDigits @@ -85,6 +38,6 @@ formatSwap _ = return $ replicate 4 "N/A"  runSwap :: [String] -> Monitor String  runSwap _ = -    do m <- io parseMEM +    do m <- io MS.parseMEM         l <- formatSwap m         parseTemplate l diff --git a/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hs b/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hs new file mode 100644 index 0000000..0e0c03d --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Swap/FreeBSD.hs @@ -0,0 +1,41 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Swap.FreeBSD +-- Copyright   :  (c) Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A  swap usage monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Swap.FreeBSD (parseMEM) where + +import System.BSD.Sysctl (sysctlReadUInt, sysctlReadULong) + +isEnabled :: IO Bool +isEnabled = do +  enabled <- sysctlReadUInt "vm.swap_enabled" +  return $ enabled == 1 + +parseMEM' :: Bool -> IO [Float] +parseMEM' False = return [] +parseMEM' True = do +  swapIn <- sysctlReadUInt "vm.stats.vm.v_swapin" +  swapTotal <- sysctlReadULong "vm.swap_total" +  let tot = toInteger swapTotal +      free = tot - toInteger swapIn + +  return $ res (fromInteger tot) (fromInteger free) +  where +    res :: Float -> Float -> [Float] +    res _ 0 = [] +    res tot free = [(tot - free) / tot, tot, tot - free, free] + +parseMEM :: IO [Float] +parseMEM = do +  enabled <- isEnabled +  parseMEM' enabled diff --git a/src/Xmobar/Plugins/Monitors/Swap/Linux.hs b/src/Xmobar/Plugins/Monitors/Swap/Linux.hs new file mode 100644 index 0000000..0af0f5d --- /dev/null +++ b/src/Xmobar/Plugins/Monitors/Swap/Linux.hs @@ -0,0 +1,35 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Swap.Linux +-- Copyright   :  (c) Andrea Rossato +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A. Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A  swap usage monitor for Xmobar +-- +----------------------------------------------------------------------------- + +module Xmobar.Plugins.Monitors.Swap.Linux (parseMEM) where + +import qualified Data.ByteString.Lazy.Char8 as B + +fileMEM :: IO B.ByteString +fileMEM = B.readFile "/proc/meminfo" + +parseMEM :: IO [Float] +parseMEM = +    do file <- fileMEM +       let li i l +               | l /= [] = head l !! i +               | otherwise = B.empty +           fs s l +               | null l    = False +               | otherwise = head l == B.pack s +           get_data s = flip (/) 1024 . read . B.unpack . li 1 . filter (fs s) +           st   = map B.words . B.lines $ file +           tot  = get_data "SwapTotal:" st +           free = get_data "SwapFree:" st +       return [(tot - free) / tot, tot, tot - free, free] | 
