import Control.Monad import Data.List import System.Directory import System.IO import System.Environment import System.Process runProcessWithInput :: FilePath -> [String] -> String -> IO String runProcessWithInput cmd args input = do (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing hPutStr pin input hClose pin output <- hGetContents pout when (output==output) $ return () hClose pout hClose perr waitForProcess ph return output getShellCompl :: String -> IO [String] getShellCompl s | s /= "" && last s /= ' ' = do f <- fmap lines $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n") c <- commandCompletionFunction s return . map escape . sort . nub $ f ++ c | otherwise = return [] commandCompletionFunction :: String -> IO [String] commandCompletionFunction str | '/' `elem` str = return [] | otherwise = do p <- getEnv "PATH" `catch` const (return []) let ds = split ':' p fp d f = d ++ "/" ++ f es <- forM ds $ \d -> do exists <- doesDirectoryExist d if exists then getDirectoryContents d >>= filterM (isExecutable . fp d) else return [] return . filter (isPrefixOf str) . concat $ es isExecutable :: FilePath ->IO Bool isExecutable f = do fe <- doesFileExist f if fe then fmap executable $ getPermissions f else return False 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 (' ':xs) = "\\ " ++ escape xs escape (x:xs) | isSpecialChar x = '\\' : x : escape xs | otherwise = x : escape xs isSpecialChar :: Char -> Bool isSpecialChar = flip elem "\\@\"'#?$*()[]{};" main = do a <- getArgs putStrLn =<< fmap (show . length) (getShellCompl $ a !! 0)