module XMonad.Prompt.Shell
    ( 
      
      Shell (..)
    , shellPrompt
    , getCommands
    , getBrowser
    , getEditor
    , getShellCompl
    , split
    , prompt
    , safePrompt
    ) where
import System.Environment
import Control.Monad
import Data.List
import System.Directory
import System.IO
import System.Posix.Files
import XMonad.Util.Run
import XMonad hiding (config)
import XMonad.Prompt
data Shell = Shell
instance XPrompt Shell where
    showXPrompt Shell     = "Run: "
    completionToCommand _ = escape
shellPrompt :: XPConfig -> X ()
shellPrompt c = do
    cmds <- io getCommands
    mkXPrompt Shell c (getShellCompl cmds) (spawn . encodeOutput)
prompt, unsafePrompt, safePrompt :: FilePath -> XPConfig -> X ()
prompt = unsafePrompt
safePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
    where run = safeSpawn c . return . encodeOutput
unsafePrompt c config = mkXPrompt Shell config (getShellCompl [c]) run
    where run a = unsafeSpawn $ c ++ " " ++ encodeOutput a
getShellCompl :: [String] -> String -> IO [String]
getShellCompl cmds s | s == "" || last s == ' ' = return []
                     | otherwise                = do
    f     <- fmap lines $ runProcessWithInput "bash" [] ("compgen -A file " ++ encodeOutput s ++ "\n")
    files <- case f of
               [x] -> do fs <- getFileStatus x
                         if isDirectory fs then return [x ++ "/"]
                                           else return [x]
               _   -> return f
    return . map decodeInput . uniqSort $ files ++ commandCompletionFunction cmds s
commandCompletionFunction :: [String] -> String -> [String]
commandCompletionFunction cmds str | '/' `elem` str = []
                                   | otherwise      = filter (isPrefixOf str) cmds
getCommands :: IO [String]
getCommands = do
    p  <- getEnv "PATH" `catch` const (return [])
    let ds = split ':' p
    es <- forM ds $ \d -> do
        exists <- doesDirectoryExist d
        if exists
            then getDirectoryContents d
            else return []
    return . uniqSort . filter ((/= '.') . head) . concat $ es
split :: Eq a => a -> [a] -> [[a]]
split _ [] = []
split e l =
    f : split e (rest ls)
        where
          (f,ls) = span (/=e) l
          rest s | s == []   = []
                 | otherwise = tail s
escape :: String -> String
escape []       = ""
escape (x:xs)
    | isSpecialChar x = '\\' : x : escape xs
    | otherwise       = x : escape xs
isSpecialChar :: Char -> Bool
isSpecialChar =  flip elem " &\\@\"'#?$*()[]{};"
env :: String -> String -> IO String
env variable fallthrough = getEnv variable `catch` \_ -> return fallthrough
getBrowser :: IO String
getBrowser = env "BROWSER" "firefox"
getEditor :: IO String
getEditor = env "EDITOR" "emacs"