diff options
| author | Michal Zielonka <michal.zielonka.8001@gmail.com> | 2021-10-07 00:46:02 +0200 | 
|---|---|---|
| committer | Michal Zielonka <michal.zielonka.8001@gmail.com> | 2021-10-07 08:36:53 +0200 | 
| commit | 34ff313d90b48033282af7b3e845614cfabcfef7 (patch) | |
| tree | 17149b2735eb8d2b070c1be45fe657ddb0b675a6 /src/Xmobar/Plugins/Monitors | |
| parent | 1f183cd7592af46c015ce57d60a88c2289069d2c (diff) | |
| download | xmobar-34ff313d90b48033282af7b3e845614cfabcfef7.tar.gz xmobar-34ff313d90b48033282af7b3e845614cfabcfef7.tar.bz2 | |
Add freebsd support for net monitor plugin.
In freebsd /sys/class/net is absent so we should use sysctl for
obtaining info about stats of network.
For parsing if_data struct we could use a "Foreign.Storable"
Diffstat (limited to 'src/Xmobar/Plugins/Monitors')
| -rw-r--r-- | src/Xmobar/Plugins/Monitors/Net.hsc (renamed from src/Xmobar/Plugins/Monitors/Net.hs) | 107 | 
1 files changed, 106 insertions, 1 deletions
| diff --git a/src/Xmobar/Plugins/Monitors/Net.hs b/src/Xmobar/Plugins/Monitors/Net.hsc index 23e0154..53a1a9e 100644 --- a/src/Xmobar/Plugins/Monitors/Net.hs +++ b/src/Xmobar/Plugins/Monitors/Net.hsc @@ -11,9 +11,13 @@  --  -- A net device monitor for Xmobar  -- +  -----------------------------------------------------------------------------  {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE CApiFFI #-}  module Xmobar.Plugins.Monitors.Net (                          startNet @@ -25,14 +29,25 @@ 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.Console.GetOpt  import System.IO.Error (catchIOError)  import System.IO.Unsafe (unsafeInterleaveIO)  import qualified Data.ByteString.Char8 as B +#endif  type DevList = [String] @@ -107,6 +122,94 @@ 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" @@ -143,6 +246,8 @@ findNetDev dev = do    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 | 
