[prev in list] [next in list] [prev in thread] [next in thread] 

List:       xmonad
Subject:    Re: [xmonad] Patch: changes in Prompt and new module
From:       Carlos_López_Camey <c.lopez () kmels ! net>
Date:       2012-08-26 9:30:54
Message-ID: CAMSgvCJ9gy77cSwopinF=wADm95_5mQqsDZj=s-mOFFQTB1Oeg () mail ! gmail ! com
[Download RAW message or body]

2012/8/26 Gwern Branwen <gwern0@gmail.com>:

> I haven't been following this discussion very closely since it started
> last month. What's the latest version of each patch, what do they do,
> and who vouches for them?

Hello Gwern, I am attaching the latest set of patches, which contains
a bug fix and documentation improvements.

Changes:
 * Add an option `alwaysHighlight :: Bool` to XPConfig which always
highlights the first completion if it is True.
 * Add mkPromptWithModes, which creates a XPrompt given a list of XPrompt`s.

["xmonad-launcher.dpatch" (application/octet-stream)]

7 patches for repository http://code.haskell.org/XMonadContrib:

Thu Jun 28 12:17:49 CEST 2012  c.lopez@kmels.net
  * Changes on XPrompt:
    
      * Adds mkPromptWithModes, creates a prompt given a list of modes (list of \
XPType).  
      * Adds Setting `alwaysHighlight` to defaultXPConfig. When set to true, \
autocompletion always highlight the first result if it is not highlighted.  
  Adds module XMonad.Actions.Launcher. This module allows to combine and switch \
between instances of XPrompt. It includes a default set of modes which require the \
programs `hoogle`, `locate` and `calc` to be installed to work properly.  

Thu Jun 28 13:45:33 CEST 2012  c.lopez@kmels.net
  * Removes warnings, adds a browser value for LauncherConfig in haddock comments
  

Sat Aug 11 12:48:05 CEST 2012  c.lopez@kmels.net
  * Correctly get the autocompletion item when alwaysHighlight in XMonad.Prompt is \
True

Sat Aug 11 13:25:02 CEST 2012  c.lopez@kmels.net
  * Fixes typos in Actions.Launcher haddock documentation

Sun Aug 26 10:31:37 CEST 2012  c.lopez@kmels.net
  * fix a bug when ncompletions = nrows

Sun Aug 26 10:54:26 CEST 2012  c.lopez@kmels.net
  * Improve comments, add an error throw that shouldn't happen

Sun Aug 26 11:17:16 CEST 2012  c.lopez@kmels.net
  * Improves haddock documentation

New patches:

[Changes on XPrompt:
c.lopez@kmels.net**20120628101749
 Ignore-this: 2384f5c1b886716b3d9785877c2e32f9
   
     * Adds mkPromptWithModes, creates a prompt given a list of modes (list of \
XPType).  
     * Adds Setting `alwaysHighlight` to defaultXPConfig. When set to true, \
autocompletion always highlight the first result if it is not highlighted.  
 Adds module XMonad.Actions.Launcher. This module allows to combine and switch \
between instances of XPrompt. It includes a default set of modes which require the \
programs `hoogle`, `locate` and `calc` to be installed to work properly.  
] {
addfile ./XMonad/Actions/Launcher.hs
hunk ./XMonad/Actions/Launcher.hs 1
+{- |
+Module      :  XMonad.Actions.Launcher
+Copyright   :  (C) 2012 Carlos López-Camey
+License     :  None; public domain
hunk ./XMonad/Actions/Launcher.hs 6
+Maintainer  :  <c.lopez@kmels.net>
+Stability   :  unstable
+
+A set of prompts for XMonad
+-}
+
+module XMonad.Actions.Launcher(
+  -- * Description and use
+  -- $description
+  defaultLauncherModes
+  , ExtensionActions
+  , LauncherConfig(..)
+  , LocateFileMode
+  , LocateFileRegexMode
+  , launcherPrompt
+  -- * ToDo
+  -- $todo
+) where
+
+import           Data.List        (find, findIndex, isPrefixOf, tails)
+import qualified Data.Map         as M
+import           Data.Maybe       (fromMaybe, isJust)
+import           System.Directory (doesDirectoryExist)
+import           XMonad           hiding (config)
+import           XMonad.Prompt
+import           XMonad.Util.Run
+
+{- $description
+    This module lets you combine and switch between different types of prompts \
(XMonad.Prompt). It includes a set of default modes: +    
+       * Hoogle mode: Search for functions using hoogle, choosing a function leads \
you to documentation in Haddock. +       
+       * Locate mode: Search for files using locate, choosing a file opens it with a \
program you specify depending on the file's extension. +       
+       * Locate regexp: Same as locate mode but autocomplete works with regular \
expressions.   +       
+       * Calc: Uses the program calc to do calculations.
+
+    To use the default modes, modify your .xmonad:
+   
+    > import XMonad.Prompt(defaultXPConfig)
+    > import XMonad.Actions.Launcher
+
+    > ((modm .|. controlMask, xK_l), launcherPrompt kmelsXPConfig $ \
defaultLauncherModes launcherConfig)    +    
+    A LauncherConfig contains settings for the default modes, modify them \
accordingly.  +    
+    > launcherConfig = LauncherConfig { pathToHoogle = "/home/YOU/.cabal/bin/hoogle" \
, actionsByExtension  = extensionActions } +    
+@extensionActions :: M.Map String (String -> X())
+extensionActions = M.fromList $ [
+ (\".hs\", \p -> spawn $ \"emacs \" ++ p)
+ , (\".pdf\", \p -> spawn $ \"acroread \" ++ p)
+ , (\".*\", \p -> spawn $ \"emacs \" ++ p) --match with any files
+ , (\"/\", \p -> spawn $ \"nautilus \" ++ p) --match with directories 
+ ]@
+ 
+ To try it, restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should \
pop up.  + 
+ You can change mode with xK_grave if you used defaultXP or change the value of \
changeModeKey in your XPConfig-} +
+data LocateFileMode = LMode ExtensionActions
+data LocateFileRegexMode = LRMode ExtensionActions
+data HoogleMode = HMode FilePath String --path to hoogle e.g. \
"/home/me/.cabal/bin/hoogle" +data CalculatorMode = CalcMode
+
+data LauncherConfig = LauncherConfig {  
+  browser                :: String
+  , pathToHoogle         :: String
+  , actionsByExtension   :: ExtensionActions
+}
+
+type ExtensionActions = M.Map String (String -> X())
+
+-- | Uses the program `locate` to list files
+instance XPrompt LocateFileMode where
+  showXPrompt (LMode _) = "locate %s> "
+  completionFunction (LMode _) = \s -> if (s == "" || last s == ' ') then return [] \
else (completionFunctionWith "locate" ["--limit","5",s]) +  modeAction (LMode \
actions) _ fp = spawnWithActions actions fp +
+-- | Uses the program `locate --regex` to list files
+instance XPrompt LocateFileRegexMode where
+  showXPrompt (LRMode _) = "locate --regexp %s> "
+  completionFunction (LRMode _) = \s -> if (s == "" || last s == ' ') then return [] \
else (completionFunctionWith "locate" ["--limit","5","--regexp",s]) +  modeAction \
(LRMode actions) _ fp = spawnWithActions actions fp +
+-- | Uses the command `calc` to compute arithmetic expressions
+instance XPrompt CalculatorMode where
+  showXPrompt CalcMode = "calc %s> "
+  commandToComplete CalcMode = id --send the whole string to `calc`
+  completionFunction CalcMode = \s -> if (length s == 0) then return [] else do
+    fmap lines $ runProcessWithInput "calc" [s] ""
+  modeAction CalcMode _ _ = return () -- do nothing; this might copy the result to \
the clipboard +
+-- | Uses the program `hoogle` to search for functions
+instance XPrompt HoogleMode where
+  showXPrompt _ = "hoogle %s> "
+  commandToComplete _ = id
+  completionFunction (HMode pathToHoogleBin' _) = \s -> completionFunctionWith \
pathToHoogleBin' ["--count","5",s] +  -- This action calls hoogle again to find the \
URL corresponding to the autocompleted item +  modeAction (HMode pathToHoogleBin'' \
browser) query result = do +    completionsWithLink <- liftIO $ \
completionFunctionWith pathToHoogleBin'' ["--count","5","--link",query] +    let link \
= do +          s <- find (isJust . \c -> findSeqIndex c result) completionsWithLink
+          i <- findSeqIndex s "http://"
+          return $ drop i s
+    case link of
+       Just l -> spawn $ browser ++ " " ++ l
+       _      -> return ()
+    where
+      -- | Receives a sublist and a list. It returns the index where the sublist \
appears in the list. +      findSeqIndex :: (Eq a) => [a] -> [a] -> Maybe Int
+      findSeqIndex xs xss = findIndex (isPrefixOf xss) $ tails xs
+
+-- | Creates an autocompletion function for a programm given the program's name and \
a list of args to send to the command. +completionFunctionWith :: String -> [String] \
-> IO [String] +completionFunctionWith cmd args = do fmap lines $ runProcessWithInput \
cmd args "" +
+-- | Creates a prompt with the given modes
+launcherPrompt :: XPConfig -> [XPMode] -> X()
+launcherPrompt config modes = mkXPromptWithModes modes config
+
+-- | Create a list of modes based on :
+-- a list of extensions mapped to actions
+-- the path to hoogle
+defaultLauncherModes :: LauncherConfig -> [XPMode]
+defaultLauncherModes cnf = let
+  ph           = pathToHoogle cnf
+  actions      = actionsByExtension cnf
+  in [ hoogleMode ph $ browser cnf
+     , locateMode actions
+     , locateRegexMode actions
+     , calcMode]
+
+locateMode, locateRegexMode :: ExtensionActions -> XPMode
+locateMode actions = XPT $ LMode actions
+locateRegexMode actions = XPT $ LRMode actions
+hoogleMode :: FilePath -> String -> XPMode
+hoogleMode pathToHoogleBin browser = XPT $ HMode pathToHoogleBin browser
+calcMode :: XPMode
+calcMode = XPT CalcMode
+
+-- | This function takes a map of extensions and a path file. It uses the map to \
find the pattern that matches the file path, then the corresponding program (listed \
in the map) is spawned. +spawnWithActions :: ExtensionActions -> FilePath -> X()
+spawnWithActions actions fp = do
+  isDirectoryPath <- liftIO $ doesDirectoryExist fp
+  let
+    takeExtension = \p -> "." ++ (reverse . takeWhile (/= '.') $ reverse p) --it \
includes the dot +    -- Patterns defined by the user
+    extAction = M.lookup (takeExtension fp) actions
+    dirAction = if (isDirectoryPath) then M.lookup "/" actions else Nothing -- / \
represents a directory +    anyFileAction = M.lookup ".*" actions  -- .* represents \
any file +    action = fromMaybe (spawnNoPatternMessage (takeExtension fp)) $ \
extAction `orElse1` dirAction `orElse1` anyFileAction +  action fp
+     where
+       -- | This function is defined in Data.Generics.Aliases (package syb "Scrap \
your boilerplate"), defined here to avoid dependency +       orElse1 :: Maybe a -> \
Maybe a -> Maybe a +       x `orElse1` y = case x of
+         Just _  -> x
+         Nothing -> y
+       spawnNoPatternMessage :: String -> String -> X ()
+       spawnNoPatternMessage fileExt _ = spawn $ "xmessage No action specified for \
file extension " ++ fileExt ++ ", add a default action by matching the extension \
\".*\" in the action map sent to launcherPrompt" +
+{- $todo  
+     * Switch to mode by name of the prompt, 1. ':' at an empty(?) buffer, 2. \
autocomplete name in buffer should happen, 3. switch to mode with enter (cancel \
switch with C-g) +     
+     * Support for actions of type String -> X a
+     
+     * Hoogle mode: add a setting in the action to either go to documentation or to \
the source code (needs hoogle change?) +     
+     * Hoogle mode: add setting to query hoogle at haskell.org instead (with \
&mode=json) +-}
hunk ./XMonad/Prompt.hs 21
       -- $usage
       mkXPrompt
     , mkXPromptWithReturn
+    , mkXPromptWithModes
     , amberXPConfig
     , defaultXPConfig
     , greenXPConfig
hunk ./XMonad/Prompt.hs 25
+    , XPMode 
     , XPType (..)
     , XPPosition (..)
     , XPConfig (..)
hunk ./XMonad/Prompt.hs 114
         , screen             :: !Rectangle
         , complWin           :: Maybe Window
         , complWinDim        :: Maybe ComplWindowDim
-        , completionFunction :: String -> IO [String]
+        , complIndex         :: !(Int,Int)
         , showComplWin       :: Bool
hunk ./XMonad/Prompt.hs 116
+        , operationMode      :: XPOperationMode
         , gcon               :: !GC
         , fontS              :: !XMonadFont
hunk ./XMonad/Prompt.hs 119
-        , xptype             :: !XPType
         , commandHistory     :: W.Stack String
         , offset             :: !Int
         , config             :: XPConfig
hunk ./XMonad/Prompt.hs 136
         , borderColor       :: String     -- ^ Border color
         , promptBorderWidth :: !Dimension -- ^ Border width
         , position          :: XPPosition -- ^ Position: 'Top' or 'Bottom'
-        , height            :: !Dimension -- ^ Window height
+        , alwaysHighlight   :: !Bool      -- ^ Always highlight an item, overriden \
to True with multiple modes. This implies having *one* column of autocompletions \
only. +        , height            :: !Dimension -- ^ Window height        
         , historySize       :: !Int       -- ^ The number of history entries to be \
saved  , historyFilter     :: [String] -> [String]
                                          -- ^ a filter to determine which
hunk ./XMonad/Prompt.hs 145
         , promptKeymap      :: M.Map (KeyMask,KeySym) (XP ())
                                          -- ^ Mapping from key combinations to \
                actions
         , completionKey     :: KeySym     -- ^ Key that should trigger completion
+        , changeModeKey     :: KeySym     -- ^ Key to change mode (when the prompt \
                has multiple modes)
         , 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 hunk ./XMonad/Prompt.hs 156
         }
 
 data XPType = forall p . XPrompt p => XPT p
+type ComplFunction = String -> IO [String]
+type XPMode = XPType
+data XPOperationMode = XPSingleMode ComplFunction XPType | XPMultipleModes (W.Stack \
XPType)  
 instance Show XPType where
     show (XPT p) = showXPrompt p
hunk ./XMonad/Prompt.hs 168
     nextCompletion      (XPT t) = nextCompletion      t
     commandToComplete   (XPT t) = commandToComplete   t
     completionToCommand (XPT t) = completionToCommand t
+    completionFunction  (XPT t) = completionFunction  t
+    modeAction          (XPT t) = modeAction          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,
hunk ./XMonad/Prompt.hs 191
     -- printed in the command line when tab is pressed, given the
     -- string presently in the command line and the list of
     -- completion.
+    -- This function is not used when in multiple modes (because alwaysHighlight in \
XPConfig is True)  nextCompletion :: t -> String -> [String] -> String
     nextCompletion = getNextOfLastWord
 
hunk ./XMonad/Prompt.hs 197
     -- | This method is used to generate the string to be passed to
     -- the completion function.
+    -- This function is not used when in multiple modes (because alwaysHighlight in \
XPConfig is True)  commandToComplete :: t -> String -> String
     commandToComplete _ = getLastWord
 
hunk ./XMonad/Prompt.hs 211
     completionToCommand :: t -> String -> String
     completionToCommand _ c = c
 
+    -- | When the prompt has multiple modes, this is the function
+    -- used to generate the autocompletion list.
+    -- The argument passed to this function is given by `commandToComplete`    
+    -- The default implementation shows an error message.
+    completionFunction :: t -> ComplFunction
+    completionFunction t = \_ -> return ["Completions for " ++ (showXPrompt t) ++ " \
could not be loaded"] +    
+    -- | When the prompt has multiple modes, this function is called 
+    -- when the user picked an item from the autocompletion list.
+    -- The first argument is the autocompleted item's text. 
+    -- The second argument is the query made by the user (written in the prompt's \
buffer). +    modeAction :: t -> String -> String -> X ()
+    modeAction _ _ _ = return ()
+    
 data XPPosition = Top
                 | Bottom
                   deriving (Show,Read)
hunk ./XMonad/Prompt.hs 241
         , promptBorderWidth = 1
         , promptKeymap      = defaultXPKeymap
         , completionKey     = xK_Tab
+        , changeModeKey     = xK_asciitilde
         , position          = Bottom
         , height            = 18
         , historySize       = 256
hunk ./XMonad/Prompt.hs 250
         , autoComplete      = Nothing
         , showCompletionOnTab = False
         , searchPredicate   = isPrefixOf
+        , alwaysHighlight   = False
         }
 greenXPConfig = defaultXPConfig { fgColor = "green", bgColor = "black", \
promptBorderWidth = 0 }  amberXPConfig = defaultXPConfig { fgColor = "#ca8f2d", \
bgColor = "black", fgHLight = "#eaaf4c" } hunk ./XMonad/Prompt.hs 255
 
-type ComplFunction = String -> IO [String]
-
-initState :: XPrompt p => Display -> Window -> Window -> Rectangle -> ComplFunction
-          -> GC -> XMonadFont -> p -> [String] -> XPConfig -> KeyMask -> XPState
-initState d rw w s compl gc fonts pt h c nm =
+initState :: Display -> Window -> Window -> Rectangle -> XPOperationMode
+          -> GC -> XMonadFont -> [String] -> XPConfig -> KeyMask -> XPState
+initState d rw w s opMode gc fonts h c nm =
     XPS { dpy                = d
         , rootw              = rw
         , win                = w
hunk ./XMonad/Prompt.hs 264
         , screen             = s
         , complWin           = Nothing
         , complWinDim        = Nothing
-        , completionFunction = compl
         , showComplWin       = not (showCompletionOnTab c)
hunk ./XMonad/Prompt.hs 265
+        , operationMode      = opMode
         , gcon               = gc
         , fontS              = fonts
hunk ./XMonad/Prompt.hs 268
-        , xptype             = XPT pt
         , commandHistory     = W.Stack { W.focus = defaultText c
                                        , W.up    = []
                                        , W.down  = h }
hunk ./XMonad/Prompt.hs 271
+        , complIndex         = (0,0) --(column index, row index), used when \
`alwaysHighlight` in XPConfig is True  , offset             = length (defaultText c)
         , config             = c
         , successful         = False
hunk ./XMonad/Prompt.hs 279
         , numlockMask        = nm
         }
 
+-- Returns the current XPType
+currentXPMode :: XPState -> XPType
+currentXPMode st = case operationMode st of
+  XPMultipleModes modes -> W.focus modes
+  XPSingleMode _ xptype -> xptype
+
+-- When in multiple modes, this function sets the next mode
+-- in the list of modes as active
+setNextMode :: XPState -> XPState
+setNextMode st = case operationMode st of
+  XPMultipleModes modes -> case W.down modes of
+    [] -> st -- there is no next mode, return same state
+    (m:ms) -> let
+      currentMode = W.focus modes
+      in st { operationMode = XPMultipleModes W.Stack { W.up = [], W.focus = m, \
W.down = ms ++ [currentMode]}} --set next and move previous current mode to the of \
the stack +  _ -> st --nothing to do, the prompt's operation has only one mode
+  
+-- Returns the highlighted item
+highlightedItem :: XPState -> [String] -> String
+highlightedItem st' completions = case complWinDim st' of 
+  Nothing -> "" -- when there isn't any compl win, we can't say how many cols,rows \
there are +  Just winDim -> 
+    let
+      (_,_,_,_,xx,yy) = winDim
+      complMatrix = splitInSubListsAt (length yy) (take (length xx * length yy) \
completions) +      (col_index,row_index) = (complIndex st')
+    in case completions of
+      [] -> "" -- no completions
+      _ -> complMatrix !! col_index !! row_index
+      
 -- this would be much easier with functional references
 command :: XPState -> String
 command = W.focus . commandHistory
hunk ./XMonad/Prompt.hs 343
   fs <- initXMF (font conf)
   numlock <- gets $ X.numberlockMask
   let hs = fromMaybe [] $ M.lookup (showXPrompt t) hist
-      st = initState d rw w s compl gc fs (XPT t) hs conf numlock
+      om = (XPSingleMode compl (XPT t)) --operation mode
+      st = initState d rw w s om gc fs hs conf numlock
   st' <- io $ execStateT runXP st
 
   releaseXMF fs
hunk ./XMonad/Prompt.hs 349
   io $ freeGC d gc
-  if successful st'
-    then do
-      let prune = take (historySize conf)
-      io $ writeHistory $ M.insertWith
-                                (\xs ys -> prune . historyFilter conf $ xs ++ ys)
-                                (showXPrompt t)
-                                (prune $ historyFilter conf [command st'])
-                                hist
+  if successful st' then do
+    completions <- liftIO $ do getCompletionFunction st' (commandToComplete \
(currentXPMode st') (command st')) `catch` \(SomeException _) -> return []     +    \
let  +      prune = take (historySize conf)    
+      
+    io $ writeHistory $ M.insertWith
+      (\xs ys -> prune . historyFilter conf $ xs ++ ys)
+      (showXPrompt t)
+      (prune $ 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
hunk ./XMonad/Prompt.hs 362
-      Just <$> action (command st')
+      --When alwaysHighlight is True, autocompletion is handled with indexes. 
+      --When it is false, it is handled depending on the prompt buffer's value
+    let selectedCompletion = case alwaysHighlight (config st') of 
+          False -> command st'
+          True -> highlightedItem st' completions
+    --Just <$> action selectedCompletion 
+    Just <$> action selectedCompletion 
     else return Nothing
 
 -- | Creates a prompt given:
hunk ./XMonad/Prompt.hs 385
 mkXPrompt :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
 mkXPrompt t conf compl action = mkXPromptWithReturn t conf compl action >> return ()
 
+-- | Creates a prompt with multiple modes given:
+--
+-- * A non-empty list of modes
+-- * A prompt configuration
+--
+-- The created prompt allows to switch between modes with `changeModeKey` in `conf`. \
The modes are  +-- instances of XPrompt. See XMonad.Actions.Launcher for more details
+--
+-- The argument supplied to the action to execute is always the current highlighted \
item,  +-- that means that this prompt overrides the value `alwaysHighlight` for its \
configuration to True. +mkXPromptWithModes :: [XPType] -> XPConfig -> X ()
+mkXPromptWithModes modes conf = do
+  XConf { display = d, theRoot = rw } <- ask
+  s    <- gets $ screenRect . W.screenDetail . W.current . windowset
+  hist <- io readHistory
+  w    <- io $ createWin d rw conf s
+  io $ selectInput d w $ exposureMask .|. keyPressMask
+  gc <- io $ createGC d w
+  io $ setGraphicsExposures d gc False
+  fs <- initXMF (font conf)
+  numlock <- gets $ X.numberlockMask
+  let
+    defaultMode = head modes
+    hs = fromMaybe [] $ M.lookup (showXPrompt defaultMode) hist
+    modeStack = W.Stack{ W.focus = defaultMode --current mode
+                       , W.up = []
+                       , W.down = tail modes --other modes
+                       }
+    st = initState d rw w s (XPMultipleModes modeStack) gc fs hs conf { \
alwaysHighlight = True} numlock +  st' <- io $ execStateT runXP st
+
+  releaseXMF fs
+  io $ freeGC d gc
+
+  if successful st' then do
+    completions <- liftIO $ do getCompletionFunction st' (commandToComplete \
(currentXPMode st') (command st')) `catch` \(SomeException _) -> return [] +    
+    let 
+      prune = take (historySize conf)
+
+      -- insert into history the buffers value
+    io $ writeHistory $ M.insertWith
+      (\xs ys -> prune . historyFilter conf $ xs ++ ys)
+      (showXPrompt defaultMode)
+      (prune $ historyFilter conf [command st'])
+      hist
+
+    case operationMode st' of
+      XPMultipleModes ms -> let
+        action = modeAction $ W.focus ms
+        in action (command st') (highlightedItem st' completions)
+      _ -> return () --This should never happen, we are creating a prompt with \
multiple modes, so its operationMode should have been constructed with XPMultipleMode \
+    else +      return ()
+
+
 runXP :: XP ()
 runXP = do
   (d,w) <- gets (dpy &&& win)
hunk ./XMonad/Prompt.hs 482
 handle :: KeyStroke -> Event -> XP ()
 handle ks@(sym,_) e@(KeyEvent {ev_event_type = t, ev_state = m}) = do
   complKey <- gets $ completionKey . config
+  chgModeKey <- gets $ changeModeKey . config
   c <- getCompletions
   when (length c > 1) $ modify (\s -> s { showComplWin = True })
   if complKey == sym
hunk ./XMonad/Prompt.hs 487
      then completionHandle c ks e
-     else when (t == keyPress) $ keyPressHandle m ks
+     else if (sym == chgModeKey) then
+           do
+             modify setNextMode
+             updateWindows
+          else when (t == keyPress) $ keyPressHandle m ks
 handle _ (ExposeEvent {ev_window = w}) = do
   st <- get
   when (win st == w) updateWindows
hunk ./XMonad/Prompt.hs 501
 completionHandle ::  [String] -> KeyStroke -> Event -> XP ()
 completionHandle c ks@(sym,_) (KeyEvent { ev_event_type = t, ev_state = m }) = do
   complKey <- gets $ completionKey . config
+  alwaysHlight <- gets $ alwaysHighlight . config
   case () of
     () | t == keyPress && sym == complKey ->
           do
hunk ./XMonad/Prompt.hs 506
             st <- get
-            let updateState l =
-                    let new_command = nextCompletion (xptype st) (command st) l
-                    in modify $ \s -> setCommand new_command $ s { offset = length \
                new_command }
-                updateWins  l = redrawWindows l >>
-                                eventLoop (completionHandle l)
+            let updateState l = case alwaysHlight of
+                  --We will modify the next command (buffer's value), to be able to \
highlight the autocompletion (nextCompletion and commandToComplete implementation \
dependent) +                  False -> let new_command = nextCompletion \
(currentXPMode st) (command st) l +                           in modify $ \s -> \
setCommand new_command $ s { offset = length new_command } +                  --TODO: \
Scroll or paginate results +                  True  -> modify $ \s -> s { complIndex \
= nextComplIndex st (length l)} +                updateWins l = redrawWindows l >> \
eventLoop (completionHandle l)  case c of
               []  -> updateWindows   >> eventLoop handle
               [x] -> updateState [x] >> getCompletions >>= updateWins
hunk ./XMonad/Prompt.hs 522
 -- some other event: go back to main loop
 completionHandle _ k e = handle k e
 
+--Receives an state of the prompt, the size of the autocompletion list and returns \
the column,row  +--which should be highlighted next 
+nextComplIndex :: XPState -> Int -> (Int,Int) 
+nextComplIndex st nitems = case complWinDim st of 
+  Nothing -> (0,0) --no window dims (just destroyed or not created)
+  Just winDim -> let
+    (_,_,_,_,xx,yy) = winDim 
+    (ncols,nrows) = (nitems `div` length yy + if (nitems `mod` length yy > 0) then 1 \
else 0, length yy)  +    (currentcol,currentrow) = complIndex st
+    in if (currentcol + 1 >= ncols) then --hlight is in the last column
+         if (currentrow + 1 < (nitems `mod` nrows) ) then --hlight is still not at \
the last row +           (currentcol, currentrow + 1)
+         else
+           (0,0)
+       else if(currentrow + 1 < nrows) then --hlight not at the last row
+              (currentcol, currentrow + 1)
+            else
+              (currentcol + 1, 0)              
 
 tryAutoComplete :: XP Bool
 tryAutoComplete = do
hunk ./XMonad/Prompt.hs 552
         Nothing    -> return False
   where runCompleted cmd delay = do
             st <- get
-            let new_command = nextCompletion (xptype st) (command st) [cmd]
+            let new_command = nextCompletion (currentXPMode st) (command st) [cmd]
             modify $ setCommand "autocompleting..."
             updateWindows
             io $ threadDelay delay
hunk ./XMonad/Prompt.hs 731
 flushString :: XP ()
 flushString = modify $ \s -> setCommand "" $ s { offset = 0}
 
+--reset index if config has `alwaysHighlight`. The inserted char could imply fewer \
autocompletions.  +--If the current index was column 2, row 1 and now there are only \
4 autocompletion rows with 1 column, what should we highlight? Set it to the first \
and start navigation again   +resetComplIndex :: XPState -> XPState
+resetComplIndex st = if (alwaysHighlight $ config st) then st { complIndex = (0,0) } \
else st +
 -- | Insert a character at the cursor position
 insertString :: String -> XP ()
 insertString str =
hunk ./XMonad/Prompt.hs 739
-  modify $ \s -> setCommand (c (command s) (offset s)) $ s { offset = o (offset s)}
+  modify $ \s -> let 
+    cmd = (c (command s) (offset s))
+    st = resetComplIndex $ s { offset = o (offset s)}
+    in setCommand cmd st
   where o oo = oo + length str
         c oc oo | oo >= length oc = oc ++ str
                 | otherwise = f ++ str ++ ss
hunk ./XMonad/Prompt.hs 848
 printPrompt drw = do
   st <- get
   let (gc,(c,(d,fs))) = (gcon &&& config &&& dpy &&& fontS) st
-      (prt,(com,off)) = (show . xptype &&& command &&& offset) st
+      (prt,(com,off)) = (show . currentXPMode &&& command &&& offset) st
       str = prt ++ com
       -- break the string in 3 parts: till the cursor, the cursor and the rest
       (f,p,ss) = if off >= length com
hunk ./XMonad/Prompt.hs 870
   -- reverse the colors and print the rest of the string
   draw (fgColor c) (bgColor c) (x + fromIntegral (fsl + psl)) y ss
 
+-- get the current completion function depending on the active mode
+getCompletionFunction :: XPState -> ComplFunction
+getCompletionFunction st = case operationMode st of
+  XPSingleMode compl _ -> compl
+  XPMultipleModes modes -> completionFunction $ W.focus modes
+  
 -- Completions
hunk ./XMonad/Prompt.hs 877
-
 getCompletions :: XP [String]
 getCompletions = do
   s <- get
hunk ./XMonad/Prompt.hs 880
-  io $ completionFunction s (commandToComplete (xptype s) (command s))
+  io $ getCompletionFunction s (commandToComplete (currentXPMode s) (command s))
        `catch` \(SomeException _) -> return []
 
 setComplWin :: Window -> ComplWindowDim -> XP ()
hunk ./XMonad/Prompt.hs 935
       xp = (asc + desc) `div` 2
       yy = map fi . take (fi actual_rows) $ [yp,(yp + ht)..]
       xx = take (fi columns) [xp,(xp + max_compl_len)..]
-
+  
   return (rect_x scr + x, rect_y scr + fi y, wh, actual_height, xx, yy)
 
 drawComplWin :: Window -> [String] -> XP ()
hunk ./XMonad/Prompt.hs 955
                          (defaultDepthOfScreen scr)
   io $ fillDrawable d p gc border bgcolor (fi bw) wh ht
   let ac = splitInSubListsAt (length yy) (take (length xx * length yy) compl)
+
   printComplList d p gc (fgColor c) (bgColor c) xx yy ac
hunk ./XMonad/Prompt.hs 957
+  --lift $ spawn $ "xmessage " ++ " ac: " ++ show ac  ++ " xx: " ++ show xx ++ " \
length xx: " ++ show (length xx) ++ " yy: " ++ show (length yy)  io $ copyArea d p w \
gc 0 0 wh ht 0 0  io $ freePixmap d p
 
hunk ./XMonad/Prompt.hs 978
             Nothing -> recreate
      else destroyComplWin
 
+-- given a string and  a matrix of strings, find the column and row indexes in which \
the string appears.  +-- if the string is not in the matrix, the function returns \
(0,0) +findComplIndex :: String -> [[String]] -> (Int,Int)
+findComplIndex x xss = let 
+  colIndex = fromMaybe 0 $ findIndex (\cols -> x `elem` cols) xss
+  rowIndex = fromMaybe 0 $ elemIndex x $ (!!) xss colIndex
+  in (colIndex,rowIndex)
+
 printComplList :: Display -> Drawable -> GC -> String -> String
                -> [Position] -> [Position] -> [[String]] -> XP ()
 printComplList d drw gc fc bc xs ys sss =
hunk ./XMonad/Prompt.hs 990
     zipWithM_ (\x ss ->
-        zipWithM_ (\y s -> do
-            st <- get
-            let (f,b) = if completionToCommand (xptype st) s == commandToComplete \
                (xptype st) (command st)
-                            then (fgHLight $ config st,bgHLight $ config st)
-                            else (fc,bc)
-            printStringXMF d drw (fontS st) gc f b x y s)
+        zipWithM_ (\y item -> do
+            st <- get 
+            alwaysHlight <- gets $ alwaysHighlight . config                     
+            let (f,b) = case alwaysHlight of 
+                  True -> --find the column, row in which this item is and decide if \
we should highlight +                    let 
+                      colIndex = fromMaybe 0 $ findIndex (\cols -> item `elem` cols) \
sss +                      rowIndex = fromMaybe 0 $ elemIndex item $ (!!) sss \
colIndex +                    in
+                     if ((complIndex st) == (colIndex,rowIndex)) then (fgHLight $ \
config st,bgHLight $ config st) +                     else (fc,bc)
+                  False -> if completionToCommand (currentXPMode st) item == \
commandToComplete (currentXPMode st) (command st) +                           then \
(fgHLight $ config st,bgHLight $ config st) +                           else (fc,bc)
+            printStringXMF d drw (fontS st) gc f b x y item)
         ys ss) xs sss
hunk ./XMonad/Prompt.hs 1006
-
+                    
 -- History
 
 type History = M.Map String [String]
hunk ./xmonad-contrib.cabal 105
                         XMonad.Actions.FocusNth
                         XMonad.Actions.GridSelect
                         XMonad.Actions.GroupNavigation
+                        XMonad.Actions.Launcher
                         XMonad.Actions.MessageFeedback
                         XMonad.Actions.MouseGestures
                         XMonad.Actions.MouseResize
}
[Removes warnings, adds a browser value for LauncherConfig in haddock comments
c.lopez@kmels.net**20120628114533
 Ignore-this: 2610cf63594db3df61bac52f3d8f5836
 
] {
hunk ./XMonad/Actions/Launcher.hs 53
     
     A LauncherConfig contains settings for the default modes, modify them \
accordingly.   
-    > launcherConfig = LauncherConfig { pathToHoogle = "/home/YOU/.cabal/bin/hoogle" \
, actionsByExtension  = extensionActions } +    > launcherConfig = LauncherConfig { \
pathToHoogle = "/home/YOU/.cabal/bin/hoogle" , browser = "firefox" , \
actionsByExtension  = extensionActions }  
 @extensionActions :: M.Map String (String -> X())
 extensionActions = M.fromList $ [
hunk ./XMonad/Actions/Launcher.hs 106
   commandToComplete _ = id
   completionFunction (HMode pathToHoogleBin' _) = \s -> completionFunctionWith \
                pathToHoogleBin' ["--count","5",s]
   -- This action calls hoogle again to find the URL corresponding to the \
                autocompleted item
-  modeAction (HMode pathToHoogleBin'' browser) query result = do
+  modeAction (HMode pathToHoogleBin'' browser') query result = do
     completionsWithLink <- liftIO $ completionFunctionWith pathToHoogleBin'' \
["--count","5","--link",query]  let link = do
           s <- find (isJust . \c -> findSeqIndex c result) completionsWithLink
hunk ./XMonad/Actions/Launcher.hs 113
           i <- findSeqIndex s "http://"
           return $ drop i s
     case link of
-       Just l -> spawn $ browser ++ " " ++ l
+       Just l -> spawn $ browser' ++ " " ++ l
        _      -> return ()
     where
       -- | Receives a sublist and a list. It returns the index where the sublist \
appears in the list. hunk ./XMonad/Actions/Launcher.hs 144
 locateMode actions = XPT $ LMode actions
 locateRegexMode actions = XPT $ LRMode actions
 hoogleMode :: FilePath -> String -> XPMode
-hoogleMode pathToHoogleBin browser = XPT $ HMode pathToHoogleBin browser
+hoogleMode pathToHoogleBin browser' = XPT $ HMode pathToHoogleBin browser'
 calcMode :: XPMode
 calcMode = XPT CalcMode
 
}
[Correctly get the autocompletion item when alwaysHighlight in XMonad.Prompt is True
c.lopez@kmels.net**20120811104805
 Ignore-this: fa2600df210c7d3472a797f19fb31a7
] {
hunk ./XMonad/Prompt.hs 25
     , amberXPConfig
     , defaultXPConfig
     , greenXPConfig
-    , XPMode 
+    , XPMode
     , XPType (..)
     , XPPosition (..)
     , XPConfig (..)
hunk ./XMonad/Prompt.hs 71
     , XPState
     ) where
 
-import Prelude hiding (catch)
+import           Prelude                      hiding (catch)
 
hunk ./XMonad/Prompt.hs 73
-import XMonad  hiding (config, cleanMask)
-import qualified XMonad as X (numberlockMask)
-import qualified XMonad.StackSet as W
-import XMonad.Util.Font
-import XMonad.Util.Types
-import XMonad.Util.XSelection (getSelection)
+import           XMonad                       hiding (cleanMask, config)
+import qualified XMonad                       as X (numberlockMask)
+import qualified XMonad.StackSet              as W
+import           XMonad.Util.Font
+import           XMonad.Util.Types
+import           XMonad.Util.XSelection       (getSelection)
 
hunk ./XMonad/Prompt.hs 80
-import Codec.Binary.UTF8.String (decodeString)
-import Control.Applicative ((<$>))
-import Control.Arrow ((&&&),(***),first)
-import Control.Concurrent (threadDelay)
-import Control.Exception.Extensible hiding (handle)
-import Control.Monad.State
-import Data.Bits
-import Data.Char (isSpace)
-import Data.IORef
-import Data.List
-import Data.Maybe (fromMaybe)
-import Data.Set (fromList, toList)
-import System.Directory (getAppUserDataDirectory)
-import System.IO
-import System.Posix.Files
-import qualified Data.Map as M
+import           Codec.Binary.UTF8.String     (decodeString)
+import           Control.Applicative          ((<$>))
+import           Control.Arrow                (first, (&&&), (***))
+import           Control.Concurrent           (threadDelay)
+import           Control.Exception.Extensible hiding (handle)
+import           Control.Monad.State
+import           Data.Bits
+import           Data.Char                    (isSpace)
+import           Data.IORef
+import           Data.List
+import qualified Data.Map                     as M
+import           Data.Maybe                   (fromMaybe)
+import           Data.Set                     (fromList, toList)
+import           System.Directory             (getAppUserDataDirectory)
+import           System.IO
+import           System.Posix.Files
 
 -- $usage
 -- For usage examples see "XMonad.Prompt.Shell",
hunk ./XMonad/Prompt.hs 117
         , complIndex         :: !(Int,Int)
         , showComplWin       :: Bool
         , operationMode      :: XPOperationMode
+        , highlightedCompl   :: Maybe String
         , gcon               :: !GC
         , fontS              :: !XMonadFont
         , commandHistory     :: W.Stack String
hunk ./XMonad/Prompt.hs 138
         , promptBorderWidth :: !Dimension -- ^ Border width
         , position          :: XPPosition -- ^ Position: 'Top' or 'Bottom'
         , alwaysHighlight   :: !Bool      -- ^ Always highlight an item, overriden \
to True with multiple modes. This implies having *one* column of autocompletions \
                only.
-        , height            :: !Dimension -- ^ Window height        
+        , height            :: !Dimension -- ^ Window height
         , historySize       :: !Int       -- ^ The number of history entries to be \
saved  , historyFilter     :: [String] -> [String]
                                          -- ^ a filter to determine which
hunk ./XMonad/Prompt.hs 214
 
     -- | When the prompt has multiple modes, this is the function
     -- used to generate the autocompletion list.
-    -- The argument passed to this function is given by `commandToComplete`    
+    -- The argument passed to this function is given by `commandToComplete`
     -- The default implementation shows an error message.
     completionFunction :: t -> ComplFunction
     completionFunction t = \_ -> return ["Completions for " ++ (showXPrompt t) ++ " \
could not be loaded"] hunk ./XMonad/Prompt.hs 218
-    
-    -- | When the prompt has multiple modes, this function is called 
+
+    -- | When the prompt has multiple modes, this function is called
     -- when the user picked an item from the autocompletion list.
hunk ./XMonad/Prompt.hs 221
-    -- The first argument is the autocompleted item's text. 
+    -- The first argument is the autocompleted item's text.
     -- The second argument is the query made by the user (written in the prompt's \
buffer).  modeAction :: t -> String -> String -> X ()
     modeAction _ _ _ = return ()
hunk ./XMonad/Prompt.hs 225
-    
+
 data XPPosition = Top
                 | Bottom
                   deriving (Show,Read)
hunk ./XMonad/Prompt.hs 267
         , complWinDim        = Nothing
         , showComplWin       = not (showCompletionOnTab c)
         , operationMode      = opMode
+        , highlightedCompl   = Nothing
         , gcon               = gc
         , fontS              = fonts
         , commandHistory     = W.Stack { W.focus = defaultText c
hunk ./XMonad/Prompt.hs 297
       currentMode = W.focus modes
       in st { operationMode = XPMultipleModes W.Stack { W.up = [], W.focus = m, \
W.down = ms ++ [currentMode]}} --set next and move previous current mode to the of \
the stack  _ -> st --nothing to do, the prompt's operation has only one mode
-  
+
 -- Returns the highlighted item
hunk ./XMonad/Prompt.hs 299
-highlightedItem :: XPState -> [String] -> String
-highlightedItem st' completions = case complWinDim st' of 
-  Nothing -> "" -- when there isn't any compl win, we can't say how many cols,rows \
                there are
-  Just winDim -> 
+highlightedItem :: XPState -> [String] -> Maybe String
+highlightedItem st' completions = case complWinDim st' of
+  Nothing -> Nothing -- when there isn't any compl win, we can't say how many \
cols,rows there are +  Just winDim ->
     let
       (_,_,_,_,xx,yy) = winDim
       complMatrix = splitInSubListsAt (length yy) (take (length xx * length yy) \
completions) hunk ./XMonad/Prompt.hs 308
       (col_index,row_index) = (complIndex st')
     in case completions of
-      [] -> "" -- no completions
-      _ -> complMatrix !! col_index !! row_index
-      
+      [] -> Nothing
+      _ -> Just $ complMatrix !! col_index !! row_index
+
 -- this would be much easier with functional references
 command :: XPState -> String
 command = W.focus . commandHistory
hunk ./XMonad/Prompt.hs 318
 setCommand :: String -> XPState -> XPState
 setCommand xs s = s { commandHistory = (commandHistory s) { W.focus = xs }}
 
+setHighlightedCompl :: Maybe String -> XPState -> XPState
+setHighlightedCompl hc st = st { highlightedCompl = hc}
+
 -- | Sets the input string to the given value.
 setInput :: String -> XP ()
 setInput = modify . setCommand
hunk ./XMonad/Prompt.hs 355
   releaseXMF fs
   io $ freeGC d gc
   if successful st' then do
-    completions <- liftIO $ do getCompletionFunction st' (commandToComplete \
                (currentXPMode st') (command st')) `catch` \(SomeException _) -> \
                return []    
-    let 
-      prune = take (historySize conf)    
-      
+    let
+      prune = take (historySize conf)
+
     io $ writeHistory $ M.insertWith
       (\xs ys -> prune . historyFilter conf $ xs ++ ys)
       (showXPrompt t)
hunk ./XMonad/Prompt.hs 366
                                 -- we need to apply historyFilter before as well, \
                since
                                 -- otherwise the filter would not be applied if
                                 -- there is no history
-      --When alwaysHighlight is True, autocompletion is handled with indexes. 
+      --When alwaysHighlight is True, autocompletion is handled with indexes.
       --When it is false, it is handled depending on the prompt buffer's value
hunk ./XMonad/Prompt.hs 368
-    let selectedCompletion = case alwaysHighlight (config st') of 
+    let selectedCompletion = case alwaysHighlight (config st') of
           False -> command st'
hunk ./XMonad/Prompt.hs 370
-          True -> highlightedItem st' completions
-    --Just <$> action selectedCompletion 
-    Just <$> action selectedCompletion 
+          True -> fromMaybe "" $ highlightedCompl st'
+    Just <$> action selectedCompletion
     else return Nothing
 
 -- | Creates a prompt given:
hunk ./XMonad/Prompt.hs 393
 -- * A non-empty list of modes
 -- * A prompt configuration
 --
--- The created prompt allows to switch between modes with `changeModeKey` in `conf`. \
The modes are  +-- The created prompt allows to switch between modes with \
                `changeModeKey` in `conf`. The modes are
 -- instances of XPrompt. See XMonad.Actions.Launcher for more details
 --
hunk ./XMonad/Prompt.hs 396
--- The argument supplied to the action to execute is always the current highlighted \
item,  +-- The argument supplied to the action to execute is always the current \
                highlighted item,
 -- that means that this prompt overrides the value `alwaysHighlight` for its \
configuration to True.  mkXPromptWithModes :: [XPType] -> XPConfig -> X ()
 mkXPromptWithModes modes conf = do
hunk ./XMonad/Prompt.hs 423
   io $ freeGC d gc
 
   if successful st' then do
-    completions <- liftIO $ do getCompletionFunction st' (commandToComplete \
                (currentXPMode st') (command st')) `catch` \(SomeException _) -> \
                return []
-    
-    let 
+    let
       prune = take (historySize conf)
 
       -- insert into history the buffers value
hunk ./XMonad/Prompt.hs 436
     case operationMode st' of
       XPMultipleModes ms -> let
         action = modeAction $ W.focus ms
-        in action (command st') (highlightedItem st' completions)
+        in action (command st') $ (fromMaybe "" $ highlightedCompl st')
       _ -> return () --This should never happen, we are creating a prompt with \
multiple modes, so its operationMode should have been constructed with XPMultipleMode \
else  return ()
hunk ./XMonad/Prompt.hs 508
           do
             st <- get
             let updateState l = case alwaysHlight of
-                  --We will modify the next command (buffer's value), to be able to \
highlight the autocompletion (nextCompletion and commandToComplete implementation \
                dependent)
-                  False -> let new_command = nextCompletion (currentXPMode st) \
                (command st) l
-                           in modify $ \s -> setCommand new_command $ s { offset = \
length new_command } +                  -- modify the buffer's value
+                  False -> let newCommand = nextCompletion (currentXPMode st) \
(command st) l +                           in modify $ \s -> setCommand newCommand $ \
                s { offset = length newCommand, highlightedCompl = Just newCommand}
                   --TODO: Scroll or paginate results
hunk ./XMonad/Prompt.hs 512
-                  True  -> modify $ \s -> s { complIndex = nextComplIndex st (length \
l)} +                  True -> let complIndex' = nextComplIndex st (length l)
+                              highlightedCompl' = highlightedItem st { complIndex = \
complIndex'} c +                          in modify $ \s -> setHighlightedCompl \
                highlightedCompl' $ s { complIndex = complIndex' }
                 updateWins l = redrawWindows l >> eventLoop (completionHandle l)
             case c of
               []  -> updateWindows   >> eventLoop handle
hunk ./XMonad/Prompt.hs 525
 -- some other event: go back to main loop
 completionHandle _ k e = handle k e
 
---Receives an state of the prompt, the size of the autocompletion list and returns \
                the column,row 
---which should be highlighted next 
-nextComplIndex :: XPState -> Int -> (Int,Int) 
-nextComplIndex st nitems = case complWinDim st of 
+--Receives an state of the prompt, the size of the autocompletion list and returns \
the column,row +--which should be highlighted next
+nextComplIndex :: XPState -> Int -> (Int,Int)
+nextComplIndex st nitems = case complWinDim st of
   Nothing -> (0,0) --no window dims (just destroyed or not created)
   Just winDim -> let
hunk ./XMonad/Prompt.hs 531
-    (_,_,_,_,xx,yy) = winDim 
-    (ncols,nrows) = (nitems `div` length yy + if (nitems `mod` length yy > 0) then 1 \
else 0, length yy)  +    (_,_,_,_,_,yy) = winDim
+    (ncols,nrows) = (nitems `div` length yy + if (nitems `mod` length yy > 0) then 1 \
else 0, length yy)  (currentcol,currentrow) = complIndex st
     in if (currentcol + 1 >= ncols) then --hlight is in the last column
          if (currentrow + 1 < (nitems `mod` nrows) ) then --hlight is still not at \
the last row hunk ./XMonad/Prompt.hs 542
        else if(currentrow + 1 < nrows) then --hlight not at the last row
               (currentcol, currentrow + 1)
             else
-              (currentcol + 1, 0)              
+              (currentcol + 1, 0)
 
 tryAutoComplete :: XP Bool
 tryAutoComplete = do
hunk ./XMonad/Prompt.hs 668
                  _ -> when (kmask .&. controlMask == 0) $ do
                                  insertString (decodeString str)
                                  updateWindows
+                                 updateHighlightedCompl
                                  completed <- tryAutoComplete
                                  when completed $ setSuccess True >> setDone True
 
hunk ./XMonad/Prompt.hs 735
 flushString :: XP ()
 flushString = modify $ \s -> setCommand "" $ s { offset = 0}
 
---reset index if config has `alwaysHighlight`. The inserted char could imply fewer \
                autocompletions. 
---If the current index was column 2, row 1 and now there are only 4 autocompletion \
rows with 1 column, what should we highlight? Set it to the first and start \
navigation again   +--reset index if config has `alwaysHighlight`. The inserted char \
could imply fewer autocompletions. +--If the current index was column 2, row 1 and \
now there are only 4 autocompletion rows with 1 column, what should we highlight? Set \
it to the first and start navigation again  resetComplIndex :: XPState -> XPState
 resetComplIndex st = if (alwaysHighlight $ config st) then st { complIndex = (0,0) } \
else st  
hunk ./XMonad/Prompt.hs 743
 -- | Insert a character at the cursor position
 insertString :: String -> XP ()
 insertString str =
-  modify $ \s -> let 
+  modify $ \s -> let
     cmd = (c (command s) (offset s))
     st = resetComplIndex $ s { offset = o (offset s)}
     in setCommand cmd st
hunk ./XMonad/Prompt.hs 774
   modify $ \s -> s { offset = o (offset s) (command s)}
   where o oo c = if d == Prev then max 0 (oo - 1) else min (length c) (oo + 1)
 
--- | Move the cursor one word, using 'isSpace' as the default 
+-- | Move the cursor one word, using 'isSpace' as the default
 --   predicate for non-word characters.  See 'moveWord''.
 moveWord :: Direction1D -> XP ()
 moveWord = moveWord' isSpace
hunk ./XMonad/Prompt.hs 788
   o <- gets offset
   let (f,ss) = splitAt o c
       len = uncurry (+)
-          . (length *** (length . fst . break p)) 
+          . (length *** (length . fst . break p))
           . break (not . p)
       newoff = case d of
                  Prev -> o - len (reverse f)
hunk ./XMonad/Prompt.hs 800
                                in s { commandHistory = ch
                                     , offset         = length $ W.focus ch }
 
+updateHighlightedCompl :: XP ()
+updateHighlightedCompl = do
+  st <- get
+  cs <- getCompletions
+  alwaysHighlight' <- gets $ alwaysHighlight . config
+  when (alwaysHighlight') $ modify $ \s -> s {highlightedCompl = highlightedItem st \
cs} +
 -- X Stuff
 
 updateWindows :: XP ()
hunk ./XMonad/Prompt.hs 886
 getCompletionFunction st = case operationMode st of
   XPSingleMode compl _ -> compl
   XPMultipleModes modes -> completionFunction $ W.focus modes
-  
+
 -- Completions
 getCompletions :: XP [String]
 getCompletions = do
hunk ./XMonad/Prompt.hs 946
       xp = (asc + desc) `div` 2
       yy = map fi . take (fi actual_rows) $ [yp,(yp + ht)..]
       xx = take (fi columns) [xp,(xp + max_compl_len)..]
-  
+
   return (rect_x scr + x, rect_y scr + fi y, wh, actual_height, xx, yy)
 
 drawComplWin :: Window -> [String] -> XP ()
hunk ./XMonad/Prompt.hs 989
             Nothing -> recreate
      else destroyComplWin
 
--- given a string and  a matrix of strings, find the column and row indexes in which \
                the string appears. 
--- if the string is not in the matrix, the function returns (0,0)
+-- Finds the column and row indexes in which a string appears.
+-- if the string is not in the matrix, the indexes default to (0,0)
 findComplIndex :: String -> [[String]] -> (Int,Int)
hunk ./XMonad/Prompt.hs 992
-findComplIndex x xss = let 
+findComplIndex x xss = let
   colIndex = fromMaybe 0 $ findIndex (\cols -> x `elem` cols) xss
   rowIndex = fromMaybe 0 $ elemIndex x $ (!!) xss colIndex
   in (colIndex,rowIndex)
hunk ./XMonad/Prompt.hs 1002
 printComplList d drw gc fc bc xs ys sss =
     zipWithM_ (\x ss ->
         zipWithM_ (\y item -> do
-            st <- get 
-            alwaysHlight <- gets $ alwaysHighlight . config                     
-            let (f,b) = case alwaysHlight of 
-                  True -> --find the column, row in which this item is and decide if \
                we should highlight
-                    let 
-                      colIndex = fromMaybe 0 $ findIndex (\cols -> item `elem` cols) \
                sss
-                      rowIndex = fromMaybe 0 $ elemIndex item $ (!!) sss colIndex
-                    in
+            st <- get
+            alwaysHlight <- gets $ alwaysHighlight . config
+            let (f,b) = case alwaysHlight of
+                  True -> -- default to the first item, the one in (0,0)
+                    let
+                      (colIndex,rowIndex) = findComplIndex item sss
+                    in -- assign some colors
                      if ((complIndex st) == (colIndex,rowIndex)) then (fgHLight $ \
config st,bgHLight $ config st)  else (fc,bc)
hunk ./XMonad/Prompt.hs 1011
-                  False -> if completionToCommand (currentXPMode st) item == \
                commandToComplete (currentXPMode st) (command st)
-                           then (fgHLight $ config st,bgHLight $ config st)
-                           else (fc,bc)
+                  False ->
+                    -- compare item with buffer's value
+                    if completionToCommand (currentXPMode st) item == \
commandToComplete (currentXPMode st) (command st) +                    then (fgHLight \
$ config st,bgHLight $ config st) +                    else (fc,bc)
             printStringXMF d drw (fontS st) gc f b x y item)
         ys ss) xs sss
hunk ./XMonad/Prompt.hs 1018
-                    
+
 -- History
 
 type History = M.Map String [String]
hunk ./XMonad/Prompt/Shell.hs 32
     , split
     ) where
 
-import Codec.Binary.UTF8.String (encodeString)
-import Control.Exception
-import Control.Monad (forM)
-import Data.List (isPrefixOf)
-import Prelude hiding (catch)
-import System.Directory (doesDirectoryExist, getDirectoryContents)
-import System.Environment (getEnv)
-import System.Posix.Files (getFileStatus, isDirectory)
+import           Codec.Binary.UTF8.String (encodeString)
+import           Control.Exception
+import           Control.Monad            (forM)
+import           Data.List                (isPrefixOf)
+import           Prelude                  hiding (catch)
+import           System.Directory         (doesDirectoryExist, getDirectoryContents)
+import           System.Environment       (getEnv)
+import           System.Posix.Files       (getFileStatus, isDirectory)
 
hunk ./XMonad/Prompt/Shell.hs 41
-import XMonad.Util.Run
-import XMonad hiding (config)
-import XMonad.Prompt
+import           XMonad                   hiding (config)
+import           XMonad.Prompt
+import           XMonad.Util.Run
 
 econst :: Monad m => a -> IOException -> m a
 econst = const . return
}
[Fixes typos in Actions.Launcher haddock documentation
c.lopez@kmels.net**20120811112502
 Ignore-this: f8152c0ad59d2b0cc9a6c9061e83aaf0
] {
hunk ./XMonad/Actions/Launcher.hs 35
 
 {- $description
     This module lets you combine and switch between different types of prompts \
                (XMonad.Prompt). It includes a set of default modes:
-    
+
        * Hoogle mode: Search for functions using hoogle, choosing a function leads \
you to documentation in Haddock. hunk ./XMonad/Actions/Launcher.hs 37
-       
+
        * Locate mode: Search for files using locate, choosing a file opens it with a \
program you specify depending on the file's extension. hunk \
                ./XMonad/Actions/Launcher.hs 39
-       
-       * Locate regexp: Same as locate mode but autocomplete works with regular \
                expressions.  
-       
+
+       * Locate regexp: Same as locate mode but autocomplete works with regular \
expressions. +
        * Calc: Uses the program calc to do calculations.
 
     To use the default modes, modify your .xmonad:
hunk ./XMonad/Actions/Launcher.hs 45
-   
+
     > import XMonad.Prompt(defaultXPConfig)
     > import XMonad.Actions.Launcher
 
hunk ./XMonad/Actions/Launcher.hs 49
-    > ((modm .|. controlMask, xK_l), launcherPrompt kmelsXPConfig $ \
                defaultLauncherModes launcherConfig)   
-    
-    A LauncherConfig contains settings for the default modes, modify them \
                accordingly. 
-    
+    > ((modm .|. controlMask, xK_l), launcherPrompt defaultXPConfig $ \
defaultLauncherModes launcherConfig) +
+    A LauncherConfig contains settings for the default modes, modify them \
accordingly. +
     > launcherConfig = LauncherConfig { pathToHoogle = "/home/YOU/.cabal/bin/hoogle" \
, browser = "firefox" , actionsByExtension  = extensionActions } hunk \
                ./XMonad/Actions/Launcher.hs 54
-    
+
 @extensionActions :: M.Map String (String -> X())
 extensionActions = M.fromList $ [
  (\".hs\", \p -> spawn $ \"emacs \" ++ p)
hunk ./XMonad/Actions/Launcher.hs 59
  , (\".pdf\", \p -> spawn $ \"acroread \" ++ p)
+ , (\".mkv\", \p -> spawn $ \"vlc \" ++ p)
  , (\".*\", \p -> spawn $ \"emacs \" ++ p) --match with any files
hunk ./XMonad/Actions/Launcher.hs 61
- , (\"/\", \p -> spawn $ \"nautilus \" ++ p) --match with directories 
+ , (\"/\", \p -> spawn $ \"nautilus \" ++ p) --match with directories
  ]@
hunk ./XMonad/Actions/Launcher.hs 63
- 
- To try it, restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should \
                pop up. 
- 
+
+ To try it, restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should \
pop up. +
  You can change mode with xK_grave if you used defaultXP or change the value of \
changeModeKey in your XPConfig-}  
 data LocateFileMode = LMode ExtensionActions
hunk ./XMonad/Actions/Launcher.hs 73
 data HoogleMode = HMode FilePath String --path to hoogle e.g. \
"/home/me/.cabal/bin/hoogle"  data CalculatorMode = CalcMode
 
-data LauncherConfig = LauncherConfig {  
+data LauncherConfig = LauncherConfig {
   browser                :: String
   , pathToHoogle         :: String
   , actionsByExtension   :: ExtensionActions
hunk ./XMonad/Actions/Launcher.hs 170
        spawnNoPatternMessage :: String -> String -> X ()
        spawnNoPatternMessage fileExt _ = spawn $ "xmessage No action specified for \
file extension " ++ fileExt ++ ", add a default action by matching the extension \
\".*\" in the action map sent to launcherPrompt"  
-{- $todo  
+{- $todo
      * Switch to mode by name of the prompt, 1. ':' at an empty(?) buffer, 2. \
autocomplete name in buffer should happen, 3. switch to mode with enter (cancel \
switch with C-g) hunk ./XMonad/Actions/Launcher.hs 172
-     
+
      * Support for actions of type String -> X a
hunk ./XMonad/Actions/Launcher.hs 174
-     
+
      * Hoogle mode: add a setting in the action to either go to documentation or to \
the source code (needs hoogle change?) hunk ./XMonad/Actions/Launcher.hs 176
-     
+
      * Hoogle mode: add setting to query hoogle at haskell.org instead (with \
                &mode=json)
 -}
hunk ./XMonad/Actions/Launcher.hs 179
+
}
[fix a bug when ncompletions = nrows
c.lopez@kmels.net**20120826083137
 Ignore-this: 5f573028318473c333809217c271a81d
] {
hunk ./XMonad/Prompt.hs 530
 nextComplIndex :: XPState -> Int -> (Int,Int)
 nextComplIndex st nitems = case complWinDim st of
   Nothing -> (0,0) --no window dims (just destroyed or not created)
-  Just winDim -> let
-    (_,_,_,_,_,yy) = winDim
+  Just (_,_,_,_,_,yy) -> let
     (ncols,nrows) = (nitems `div` length yy + if (nitems `mod` length yy > 0) then 1 \
else 0, length yy)  (currentcol,currentrow) = complIndex st
     in if (currentcol + 1 >= ncols) then --hlight is in the last column
hunk ./XMonad/Prompt.hs 534
-         if (currentrow + 1 < (nitems `mod` nrows) ) then --hlight is still not at \
the last row +         if (currentrow + 1 < nrows ) then --hlight is still not at the \
last row  (currentcol, currentrow + 1)
          else
            (0,0)
}
[Improve comments, add an error throw that shouldn't happen
c.lopez@kmels.net**20120826085426
 Ignore-this: 7675070826b3c53499e4352e692d6036
] {
hunk ./XMonad/Prompt.hs 219
     completionFunction :: t -> ComplFunction
     completionFunction t = \_ -> return ["Completions for " ++ (showXPrompt t) ++ " \
could not be loaded"]  
-    -- | When the prompt has multiple modes, this function is called
-    -- when the user picked an item from the autocompletion list.
-    -- The first argument is the autocompleted item's text.
-    -- The second argument is the query made by the user (written in the prompt's \
buffer). +    -- | When the prompt has multiple modes (created with \
mkXPromptWithModes), this function is called +    -- when the user picks an item from \
the autocompletion list. +    -- The first argument is the prompt (or mode) on which \
the item was picked +    -- The first string argument is the autocompleted item's \
text. +    -- The second string argument is the query made by the user (written in \
the prompt's buffer). +    -- See XMonad/Actions/Launcher.hs for a usage example.
     modeAction :: t -> String -> String -> X ()
     modeAction _ _ _ = return ()
 
hunk ./XMonad/Prompt.hs 439
       XPMultipleModes ms -> let
         action = modeAction $ W.focus ms
         in action (command st') $ (fromMaybe "" $ highlightedCompl st')
-      _ -> return () --This should never happen, we are creating a prompt with \
multiple modes, so its operationMode should have been constructed with XPMultipleMode \
+      _ -> error "The impossible occurred: This prompt runs with multiple modes but \
they could not be found." --we are creating a prompt with multiple modes, so its \
operationMode should have been constructed with XPMultipleMode  else
       return ()
 
}
[Improves haddock documentation
c.lopez@kmels.net**20120826091716
 Ignore-this: a0ce4838652acfff7922c111e4d879bb
] {
hunk ./XMonad/Actions/Launcher.hs 34
 import           XMonad.Util.Run
 
 {- $description
-    This module lets you combine and switch between different types of prompts \
(XMonad.Prompt). It includes a set of default modes: +    This module lets you \
combine and switch between different types of prompts (`XMonad.Prompt.XPrompt`). It \
includes a set of default modes:  
        * Hoogle mode: Search for functions using hoogle, choosing a function leads \
you to documentation in Haddock.  
hunk ./XMonad/Actions/Launcher.hs 66
 
  To try it, restart xmonad. Press Ctrl + Your_Modkey + L and the first prompt should \
pop up.  
- You can change mode with xK_grave if you used defaultXP or change the value of \
changeModeKey in your XPConfig-} + If you used `defaultXPConfig`, you can change mode \
with xK_grave. If you are using your own `XPConfig`, define the value for \
`changeModeKey`. + -}
 
 data LocateFileMode = LMode ExtensionActions
 data LocateFileRegexMode = LRMode ExtensionActions
hunk ./XMonad/Actions/Launcher.hs 111
   modeAction (HMode pathToHoogleBin'' browser') query result = do
     completionsWithLink <- liftIO $ completionFunctionWith pathToHoogleBin'' \
["--count","5","--link",query]  let link = do
-          s <- find (isJust . \c -> findSeqIndex c result) completionsWithLink
+          s <- find (isJust . \complStr -> findSeqIndex complStr result) \
completionsWithLink  i <- findSeqIndex s "http://"
           return $ drop i s
     case link of
hunk ./XMonad/Prompt.hs 244
         , promptBorderWidth = 1
         , promptKeymap      = defaultXPKeymap
         , completionKey     = xK_Tab
-        , changeModeKey     = xK_asciitilde
+        , changeModeKey     = xK_grave
         , position          = Bottom
         , height            = 18
         , historySize       = 256
}

Context:

[strip newlines from dmenu's returns to be compatible with the newest version of \
dmenu longpoke@gmail.com**20120723212807
 Ignore-this: 3b11a35125d0bc23b33e0b926562f85a
] 
[A workscreen permits to display a set of workspaces on several
kedals0@gmail.com**20120706093308
 Ignore-this: 572ed3c3305205bfbcc17bb3fe2600a3
 screens. In xinerama mode, when a workscreen is viewed, workspaces
 associated to all screens are visible.
 
 The first workspace of a workscreen is displayed on first screen,
 second on second screen, etc. Workspace position can be easily
 changed. If the current workscreen is called again, workspaces are
 shifted.
 
 This also permits to see all workspaces of a workscreen even if just
 one screen is present, and to move windows from workspace to workscreen.
] 
[refer to the new name 'handleEventHook' instead of the old name 'eventHook' in \
X.L.Fullscreen documentation Daniel Wagner <daniel@wagner-home.com>**20120618181003
 Ignore-this: bd3b26c758cf3993d5a93957bb6f3663
] 
[UrgencyHooks made available as Window -> X () functions
gopsychonauts@gmail.com**20120504062339
 Ignore-this: 6a57cae1d693109b7e27c6471d04f50f
 Adds an UrgencyHook instance for the type Window -> X (), allowing any such
 functions to be used directly as UrgencyHooks. The Show and Read constraints
 were removed from the UrgencyHook class in order to permit this; these
 constraints were required only in a historical implementation of the module,
 which used a layout modifier.
 
 All existing configurations using UrgencyHooks should remain fully functional.
 New configs may make use of this modification by declaring their UrgencyHook as
 a simple Window -> X () function.
 
] 
[updates to XMonad.Prompt re: word-oriented commands
Brent Yorgey <byorgey@cis.upenn.edu>**20120510174317
 Ignore-this: 138b5e8942fe4b55ad7e6ab24f17703f
 
   + change killWord and moveWord to have emacs-like behavior: first move
     past/kill consecutive whitespace, then move past/kill consecutive
     non-whitespace.
 
   + create variants killWord' and moveWord' which take a predicate
     specifying non-word characters.
 
   + create variants defaultXPKeymap' and emacsLikeXPKeymap' which take
     the same sort of predicate, which is applied to all keybindings with
     word-oriented commands.
] 
[Added isUnfocusedOnCurrentWS and fadeInactiveCurrentWSLogHook for better support of \
fading/opacity on multi monitor setups Jesper Reenberg \
<jesper.reenberg@gmail.com>**20120329141818  Ignore-this: \
d001a8aafbcdedae21ccd1d18f019185 ] 
[Fixed X.A.GridSelect to be consistent in the way it (now) sorts the shown
Jesper Reenberg <jesper.reenberg@gmail.com>**20120501180415
 Ignore-this: 1d0991f9fb44e42f5d1c5a4f427ea661
 elements when modifying the searchString.
 
 The implemented ordering sorts based on how "deep the needle is in the
 haystack", meaning that searching for "st" in the elements "Install" and "Study"
 will order them as "Study" and "Install". Previously there was no ordering and
 when using GridSelect to select workspaces, the ordering was not consistent, as
 the list of workspaces (if not modified manually) is ordered by last used. In
 this case either "Study" or "Install" would come first depending on which
 workspace was last visited.
] 
[Use getXMonadDir to get the default xmonad directory.
Julia Jomantaite <julia.jomantaite@gmail.com>**20120501121427
 Ignore-this: a075433761488b76a58a193aeb4e4a25
] 
[Minor haddock formatting for X.L.OnHost and X.A.DynamicWorkspaceOrder
Adam Vogt <vogt.adam@gmail.com>**20120428194552
 Ignore-this: 843ec567e249cc96d51ca931f1e36514
] 
[Remove trailing whitespace.
Adam Vogt <vogt.adam@gmail.com>**20120428194048
 Ignore-this: d61584110954e84d3611ef3497a29725
] 
[Add emacs-like keys to browse history in XMonad.Prompt
Carlos Lopez-Camey <c.lopez@kmels.net>**20120421110737
 Ignore-this: b90345f72007d09a6b732b974c0faf79
] 
[Adds an emacs-like Keymap in XMonad.Prompt
Carlos Lopez-Camey <c.lopez@kmels.net>**20120421012335
 Ignore-this: f281b8ad01f3d21055e2d6de79af2d79
] 
[add 'withNthWorkspace' to DynamicWorkspaceOrder.
jakob@pipefour.org**20120407184640
 Ignore-this: f5f87ffe9ddf1a12fab775e6fb8e856f
 Note this is very similar to the function of the same name exported by
 DynamicWorkspaces.  Ultimately it would probably be cleaner to
 generalize the one in DynamicWorkspaces to accept an arbitrary
 workspace sort as a parameter; this is left as an exercise for future
 hackers.
] 
[XMonad.Layout.OnHost allows host-specific modifications to a layout, which
allbery.b@gmail.com**20120320030912
 Ignore-this: 4c0d5580e805ff9f40918308914f3bf9
 is otherwise very difficult to do.  Similarly to X.L.PerWorkspace, it provides
 onHost, onHosts, modHost, and modHosts layout modifiers.  It attempts to do
 smart hostname comparison, such that short names will be matched with short
 names and FQDNs with FQDNs.
 
 This module currently requires that $HOST be set in the environment.
 You can use System.Posix.Env.setEnv to do so in xmonad.hs if need be.
 (Properly, this should be done via the network library, but I'm trying to
 avoid adding that dependency.)  An alternative would be to shell out to
 get the name, but that has considerable portability hurdles.
] 
[Bump version to 0.10.1
Adam Vogt <vogt.adam@gmail.com>**20120320005311
 Ignore-this: f0608ffaa877f605eaa86c45a107a14d
 
 Raising the X11 dependency while keeping the xmonad version the same leads to
 problems where cabal install uses the dependency versions following hackage,
 not what is installed.
] 
[narrower BorderResize rectangles placed within border edges
Jens Petersen <juhp@community.haskell.org>**20120314064703
 Ignore-this: 3a43bbdb7f2317d702edafb231f58802
 
   Change the border resize rectangles to be narrower and only extend
   inside the window not outside.  Most window managers just seem to use
   the border decoration area for starting resizes which is often just 1 pixel
   wide but as a compromise the width is now 2 pixels (before it was 10!).
   The rectangles are now placed symmetrically within the border and window.
   This seems to work ok with PositionStoreFloat for the Bluetile config.
] 
[add-dynamic-bars-module
Ben Boeckel <mathstuf@gmail.com>**20120316002204
 Ignore-this: 41347c8f894d8d0b5095dfad86784cf4
 
 This adds the X.H.DynamicBars module. It allows per-screen status bars to be
 easily managed and dynamically handles the number of screens changing.
] 
[bump X11 dependency so that noModMask is available
Daniel Wagner <daniel@wagner-home.com>**20120316000302
 Ignore-this: 971a75dcad25f66848eef4174cd4ddd1
] 
[Paste.hs: rm noModMask, shifted definition to X11 binding (see previous email)
gwern0@gmail.com**20111203203038
 Ignore-this: dcd164ff8f8f135c8fdef08f42f9244d
] 
[GroupNavigation: fix import typo in usage
Jens Petersen <juhp@community.haskell.org>**20120312103349
 Ignore-this: 65367218ca50a33a37813469b4616f34
] 
[add sendToEmptyWorkspace to FindEmptyWorkspace
Jens Petersen <juhp@community.haskell.org>**20120312102331
 Ignore-this: 50e7992d80d2db43e4d0adf5c95e964f
 
 sendToEmptyWorkspace is like tagToEmptyWorkspace except
 it does not change workspace after moving the window.
] 
[xmonad-contrib.cabal: simplify xmonad dependency to >=0.10 && < 0.11
Jens Petersen <juhp@community.haskell.org>**20120312101800
 Ignore-this: 1ff5a0caa2a1e3487e9a0831e385b3d2
 
 Unless there is a particular reason for listing the lower and upper bounds
 separately then this seems simpler and cleaner.
] 
[ShowWName: Increase horizontal padding for flash
crodjer@gmail.com**20120305164517
 Ignore-this: de5fd30fad2630875c5c78091f07c324
 
 Currently the flash window width leaves a very small amount of padding. This
 patch adds some extra horizontal width, governed by text width and length.
] 
[persist-togglehook-options
Ben Boeckel <mathstuf@gmail.com>**20120311050143
 Ignore-this: 580bacb35b617c1198f01c5a7c0d3fef
 
 Save the state of ToggleHook options over a restart.
] 
[ShowWName flash window background color
Rohan Jain <crodjer@gmail.com>**20120306065224
 Ignore-this: 9cd8fcfc13cc326b9dcc79ef3cc21b26
 
 While calling paintAndWrite for flash window, the background color from config
 should also be passed on as window background in addition to as text background
 color. Otherwise the window color gets set to the default black which shows up
 when text cannot span whole of the window.
 
 This issue becomes visible when the font size is considerably large or even in
 small size with truetype fonts.
] 
[ShowWName: Fix flash location by screen rectangle
crodjer@gmail.com**20120305161240
 Ignore-this: 83ec4cce2297efc6736a1fe55f44ee73
 
 In case of using this hook with multiple monitors, the Tag flash was not
 following the screen's coordinates. This patch shifts the new window created for
 flash according to the Rectangle defined by the screen.
] 
[Fix typo in tabbed layout link for font utils docs
crodjer@gmail.com**20120229070022
 Ignore-this: 2f7e90269e08ce08264d7b1d05bb16f9
] 
[L.WorkspaceDir: cleanup redundant {definitions,imports}
Steffen Schuldenzucker <sschuldenzucker@uni-bonn.de>**20120229112124
 Ignore-this: 7a796b18a64e693e071e9ea3a6a01aa3
] 
[fix L.WorkspaceDir special char handling: remove "echo -n" processing
Steffen Schuldenzucker <sschuldenzucker@uni-bonn.de>**20120227122004
 Ignore-this: ab48687eb4c9018312089a13fd25ecd8
] 
[Add BorderUrgencyHook to XMonad.Hooks.UrgencyHook
allbery.b@gmail.com**20120225082616
 Ignore-this: 9fac77914ff28a6e9eb830e8c9c7e21e
 BorderUrgencyHook is a new UrgencyHook usable with withUrgencyHook or
 withUrgencyHookC; it allows an urgent window to be given a different
 border color.  This may not always work as intended, since UrgencyHook
 likes to assume that a window being visible is sufficient to disable
 urgency notification; but with suppressWhen = Never it may work well
 enough.
 
 There is a report that if a new window is created at the wrong time,
 the wrong window may be marked urgent somehow.  I seem to once again
 be revealing bugs in underlying packages, although a quick examination
 of X.H.UrgencyHook doesn't seem to show any way for the wrong window
 to be selected.
] 
[Adding use case for namedScratchpad.
nicolas.dudebout@gatech.edu**20120122235843
 Ignore-this: 44201e82bcd708cd7098f060345400f1
] 
[Actions.WindowGo: typo fix - trim 's' per cub.uanic \
https://code.google.com/p/xmonad/issues/detail?id=491 \
gwern0@gmail.com**20120116224244  Ignore-this: fb1d55c1b4609069c55f13523c091260
] 
[XMonad.Actions.PhysicalScreens: fix typo spotted by Chris Pick \
<haskell@chrispick.com> gwern0@gmail.com**20120115223013
 Ignore-this: eb73b33b07dc58a36d3aa00bc8ac31c2
] 
[roll back previous incorrect fix
Daniel Wagner <daniel@wagner-home.com>**20120111214133
 Ignore-this: 91496faef411e6ae3442498b528d119b
] 
[Extending: fix http://code.google.com/p/xmonad/issues/detail?id=490
gwern0@gmail.com**20120111211907
 Ignore-this: 515afbed507c070d60ab547e98682f12
] 
[another documentation patch: XMonadContrib.UpdatePointer -> \
XMonad.Actions.UpdatePointer Daniel Wagner <daniel@wagner-home.com>**20120111211226
 Ignore-this: 1444e4a3f20ba442602ef1811d0b32c7
] 
[documentation patch, fixes issue 490
Daniel Wagner <daniel@wagner-home.com>**20120111210832
 Ignore-this: 8d899e15f9d1a657e9fc687e2f649f45
] 
[X.H.EwmhDesktops note that fullscreenEventHook is not included in ewmh
Adam Vogt <vogt.adam@gmail.com>**20120102211404
 Ignore-this: 92f15fa93877c165158c8fbd24aa2360
 
 Just a documentation fix (nomeata's suggestion at issue 339).
] 
[X.H.EwmhDesktops haddock formatting.
Adam Vogt <vogt.adam@gmail.com>**20120102211203
 Ignore-this: cfff985e4034e06a0fe27c52c9971901
] 
[X.A.Navigation2D
Norbert Zeh <nzeh@cs.dal.ca>**20111208205842
 Ignore-this: 3860cc71bfc08d99bd8279c2e0945186
 
 This is a new module to support directional navigation across multiple screens.
 As such it is related to X.A.WindowNavigation and X.L.WindowNavigation, but it
 is more general.  For a detailed discussion of the differences, see
 http://www.cs.dal.ca/~nzeh/xmonad/Navigation2D.pdf.
] 
[documentation patch: mention PostfixOperators
Daniel Wagner <daniel@wagner-home.com>**20111210234820
 Ignore-this: 20a05b1f396f18a742346d6e3daea9a8
] 
[P.Shell documentation and add missing unsafePrompt export
Adam Vogt <vogt.adam@gmail.com>**20111207163951
 Ignore-this: a03992ffdc9c1a0f5bfa6dafc453b587
 
 Haddock (version 2.9.2 at least) does not attach documentation to any of a b or
 c when given:
 
     -- | documentation
     a,b,c :: X
 
] 
[Paste: 3 more escaped characters from alistra
gwern0@gmail.com**20111129160335
 Ignore-this: 46f5b86a25bcd2b26d2e07ed33ffad68
] 
[unfuck X.U.Paste
Daniel Wagner <daniel@wagner-home.com>**20111129032331
 Ignore-this: d450e23ca026143bb6ca9d744dcdd906
] 
[XMonad.Util.Paste: +alistra's patch for fixing his pasting of things like email \
address (@) gwern0@gmail.com**20111128215648
 Ignore-this: 4af1af27637fe056792aa4f3bb0403eb
] 
[XMonad.Util.Paste: rm myself from maintainer field; I don't know how to fix any of \
it even if I wanted gwern0@gmail.com**20111128213001
 Ignore-this: 87a4996aaa5241428ccb13851c5eb455
] 
[XMonad.Prompt.Shell: improve 'env' documentation to cover goodgrue's problem
gwern0@gmail.com**20111127231507
 Ignore-this: 7b652a280960cbdf99c236496ca091b0
] 
[Fix spelling 'prefered' -> 'preferred'.
Erik de Castro Lopo <erikd@mega-nerd.com>**20111125010229
 Ignore-this: f2eac1728b5e023399188becf867a14d
] 
[Restore TrackFloating behavior to an earlier version.
Adam Vogt <vogt.adam@gmail.com>**20111120045538
 Ignore-this: 1a1367b4171c3ad23b0553766021629f
 
 Thanks for liskni_si for pressing the matter: without this change it is very
 broken, with the patch it is still not perfect but still useful.
] 
[Explicitly list test files in .cabal
Adam Vogt <vogt.adam@gmail.com>**20111118232511
 Ignore-this: ac48a0d388293cc6c771d676aaf142e3
 
 In the future, require Cabal >= 1.6 to be able to just write tests/*.hs
] 
[TAG 0.10
Adam Vogt <vogt.adam@gmail.com>**20111118225640
 Ignore-this: 8f81b175b902e985d584160fc41ab7d1
] 
Patch bundle hash:
f0d3a0b470003b08a6fcfb5ebb981c1c37c5d809



_______________________________________________
xmonad mailing list
xmonad@haskell.org
http://www.haskell.org/mailman/listinfo/xmonad


[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic