aboutsummaryrefslogtreecommitdiffstats
path: root/XPrompt.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-08-17 17:54:54 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-08-17 17:54:54 +0200
commit7132b00ac612fb8822641c45a144fc43df72e415 (patch)
tree7825c343e7a0b71853a56c64d6910b5254104dd5 /XPrompt.hs
parent3be471b1ae883c6b5326c9bdb66ad6d77fea5280 (diff)
downloadXMonadContrib-7132b00ac612fb8822641c45a144fc43df72e415.tar.gz
XMonadContrib-7132b00ac612fb8822641c45a144fc43df72e415.tar.xz
XMonadContrib-7132b00ac612fb8822641c45a144fc43df72e415.zip
XPrompt: quickcheck related refactoring
With this patch XPrompt can be tested with quickcheck. As a result getLastWord and skipLastWord has been refactored to avoid possible exceptions. darcs-hash:20070817155454-32816-cf913d1207efe2c090c150bf192ba737323c4593.gz
Diffstat (limited to '')
-rw-r--r--XPrompt.hs39
1 files changed, 25 insertions, 14 deletions
diff --git a/XPrompt.hs b/XPrompt.hs
index c6b1c78..9546151 100644
--- a/XPrompt.hs
+++ b/XPrompt.hs
@@ -23,6 +23,13 @@ module XMonadContrib.XPrompt (
, XPPosition (..)
, XPConfig (..)
, XPrompt (..)
+ , mkUnmanagedWindow
+ , getLastWord
+ , skipLastWord
+ , splitInSubListsAt
+ , newIndex
+ , newCommand
+
) where
import Graphics.X11.Xlib
@@ -196,14 +203,10 @@ completionHandle c (ks,_) (KeyEvent {ev_event_type = t})
case c of
[] -> do updateWindows
eventLoop handle
- l -> let new_index = case elemIndex (getLastWord (command st)) l of
- Just i -> if i >= (length l - 1) then 0 else i + 1
- Nothing -> 0
- new_command = skipLastWord (command st) ++ fill ++ l !! new_index
- fill = if ' ' `elem` (command st) then " " else ""
- in do modify $ \s -> s { command = new_command, offset = length new_command }
- redrawWindows c
- eventLoop (completionHandle c)
+ l -> do let new_command = newCommand (command st) l
+ modify $ \s -> s { command = new_command, offset = length new_command }
+ redrawWindows c
+ eventLoop (completionHandle c)
-- key release
| t == keyRelease && ks == xK_Tab = eventLoop (completionHandle c)
-- other keys
@@ -212,6 +215,16 @@ completionHandle _ ks (KeyEvent {ev_event_type = t, ev_state = m})
-- some other event: go back to main loop
completionHandle _ k e = handle k e
+newIndex :: String -> [String] -> Int
+newIndex com cl =
+ case elemIndex (getLastWord com) cl of
+ Just i -> if i >= length cl - 1 then 0 else i + 1
+ Nothing -> 0
+
+newCommand :: String -> [String] -> String
+newCommand com cl =
+ skipLastWord com ++ (cl !! (newIndex com cl))
+
-- KeyPresses
data Direction = Prev | Next deriving (Eq,Show,Read)
@@ -603,7 +616,6 @@ mkComplFunFromList _ [] = return []
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
@@ -618,10 +630,9 @@ splitInSubListsAt i x = f : splitInSubListsAt i rest
where (f,rest) = splitAt i x
getLastWord :: String -> String
-getLastWord c
- | c == [] || filter (/=' ') c == [] = []
- | otherwise = last . words $ c
+getLastWord str =
+ reverse . fst . break isSpace . reverse $ str
skipLastWord :: String -> String
-skipLastWord [] = []
-skipLastWord c = unwords . init . words $ c
+skipLastWord str =
+ reverse . snd . break isSpace . reverse $ str