aboutsummaryrefslogtreecommitdiffstats
path: root/ShellPrompt.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-10-07 13:01:33 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-10-07 13:01:33 +0200
commit09561ded3e37305570f10ae857dfe9c11ad0bf16 (patch)
treeb1a67b1626332a7d28df9bc24376954a67ebc979 /ShellPrompt.hs
parent6a386110616c2156847ae575f787e494de1dff8a (diff)
downloadXMonadContrib-09561ded3e37305570f10ae857dfe9c11ad0bf16.tar.gz
XMonadContrib-09561ded3e37305570f10ae857dfe9c11ad0bf16.tar.xz
XMonadContrib-09561ded3e37305570f10ae857dfe9c11ad0bf16.zip
ShellPrompt: check for executables and better error handling
Code contributed by Spencer (basically I just removed FilePath depenency). darcs-hash:20071007110133-32816-49cab7bd033569a16c55a3d1bfde3aba8c9fc3ee.gz
Diffstat (limited to 'ShellPrompt.hs')
-rw-r--r--ShellPrompt.hs38
1 files changed, 20 insertions, 18 deletions
diff --git a/ShellPrompt.hs b/ShellPrompt.hs
index 1ff4705..14e855c 100644
--- a/ShellPrompt.hs
+++ b/ShellPrompt.hs
@@ -16,7 +16,6 @@ module XMonadContrib.ShellPrompt (
-- * Usage
-- $usage
shellPrompt
- , rmPath
, split
) where
@@ -62,26 +61,29 @@ getShellCompl s
f <- fmap (lines . fromMaybe "") $ runProcessWithInput "/bin/bash" [] ("compgen -A file " ++ s ++ "\n")
c <- commandCompletionFunction s
hPutStrLn stdout s
- return $ map escape . sort . nub $ f ++ c
+ return . map escape . sort . nub $ f ++ c
| otherwise = return []
commandCompletionFunction :: String -> IO [String]
-commandCompletionFunction str
+commandCompletionFunction str
| '/' `elem` str = return []
| otherwise = do
- p <- getEnv "PATH"
- cl p
- where
- cl = liftM (nub . rmPath . concat) . mapM cmpl . split ':'
- cmpl s = filter (isPrefixOf str) `fmap` getFileNames s
-
-getFileNames :: FilePath -> IO [FilePath]
-getFileNames fp =
- getDirectoryContents fp `catch` \_ -> return []
-
-rmPath :: [String] -> [String]
-rmPath s =
- map (reverse . fst . break (=='/') . reverse) s
+ 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 _ [] = []
@@ -89,7 +91,7 @@ split e l =
f : split e (rest ls)
where
(f,ls) = span (/=e) l
- rest s | s == [] = []
+ rest s | s == [] = []
| otherwise = tail s
escape :: String -> String
@@ -97,7 +99,7 @@ escape [] = ""
escape (' ':xs) = "\\ " ++ escape xs
escape (x:xs)
| isSpecialChar x = '\\' : x : escape xs
- | otherwise = x : escape xs
+ | otherwise = x : escape xs
isSpecialChar :: Char -> Bool
isSpecialChar = flip elem "\\@\"'#?$*()[]{};"