module XMonad.Prompt.Man (
                          
                          
                          manPrompt
                         , getCommandOutput
                         , Man
                         ) where
import XMonad
import XMonad.Prompt
import XMonad.Util.Run
import XMonad.Prompt.Shell (split)
import System.Directory
import System.Process
import System.IO
import qualified Control.Exception.Extensible as E
import Control.Monad
import Data.List
import Data.Maybe
data Man = Man
instance XPrompt Man where
    showXPrompt Man = "Manual page: "
manPrompt :: XPConfig -> X ()
manPrompt c = do
  mans <- io getMans
  mkXPrompt Man c (manCompl mans) $ runInTerm "" . (++) "man "
getMans :: IO [String]
getMans = do
  paths <- do
    let getout cmd = getCommandOutput cmd `E.catch` \E.SomeException{} -> return ""
    
    p1 <- getout "manpath -g 2>/dev/null"
    p2 <- getout "manpath 2>/dev/null"
    return $ intercalate ":" $ lines $ p1 ++ p2
  let sects    = ["man" ++ show n | n <- [1..9 :: Int]]
      dirs     = [d ++ "/" ++ s | d <- split ':' paths, s <- sects]
  mans <- forM (nub dirs) $ \d -> do
            exists <- doesDirectoryExist d
            if exists
              then map (stripExt . stripSuffixes [".gz", ".bz2"]) `fmap`
                   getDirectoryContents d
              else return []
  return $ uniqSort $ concat mans
manCompl :: [String] -> String -> IO [String]
manCompl mans s | s == "" || last s == ' ' = return []
                | otherwise                = do
  
  f <- lines `fmap` getCommandOutput ("bash -c 'compgen -A file " ++ s ++ "'")
  mkComplFunFromList (f ++ mans) s
getCommandOutput :: String -> IO String
getCommandOutput s = do
  
  (pin, pout, perr, _) <- runInteractiveCommand s
  hClose pin
  output <- hGetContents pout
  E.evaluate (length output)
  hClose perr
  return output
stripExt :: String -> String
stripExt = reverse . drop 1 . dropWhile (/= '.') . reverse
stripSuffixes :: Eq a => [[a]] -> [a] -> [a]
stripSuffixes sufs fn =
    head . catMaybes $ map (flip rstrip fn) sufs ++ [Just fn]
rstrip :: Eq a => [a] -> [a] -> Maybe [a]
rstrip suf lst
    | suf `isSuffixOf` lst = Just $ take (length lst  length suf) lst
    | otherwise            = Nothing