aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-16 14:34:54 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-16 14:34:54 +0100
commit0cf2ff67e2c11ed6ffcba558dfec3a906f170266 (patch)
tree5c2e51c777bd66da9676e14b9815832c9b857beb /XMonad
parent9bebda0dc13ee465b9f5ee86fdc6ddc8132598ec (diff)
downloadXMonadContrib-0cf2ff67e2c11ed6ffcba558dfec3a906f170266.tar.gz
XMonadContrib-0cf2ff67e2c11ed6ffcba558dfec3a906f170266.tar.xz
XMonadContrib-0cf2ff67e2c11ed6ffcba558dfec3a906f170266.zip
Prompt: add some methods to make completions more flexible
- now it is possible to decide if the prompt will complete the last word of the command line or the whole line (default is the last word); - completing the last word can be fine tuned by implementing 'commandToComplete' and 'completionToCommand': see comments for details; - move mkComplFunFromList' from TagWindows to Prompt. darcs-hash:20080216133454-32816-86eba16c4c73357b5bf6fee185c652d5ecd75521.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/TagWindows.hs6
-rw-r--r--XMonad/Prompt.hs65
2 files changed, 47 insertions, 24 deletions
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index 42c3613..4501e7d 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -193,9 +193,3 @@ tagDelPrompt c = do
tagDelComplList :: X [String]
tagDelComplList = gets windowset >>= maybe (return []) getTags . peek
-
-
-mkComplFunFromList' :: [String] -> String -> IO [String]
-mkComplFunFromList' l [] = return l
-mkComplFunFromList' l s =
- return $ filter (\x -> take (length s) x == s) l
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs
index de132f1..2377261 100644
--- a/XMonad/Prompt.hs
+++ b/XMonad/Prompt.hs
@@ -20,6 +20,7 @@ module XMonad.Prompt
, mkXPromptWithReturn
, defaultXPConfig
, mkComplFunFromList
+ , mkComplFunFromList'
, XPType (..)
, XPPosition (..)
, XPConfig (..)
@@ -31,12 +32,12 @@ module XMonad.Prompt
, fillDrawable
-- * Other Utilities
-- $utils
+ , getNextCompletion
+ , getNextOfLastWord
, getLastWord
, skipLastWord
, splitInSubListsAt
, breakAtSpace
- , newIndex
- , newCommand
, uniqSort
) where
@@ -104,9 +105,10 @@ instance Show XPType where
show (XPT p) = showXPrompt p
instance XPrompt XPType where
- showXPrompt = show
- nextCompletion (XPT t) c l = nextCompletion t c l
- commandToComplete (XPT t) c = commandToComplete t c
+ showXPrompt = show
+ nextCompletion (XPT t) = nextCompletion t
+ commandToComplete (XPT t) = commandToComplete t
+ completionToCommand (XPT t) = completionToCommand t
-- | The class prompt types must be an instance of. In order to
-- create a prompt you need to create a data type, without parameters,
@@ -119,14 +121,31 @@ instance XPrompt XPType where
-- > instance XPrompt Shell where
-- > showXPrompt Shell = "Run: "
class XPrompt t where
+
+ -- | This method is used to print the string to be
+ -- displayed in the command line window.
showXPrompt :: t -> String
+ -- | This method is used to generate the next completion to be
+ -- printed in the command line when tab is pressed, given the
+ -- string presently in the command line and the list of
+ -- completion.
nextCompletion :: t -> String -> [String] -> String
- nextCompletion t c l = newCommand t c l
+ nextCompletion t c l = getNextOfLastWord t c l
+ -- | If the prompt is using 'getNextOfLastWord' for implementing
+ -- 'nextCompletion' (the default implementation), this is used to
+ -- generate the string to be passed to the completion function.
commandToComplete :: t -> String -> String
commandToComplete _ c = getLastWord c
+ -- | If the prompt is using 'getNextOfLastWord' for implementing
+ -- 'nextCompletion' (the default implementation), this is used to
+ -- generate the string to compare each completion with the
+ -- command presently in the command line.
+ completionToCommand :: t -> String -> String
+ completionToCommand _ c = c
+
data XPPosition = Top
| Bottom
deriving (Show,Read)
@@ -613,7 +632,7 @@ printComplString :: Display -> Drawable -> GC -> String -> String
-> Position -> Position -> String -> XP ()
printComplString d drw gc fc bc x y s = do
st <- get
- if s == commandToComplete (xptype st) (command st)
+ if completionToCommand (xptype st) s == commandToComplete (xptype st) (command st)
then printStringXMF d drw (fontS st) gc
(fgHLight $ config st) (bgHLight $ config st) x y s
else printStringXMF d drw (fontS st) gc fc bc x y s
@@ -691,6 +710,14 @@ mkComplFunFromList _ [] = return []
mkComplFunFromList l s =
return $ filter (\x -> take (length s) x == s) l
+-- | This function takes a list of possible completions and returns a
+-- completions function to be used with 'mkXPrompt'. If the string is
+-- null it will return all completions.
+mkComplFunFromList' :: [String] -> String -> IO [String]
+mkComplFunFromList' l [] = return l
+mkComplFunFromList' l s =
+ return $ filter (\x -> take (length s) x == s) l
+
-- Lift an IO action into the XP
io :: IO a -> XP a
io = liftIO
@@ -705,19 +732,21 @@ splitInSubListsAt _ [] = []
splitInSubListsAt i x = f : splitInSubListsAt i rest
where (f,rest) = splitAt i x
--- | Given a completion and a list of possible completions, returns the
--- the next completion in the list
-newCommand :: XPrompt t => t -> String -> [String] -> String
-newCommand t com cl =
- skipLastWord com ++ (cl !! (newIndex t com cl))
+-- | Given a command and a completion list, get the next completion in
+-- the list.
+getNextCompletion :: String -> [String] -> String
+getNextCompletion c l = l !! idx
+ where idx = case c `elemIndex` l of
+ Just i -> if i >= length l - 1 then 0 else i + 1
+ Nothing -> 0
-- | Given a completion and a list of possible completions, returns the
--- index of the next completion in the list
-newIndex :: XPrompt t => t -> String -> [String] -> Int
-newIndex t com cl =
- case elemIndex (commandToComplete t com) cl of
- Just i -> if i >= length cl - 1 then 0 else i + 1
- Nothing -> 0
+-- the next completion in the list
+getNextOfLastWord :: XPrompt t => t -> String -> [String] -> String
+getNextOfLastWord t c l = skipLastWord c ++ completionToCommand t (l !! ni)
+ where ni = case commandToComplete t c `elemIndex` map (completionToCommand t) l of
+ Just i -> if i >= length l - 1 then 0 else i + 1
+ Nothing -> 0
-- | Gets the last word of a string or the whole string if formed by
-- only one word