aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Prompt/Man.hs
diff options
context:
space:
mode:
authorValery V. Vorotyntsev <valery.vv@gmail.com>2007-12-12 10:02:56 +0100
committerValery V. Vorotyntsev <valery.vv@gmail.com>2007-12-12 10:02:56 +0100
commit0e31165d554da9b6d3b8a25e69b9dcc0f761e253 (patch)
tree81a11bc79b5894382c3526d1b47de711211deefb /XMonad/Prompt/Man.hs
parent7986238a42c1100084e1f5525b42b8cecc30634a (diff)
downloadXMonadContrib-0e31165d554da9b6d3b8a25e69b9dcc0f761e253.tar.gz
XMonadContrib-0e31165d554da9b6d3b8a25e69b9dcc0f761e253.tar.xz
XMonadContrib-0e31165d554da9b6d3b8a25e69b9dcc0f761e253.zip
Man.hs: input speedup
Descend manpage directories once -- when `manPrompt' is called. (Previous version used to search directories upon each character arrival.) darcs-hash:20071212090256-ae588-c8afdd4f04a9aa9e6ee947d0d1559566134ffb9d.gz
Diffstat (limited to 'XMonad/Prompt/Man.hs')
-rw-r--r--XMonad/Prompt/Man.hs38
1 files changed, 21 insertions, 17 deletions
diff --git a/XMonad/Prompt/Man.hs b/XMonad/Prompt/Man.hs
index 265abed..71c7dbd 100644
--- a/XMonad/Prompt/Man.hs
+++ b/XMonad/Prompt/Man.hs
@@ -13,8 +13,6 @@
--
-- * narrow completions by section number, if the one is specified
-- (like @\/etc\/bash_completion@ does)
---
--- * write QuickCheck properties
-----------------------------------------------------------------------------
module XMonad.Prompt.Man (
@@ -58,33 +56,36 @@ instance XPrompt Man where
-- | Query for manual page to be displayed.
manPrompt :: XPConfig -> X ()
-manPrompt c = mkXPrompt Man c manCompl $ runInTerm . (++) "man "
+manPrompt c = do
+ mans <- io getMans
+ mkXPrompt Man c (manCompl mans) $ runInTerm . (++) "man "
-manCompl :: String -> IO [String]
-manCompl str | '/' `elem` str = do
- -- XXX It may be better to use readline instead of bash's compgen...
- lines `fmap` getCommandOutput ("bash -c 'compgen -A file " ++ str ++ "'")
- | otherwise = do
- mp <- getCommandOutput "manpath -g 2>/dev/null" `E.catch` \_ -> return []
+getMans :: IO [String]
+getMans = do
+ paths <- getCommandOutput "manpath -g 2>/dev/null" `E.catch` \_ -> return []
let sects = ["man" ++ show n | n <- [1..9 :: Int]]
- dirs = [d ++ "/" ++ s | d <- split ':' mp, s <- sects]
- stripExt = reverse . drop 1 . dropWhile (/= '.') . reverse
+ dirs = [d ++ "/" ++ s | d <- split ':' paths, s <- sects]
mans <- forM dirs $ \d -> do
exists <- doesDirectoryExist d
if exists
then map (stripExt . stripSuffixes [".gz", ".bz2"]) `fmap`
getDirectoryContents d
else return []
- mkComplFunFromList (uniqSort $ concat mans) str
+ return $ uniqSort $ concat mans
+
+manCompl :: [String] -> String -> IO [String]
+manCompl mans s | s == "" || last s == ' ' = return []
+ | otherwise = do
+ -- XXX readline instead of bash's compgen?
+ f <- lines `fmap` getCommandOutput ("bash -c 'compgen -A file " ++ s ++ "'")
+ mkComplFunFromList (f ++ mans) s
-- | Run a command using shell and return its output.
--
--- XXX merge with 'XMonad.Util.Run.runProcessWithInput'?
+-- XXX Merge into 'XMonad.Util.Run'?
--
--- * update documentation of the latter (there is no 'Maybe' in result)
---
--- * ask \"gurus\" whether @evaluate (length ...)@ approach is
--- better\/more idiomatic
+-- (Ask \"gurus\" whether @evaluate (length ...)@ approach is
+-- better\/more idiomatic.)
getCommandOutput :: String -> IO String
getCommandOutput s = do
(pin, pout, perr, ph) <- runInteractiveCommand s
@@ -95,6 +96,9 @@ getCommandOutput s = do
waitForProcess ph
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]