diff options
| -rw-r--r-- | IWlib.hsc | 75 | ||||
| -rw-r--r-- | Plugins/Monitors.hs | 12 | ||||
| -rw-r--r-- | Plugins/Monitors/Wireless.hs | 31 | ||||
| -rw-r--r-- | README | 13 | ||||
| -rw-r--r-- | xmobar.cabal | 10 | 
5 files changed, 140 insertions, 1 deletions
| diff --git a/IWlib.hsc b/IWlib.hsc new file mode 100644 index 0000000..afd6bf0 --- /dev/null +++ b/IWlib.hsc @@ -0,0 +1,75 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  IWlib +-- Copyright   :  (c) Jose A Ortega Ruiz +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose A Ortega Ruiz <jao@gnu.org> +-- Stability   :  unstable +-- Portability :  unportable +-- +--  A partial binding to iwlib +-- +----------------------------------------------------------------------------- + +{-# LANGUAGE CPP, ForeignFunctionInterface, EmptyDataDecls #-} + + +module IWlib (WirelessInfo(..), getWirelessInfo) where + +import Foreign +import Foreign.C.Types +import Foreign.C.String + +data WirelessInfo = WirelessInfo { wiEssid :: String,  wiQuality :: Int } +                  deriving Show + +#include <iwlib.h> + +data WCfg +data WStats +data WRange + +foreign import ccall "iwlib.h iw_sockets_open" +  c_iw_open :: IO CInt + +foreign import ccall "unistd.h close" +  c_iw_close :: CInt -> IO () + +foreign import ccall "iwlib.h iw_get_basic_config" +  c_iw_basic_config :: CInt -> CString -> Ptr WCfg -> IO CInt + +foreign import ccall "iwlib.h iw_get_stats" +  c_iw_stats :: CInt -> CString -> Ptr WStats -> Ptr WRange -> CInt -> IO CInt + +foreign import ccall "iwlib.h iw_get_range_info" +  c_iw_range :: CInt -> CString -> Ptr WRange -> IO CInt + +getWirelessInfo :: String -> IO WirelessInfo +getWirelessInfo iface = +  allocaBytes (#size struct wireless_config) $ \wc -> +  allocaBytes (#size struct iw_statistics) $ \stats -> +  allocaBytes (#size struct iw_range) $ \rng -> +  withCString iface $ \istr -> do +    i <- c_iw_open +    bcr <- c_iw_basic_config i istr wc +    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 = -1} 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 +                    do l <- (#peek struct wireless_config, essid_len) wc +                       let e = (#ptr struct wireless_config, essid) wc +                       peekCStringLen (e, fromIntegral (l :: CInt)) +                  else return "" +         q <- if str >= 0 && rgr >=0 then +                do let qual = (#ptr struct iw_statistics, qual) stats +                   qualv <- (#peek struct iw_param, value) qual :: IO CInt +                   let qualm = (#ptr struct iw_range, max_qual) rng +                   mv <- (#peek struct iw_param, value) qualm :: IO CInt +                   return $ fromIntegral qualv / fromIntegral (max 1 mv) +              else return (-1) +         let qv = round (100 * (q :: Double)) +         return $ WirelessInfo { wiEssid = essid, wiQuality = qv } diff --git a/Plugins/Monitors.hs b/Plugins/Monitors.hs index cba7332..2aff132 100644 --- a/Plugins/Monitors.hs +++ b/Plugins/Monitors.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE CPP #-} +  -----------------------------------------------------------------------------  -- |  -- Module      :  Xmobar.Plugins.Monitors @@ -29,6 +31,9 @@ import Plugins.Monitors.CpuFreq  import Plugins.Monitors.CoreTemp  import Plugins.Monitors.Disk  import Plugins.Monitors.Top +#ifdef IWLIB +import Plugins.Monitors.Wireless +#endif  data Monitors = Weather  Station    Args Rate                | Network  Interface  Args Rate @@ -45,6 +50,9 @@ data Monitors = Weather  Station    Args Rate                | CoreTemp Args       Rate                | TopCpu   Args       Rate                | TopMem   Args       Rate +#ifdef IWLIB +              | Wireless Interface  Args Rate +#endif                  deriving (Show,Read,Eq)  type Args      = [String] @@ -72,6 +80,10 @@ instance Exec Monitors where      alias (CoreTemp   _ _) = "coretemp"      alias (DiskU    _ _ _) = "disku"      alias (DiskIO   _ _ _) = "diskio" +#ifdef IWLIB +    alias (Wireless i _ _) = i ++ "wi" +    start (Wireless i a r) = runM (a ++ [i]) wirelessConfig  runWireless  r +#endif      start (Weather  s a r) = runM (a ++ [s]) weatherConfig  runWeather    r      start (Network  i a r) = runM (a ++ [i]) netConfig      runNet        r      start (Thermal  z a r) = runM (a ++ [z]) thermalConfig  runThermal    r diff --git a/Plugins/Monitors/Wireless.hs b/Plugins/Monitors/Wireless.hs new file mode 100644 index 0000000..167a48f --- /dev/null +++ b/Plugins/Monitors/Wireless.hs @@ -0,0 +1,31 @@ +----------------------------------------------------------------------------- +-- | +-- Module      :  Plugins.Monitors.Wireless +-- Copyright   :  (c) Jose Antonio Ortega Ruiz +-- License     :  BSD-style (see LICENSE) +-- +-- Maintainer  :  Jose Antonio Ortega Ruiz +-- Stability   :  unstable +-- Portability :  unportable +-- +-- A monitor reporting ESSID and link quality for wireless interfaces +-- +----------------------------------------------------------------------------- + +module Plugins.Monitors.Wireless (wirelessConfig, runWireless)  where + +import Plugins.Monitors.Common +import IWlib + +wirelessConfig :: IO MConfig +wirelessConfig = mkMConfig "<essid> <quality>" ["essid", "quality"] + +runWireless :: [String] -> Monitor String +runWireless (iface:_) = do +  wi <- io $ getWirelessInfo iface +  let essid = wiEssid wi +      quality = wiQuality wi +      e = if essid == "" then "N/A" else essid +  q <- if quality >= 0 then showWithColors show quality else return "N/A" +  parseTemplate [e, q] +runWireless _ = return ""
\ No newline at end of file @@ -300,6 +300,19 @@ Monitors have default aliases.  	    `dev`, `rx`, `tx`  - Default template: `<dev>: <rx>|<tx>` +`Wireless Interface Args RefreshRate` + +- aliases to the interface name with the suffix "wi": thus, `Wirelss +  "wlan0" []` can be used as `%wlan0wi%` +- Args: the argument list (see below) +- Variables that can be used with the `-t`/`--template` argument: +            `essid`, `quality` +- Default template: `<essid> <quality>` +- Requires the C library libiw (part of the wireless tools suite) +  installed in your system. In addition, to activate this plugin you +  must pass --flags="with_iwlib" to "runhaskell Setup configure" +  or to "cabal install". +  `Memory Args RefreshRate`  - aliases to `memory` diff --git a/xmobar.cabal b/xmobar.cabal index 24f6b36..4af6d3b 100644 --- a/xmobar.cabal +++ b/xmobar.cabal @@ -31,9 +31,13 @@ flag with_inotify    description: inotify support (modern Linux only).  Required for the Mail plugin.    default: False +flag with_iwlib +  description: wireless info support. Required for the Wireless plugin, needs iwlib installed. +  default: False +  executable xmobar      main-is:            Main.hs -    other-Modules:      Xmobar, Config, Parsers, Commands, XUtil, StatFS, Runnable, Plugins +    other-modules:      Xmobar, Config, Parsers, Commands, XUtil, StatFS, Runnable, Plugins      ghc-prof-options:   -prof -auto-all      if true @@ -65,3 +69,7 @@ executable xmobar         build-depends: hinotify         cpp-options: -DINOTIFY +    if flag(with_iwlib) +       extra-libraries: iw +       other-modules: IWlib +       cpp-options: -DIWLIB
\ No newline at end of file | 
