-------------------------------------------------------------------------------
-- |
-- Module: Network.Cell
-- Copyright: (c) 2008 Marco TĂșlio Gontijo e Silva <marcot@riseup.net>
-- License: Simple permissive license (see LICENSE)
--
-- Maintainer: Marco TĂșlio Gontijo e Silva <marcot@riseup.net>
-- Stability: unstable
-- Portability: unportable
--
-- This module provides functions to parse the output of @iwlist scan@.
-------------------------------------------------------------------------------

module
  Network.Cell
  (
    -- * Data type
    Cell (..)
  , getCells
    -- * Queries
  , getQuality
  , isOpen
    -- ** General
  , getValue
    -- ** Utilities
  , getOpenEssids)
  where

-- base
import Data.List

-- | Each available network.
newtype Cell = Cell [String] deriving Eq

instance Ord Cell where
  compare c d = compare (getQuality c) (getQuality d)

-- | Get the list of available networks, given the output of @iwlist scan@.
getCells
  :: [String] -- ^ Output of @iwlist scan@
  -> [Cell]
getCells [] = []
getCells iwlist
  = case cell of
  (_ : _) -> Cell cell : rest
  _ -> rest
  where
    isPrefix = isPrefixOf prefix
    cell = map (drop (length prefix)) $ takeWhile isPrefix usable
    rest = getCells (dropWhile isPrefix usable)
    usable = dropWhile (not . isPrefix) iwlist

-- | Gets the field @Quality@.
getQuality :: Cell -> Int
getQuality = read . takeWhile (/= '/') . getValue "Quality:"

-- | Checks whether the network is open.
isOpen :: Cell -> Bool
isOpen cell = getValue "Encryption key:" cell == "off"

-- | Gets the field with @name@.
getValue
  :: String -- ^ @name@
  -> Cell
  -> String
getValue name (Cell cell)
  = case mValue of
  (value : _) -> value
  _ -> error $ show cell
  where
    mValue = map (drop (length name)) $ filter (isPrefixOf name) cell

-- | Gets the @essid@s of networks that don't use encryption.
getOpenEssids :: [Cell] -> [String]
getOpenEssids
  = nub
  . map (getValue "ESSID:")
  . reverse
  . sort
  . filter isOpen

prefix :: String
prefix = replicate 20 ' '