From b03f8e33706718b1f3c4bda8dc4a058911645557 Mon Sep 17 00:00:00 2001 From: Daniel Schoepe Date: Mon, 21 Sep 2009 00:14:55 +0200 Subject: Only use search history for completion in X.A.Search Ignore-this: 807fcd4fa14a25ecc9787940f9950736 darcs-hash:20090920221455-7f603-eca315cbb45fe6bc4f34e45a7f9a00f6770119e4.gz --- XMonad/Actions/Search.hs | 5 +++-- XMonad/Prompt.hs | 25 ++++++++++++++++++------- 2 files changed, 21 insertions(+), 9 deletions(-) (limited to 'XMonad') diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs index 5d1a57c..a9f6709 100644 --- a/XMonad/Actions/Search.hs +++ b/XMonad/Actions/Search.hs @@ -59,7 +59,7 @@ import Data.Char (chr, ord, isAlpha, isMark, isDigit) import Data.List (isPrefixOf) import Numeric (showIntAtBase) import XMonad (X(), MonadIO, liftIO) -import XMonad.Prompt (XPrompt(showXPrompt), mkXPrompt, XPConfig(), historyCompletion) +import XMonad.Prompt (XPrompt(showXPrompt), mkXPrompt, XPConfig(), historyCompletionP) import XMonad.Prompt.Shell (getBrowser) import XMonad.Util.Run (safeSpawn) import XMonad.Util.XSelection (getSelection) @@ -351,7 +351,8 @@ namedEngine name (SearchEngine _ site) = searchEngineF name site Prompt's result, passes it to a given searchEngine and opens it in a given browser. -} promptSearchBrowser :: XPConfig -> Browser -> SearchEngine -> X () -promptSearchBrowser config browser (SearchEngine name site) = mkXPrompt (Search name) config historyCompletion $ search browser site +promptSearchBrowser config browser (SearchEngine name site) = + mkXPrompt (Search name) config (historyCompletionP ("Search [" `isPrefixOf`)) $ search browser site {- | Like 'search', but in this case, the string is not specified but grabbed from the user's response to a prompt. Example: diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs index 8e6f97a..07f80c0 100644 --- a/XMonad/Prompt.hs +++ b/XMonad/Prompt.hs @@ -54,6 +54,7 @@ module XMonad.Prompt , decodeInput , encodeOutput , historyCompletion + , historyCompletionP -- * History filters , deleteAllDuplicates , deleteConsecutive @@ -127,15 +128,15 @@ data XPConfig = , height :: !Dimension -- ^ Window height , historySize :: !Int -- ^ The number of history entries to be saved , historyFilter :: [String] -> [String] - -- ^ a filter to determine which - -- history entries to remember + -- ^ a filter to determine which + -- history entries to remember , promptKeymap :: M.Map (KeyMask,KeySym) (XP ()) - , completionKey :: KeySym -- ^ Key that should trigger completion - -- ^ Mapping from key combinations to actions + -- ^ Mapping from key combinations to actions + , completionKey :: KeySym -- ^ Key that should trigger completion , defaultText :: String -- ^ The text by default in the prompt line , autoComplete :: Maybe Int -- ^ Just x: if only one completion remains, auto-select it, , showCompletionOnTab :: Bool -- ^ Only show list of completions when Tab was pressed - -- and delay by x microseconds + -- and delay by x microseconds } data XPType = forall p . XPrompt p => XPT p @@ -277,7 +278,11 @@ mkXPromptWithReturn t conf compl action = do liftIO $ writeHistory $ M.insertWith (\xs ys -> take (historySize conf) . historyFilter conf $ xs ++ ys) - (showXPrompt t) [command st'] hist + (showXPrompt t) (historyFilter conf [command st']) + hist + -- we need to apply historyFilter before as well, since + -- otherwise the filter would not be applied if + -- there is no history Just <$> action (command st') else return Nothing @@ -862,7 +867,13 @@ breakAtSpace s -- 'getShellCompl'; you pass it to mkXPrompt, and it will make completions work -- from the query history stored in ~\/.xmonad\/history. historyCompletion :: ComplFunction -historyCompletion x = fmap (deleteConsecutive . filter (isInfixOf x) . M.fold (++) []) readHistory +historyCompletion = historyCompletionP (const True) + +-- | Like 'historyCompletion' but only uses history data from Prompts whose +-- name satisfies the given predicate. +historyCompletionP :: (String -> Bool) -> ComplFunction +historyCompletionP p x = fmap (toComplList . M.filterWithKey (const . p)) readHistory + where toComplList = deleteConsecutive . filter (isInfixOf x) . M.fold (++) [] -- | Sort a list and remove duplicates. Like 'deleteAllDuplicates', but trades off -- laziness and stability for efficiency. -- cgit v1.2.3