| Copyright | (C) 2007 Andrea Rossato, 2015 Evgeny Kurnevsky | 
|---|---|
| License | BSD3 | 
| Maintainer | Spencer Janssen <spencerjanssen@gmail.com> | 
| Stability | unstable | 
| Portability | unportable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
XMonad.Prompt
Contents
Description
A module for writing graphical prompts for XMonad
- mkXPrompt :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X ()) -> X ()
- mkXPromptWithReturn :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X a) -> X (Maybe a)
- mkXPromptWithModes :: [XPType] -> XPConfig -> X ()
- def :: Default a => a
- amberXPConfig :: XPConfig
- defaultXPConfig :: XPConfig
- greenXPConfig :: XPConfig
- type XPMode = XPType
- data XPType = forall p . XPrompt p => XPT p
- data XPPosition
- data XPConfig = XPC {- font :: String
- bgColor :: String
- fgColor :: String
- fgHLight :: String
- bgHLight :: String
- borderColor :: String
- promptBorderWidth :: !Dimension
- position :: XPPosition
- alwaysHighlight :: !Bool
- height :: !Dimension
- maxComplRows :: Maybe Dimension
- historySize :: !Int
- historyFilter :: [String] -> [String]
- promptKeymap :: Map (KeyMask, KeySym) (XP ())
- completionKey :: KeySym
- changeModeKey :: KeySym
- defaultText :: String
- autoComplete :: Maybe Int
- showCompletionOnTab :: Bool
- searchPredicate :: String -> String -> Bool
 
- class XPrompt t where- showXPrompt :: t -> String
- nextCompletion :: t -> String -> [String] -> String
- commandToComplete :: t -> String -> String
- completionToCommand :: t -> String -> String
- completionFunction :: t -> ComplFunction
- modeAction :: t -> String -> String -> X ()
 
- type XP = StateT XPState IO
- defaultXPKeymap :: Map (KeyMask, KeySym) (XP ())
- defaultXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ())
- emacsLikeXPKeymap :: Map (KeyMask, KeySym) (XP ())
- emacsLikeXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ())
- quit :: XP ()
- killBefore :: XP ()
- killAfter :: XP ()
- startOfLine :: XP ()
- endOfLine :: XP ()
- pasteString :: XP ()
- moveCursor :: Direction1D -> XP ()
- setInput :: String -> XP ()
- getInput :: XP String
- moveWord :: Direction1D -> XP ()
- moveWord' :: (Char -> Bool) -> Direction1D -> XP ()
- killWord :: Direction1D -> XP ()
- killWord' :: (Char -> Bool) -> Direction1D -> XP ()
- deleteString :: Direction1D -> XP ()
- moveHistory :: (Stack String -> Stack String) -> XP ()
- setSuccess :: Bool -> XP ()
- setDone :: Bool -> XP ()
- data Direction1D
- type ComplFunction = String -> IO [String]
- mkUnmanagedWindow :: Display -> Screen -> Window -> Position -> Position -> Dimension -> Dimension -> IO Window
- fillDrawable :: Display -> Drawable -> GC -> Pixel -> Pixel -> Dimension -> Dimension -> Dimension -> IO ()
- mkComplFunFromList :: [String] -> String -> IO [String]
- mkComplFunFromList' :: [String] -> String -> IO [String]
- getNextOfLastWord :: XPrompt t => t -> String -> [String] -> String
- getNextCompletion :: String -> [String] -> String
- getLastWord :: String -> String
- skipLastWord :: String -> String
- splitInSubListsAt :: Int -> [a] -> [[a]]
- breakAtSpace :: String -> (String, String)
- uniqSort :: Ord a => [a] -> [a]
- historyCompletion :: ComplFunction
- historyCompletionP :: (String -> Bool) -> ComplFunction
- deleteAllDuplicates :: [String] -> [String]
- deleteConsecutive :: [String] -> [String]
- data HistoryMatches
- initMatches :: (Functor m, MonadIO m) => m HistoryMatches
- historyUpMatching :: HistoryMatches -> XP ()
- historyDownMatching :: HistoryMatches -> XP ()
- data XPState
Usage
For usage examples see XMonad.Prompt.Shell, XMonad.Prompt.XMonad or XMonad.Prompt.Ssh
TODO:
- scrolling the completions that don't fit in the window (?)
mkXPrompt :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X ()) -> X () Source
Creates a prompt given:
- a prompt type, instance of the XPromptclass.
- a prompt configuration (defcan be used as a starting point)
- a completion function (mkComplFunFromListcan be used to create a completions function given a list of possible completions)
- an action to be run: the action must take a string and return X()
mkXPromptWithReturn :: XPrompt p => p -> XPConfig -> ComplFunction -> (String -> X a) -> X (Maybe a) Source
Same as mkXPrompt, except that the action function can have
   type String -> X a, for any a, and the final action returned
   by mkXPromptWithReturn will have type X (Maybe a).  Nothing
   is yielded if the user cancels the prompt (by e.g. hitting Esc or
   Ctrl-G).  For an example of use, see the Input
   module.
mkXPromptWithModes :: [XPType] -> XPConfig -> X () Source
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.
defaultXPConfig :: XPConfig Source
Deprecated: Use def (from Data.Default, and re-exported from XMonad.Prompt) instead.
Constructors
| XPC | |
| Fields 
 | |
The class prompt types must be an instance of. In order to
 create a prompt you need to create a data type, without parameters,
 and make it an instance of this class, by implementing a simple
 method, showXPrompt, which will be used to print the string to be
 displayed in the command line window.
This is an example of a XPrompt instance definition:
    instance XPrompt Shell where
         showXPrompt Shell = "Run: "Minimal complete definition
Methods
showXPrompt :: t -> String Source
This method is used to print the string to be displayed in the command line window.
nextCompletion :: t -> String -> [String] -> String Source
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. This function is not used when in multiple modes (because alwaysHighlight in XPConfig is True)
commandToComplete :: t -> String -> String Source
This method is used to generate the string to be passed to the completion function.
completionToCommand :: t -> String -> String Source
This method is used to process each completion in order to
 generate the string that will be compared with the command
 presently displayed in the command line. If the prompt is using
 getNextOfLastWord for implementing nextCompletion (the
 default implementation), this method is also used to generate,
 from the returned completion, the string that will form the
 next command line when tab is pressed.
completionFunction :: t -> ComplFunction Source
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.
modeAction :: t -> String -> String -> X () Source
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 XMonadActionsLauncher.hs for a usage example.
Instances
defaultXPKeymap :: Map (KeyMask, KeySym) (XP ()) Source
Default key bindings for prompts.  Click on the "Source" link
   to the right to see the complete list.  See also defaultXPKeymap'.
defaultXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ()) Source
A variant of defaultXPKeymap which lets you specify a custom
   predicate for identifying non-word characters, which affects all
   the word-oriented commands (move/kill word).  The default is
   isSpace.  For example, by default a path like foo/bar/baz
   would be considered as a single word.  You could use a predicate
   like (\c -> isSpace c || c == '/') to move through or
   delete components of the path one at a time.
emacsLikeXPKeymap :: Map (KeyMask, KeySym) (XP ()) Source
A keymap with many emacs-like key bindings.  Click on the
   "Source" link to the right to see the complete list.
   See also emacsLikeXPKeymap'.
emacsLikeXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ()) Source
A variant of emacsLikeXPKeymap which lets you specify a custom
   predicate for identifying non-word characters, which affects all
   the word-oriented commands (move/kill word).  The default is
   isSpace.  For example, by default a path like foo/bar/baz
   would be considered as a single word.  You could use a predicate
   like (\c -> isSpace c || c == '/') to move through or
   delete components of the path one at a time.
killBefore :: XP () Source
Kill the portion of the command before the cursor
startOfLine :: XP () Source
Put the cursor at the start of line
pasteString :: XP () Source
Insert the current X selection string at the cursor position.
moveCursor :: Direction1D -> XP () Source
move the cursor one position
Returns the current input string. Intented for use in custom keymaps
 where the get or similar can't be used to retrieve it.
moveWord :: Direction1D -> XP () Source
moveWord' :: (Char -> Bool) -> Direction1D -> XP () Source
Move the cursor one word, given a predicate to identify non-word characters. First move past any consecutive non-word characters; then move to just before the next non-word character.
killWord :: Direction1D -> XP () Source
killWord' :: (Char -> Bool) -> Direction1D -> XP () Source
Kill the next/previous word, given a predicate to identify non-word characters. First delete any consecutive non-word characters; then delete consecutive word characters, stopping just before the next non-word character.
For example, by default (using killWord) a path like
   foo/bar/baz would be deleted in its entirety.  Instead you can
   use something like killWord' (\c -> isSpace c || c == '/') to
   delete the path one component at a time.
deleteString :: Direction1D -> XP () Source
Remove a character at the cursor position
setSuccess :: Bool -> XP () Source
type ComplFunction = String -> IO [String] Source
X Utilities
mkUnmanagedWindow :: Display -> Screen -> Window -> Position -> Position -> Dimension -> Dimension -> IO Window Source
Creates a window with the attribute override_redirect set to True. Windows Managers should not touch this kind of windows.
fillDrawable :: Display -> Drawable -> GC -> Pixel -> Pixel -> Dimension -> Dimension -> Dimension -> IO () Source
Fills a Drawable with a rectangle and a border
Other Utilities
mkComplFunFromList :: [String] -> String -> IO [String] Source
This function takes a list of possible completions and returns a
 completions function to be used with mkXPrompt
mkComplFunFromList' :: [String] -> String -> IO [String] Source
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.
nextCompletion implementations
getNextOfLastWord :: XPrompt t => t -> String -> [String] -> String Source
Given the prompt type, the command line and the completion list,
 return the next completion in the list for the last word of the
 command line. This is the default nextCompletion implementation.
getNextCompletion :: String -> [String] -> String Source
An alternative nextCompletion implementation: given a command
 and a completion list, get the next completion in the list matching
 the whole command line.
List utilities
getLastWord :: String -> String Source
Gets the last word of a string or the whole string if formed by only one word
skipLastWord :: String -> String Source
Skips the last word of the string, if the string is composed by more then one word. Otherwise returns the string.
splitInSubListsAt :: Int -> [a] -> [[a]] Source
Given a maximum length, splits a list into sublists
breakAtSpace :: String -> (String, String) Source
uniqSort :: Ord a => [a] -> [a] Source
Sort a list and remove duplicates. Like deleteAllDuplicates, but trades off
   laziness and stability for efficiency.
historyCompletion :: ComplFunction Source
historyCompletion provides a canned completion function much like
   getShellCompl; you pass it to mkXPrompt, and it will make completions work
   from the query history stored in ~/.xmonad/history.
historyCompletionP :: (String -> Bool) -> ComplFunction Source
Like historyCompletion but only uses history data from Prompts whose
 name satisfies the given predicate.
History filters
deleteAllDuplicates :: [String] -> [String] Source
Functions to be used with the historyFilter setting.
 deleteAllDuplicates will remove all duplicate entries.
 deleteConsecutive will only remove duplicate elements
 immediately next to each other.
deleteConsecutive :: [String] -> [String] Source
Functions to be used with the historyFilter setting.
 deleteAllDuplicates will remove all duplicate entries.
 deleteConsecutive will only remove duplicate elements
 immediately next to each other.
data HistoryMatches Source
initMatches :: (Functor m, MonadIO m) => m HistoryMatches Source
Initializes a new HistoryMatches structure to be passed to historyUpMatching
historyUpMatching :: HistoryMatches -> XP () Source
Retrieve the next history element that starts with the current input. Pass it the result of initMatches when creating the prompt. Example:
..
((modMask,xK_p), shellPrompt . myPrompt =<< initMatches)
..
myPrompt ref = def
  { promptKeymap = M.union [((0,xK_Up), historyUpMatching ref)
                           ,((0,xK_Down), historyDownMatching ref)]
                           (promptKeymap def)
  , .. }historyDownMatching :: HistoryMatches -> XP () Source
Retrieve the next history element that starts with the current input. Pass it the result of initMatches when creating the prompt. Example:
..
((modMask,xK_p), shellPrompt . myPrompt =<< initMatches)
..
myPrompt ref = def
  { promptKeymap = M.union [((0,xK_Up), historyUpMatching ref)
                           ,((0,xK_Down), historyDownMatching ref)]
                           (promptKeymap def)
  , .. }