Copyright | (C) 2007 Andrea Rossato 2015 Evgeny Kurnevsky 2015 Sibi Prabakaran 2018 Yclept Nemo |
---|---|
License | BSD3 |
Maintainer | Spencer Janssen <spencerjanssen@gmail.com> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A module for writing graphical prompts for XMonad
Synopsis
- 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
- greenXPConfig :: XPConfig
- type XPMode = XPType
- data XPType = forall p.XPrompt p => XPT p
- data XPColor = XPColor {
- bgNormal :: String
- fgNormal :: String
- bgHighlight :: String
- fgHighlight :: String
- border :: String
- data XPPosition
- data XPConfig = XPC {
- font :: String
- bgColor :: String
- fgColor :: String
- bgHLight :: String
- fgHLight :: String
- borderColor :: String
- promptBorderWidth :: !Dimension
- position :: XPPosition
- alwaysHighlight :: !Bool
- height :: !Dimension
- maxComplRows :: Maybe Dimension
- maxComplColumns :: Maybe Dimension
- historySize :: !Int
- historyFilter :: [String] -> [String]
- promptKeymap :: Map (KeyMask, KeySym) (XP ())
- completionKey :: (KeyMask, KeySym)
- prevCompletionKey :: (KeyMask, KeySym)
- changeModeKey :: KeySym
- defaultText :: String
- autoComplete :: Maybe Int
- showCompletionOnTab :: Bool
- complCaseSensitivity :: ComplCaseSensitivity
- searchPredicate :: String -> String -> Bool
- defaultPrompter :: String -> String
- sorter :: String -> [String] -> [String]
- 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 ())
- vimLikeXPKeymap :: Map (KeyMask, KeySym) (XP ())
- vimLikeXPKeymap' :: (XPColor -> XPColor) -> (String -> String) -> (String -> String) -> (Char -> Bool) -> Map (KeyMask, KeySym) (XP ())
- quit :: XP ()
- promptSubmap :: XP () -> Map (KeyMask, KeySym) (XP ()) -> XP ()
- promptBuffer :: (String -> String -> (Bool, Bool)) -> XP String
- toHeadChar :: Direction1D -> String -> XP ()
- bufferOne :: String -> String -> (Bool, Bool)
- killBefore :: XP ()
- killAfter :: XP ()
- startOfLine :: XP ()
- endOfLine :: XP ()
- insertString :: String -> XP ()
- pasteString :: XP ()
- pasteString' :: (String -> String) -> XP ()
- clipCursor :: XP ()
- moveCursor :: Direction1D -> XP ()
- moveCursorClip :: Direction1D -> XP ()
- setInput :: String -> XP ()
- getInput :: XP String
- getOffset :: XP Int
- defaultColor :: XPConfig -> XPColor
- modifyColor :: (XPColor -> XPColor) -> XP ()
- setColor :: XPColor -> XP ()
- resetColor :: XP ()
- setBorderColor :: String -> XPColor -> XPColor
- modifyPrompter :: ((String -> String) -> String -> String) -> XP ()
- setPrompter :: (String -> String) -> XP ()
- resetPrompter :: XP ()
- selectedCompletion :: XPState -> String
- setCurrentCompletions :: Maybe [String] -> XP ()
- getCurrentCompletions :: XP (Maybe [String])
- moveWord :: Direction1D -> XP ()
- moveWord' :: (Char -> Bool) -> Direction1D -> XP ()
- killWord :: Direction1D -> XP ()
- killWord' :: (Char -> Bool) -> Direction1D -> XP ()
- changeWord :: (Char -> Bool) -> XP ()
- deleteString :: Direction1D -> XP ()
- moveHistory :: (Stack String -> Stack String) -> XP ()
- setSuccess :: Bool -> XP ()
- setDone :: Bool -> XP ()
- setModeDone :: Bool -> XP ()
- data Direction1D
- type ComplFunction = String -> IO [String]
- data ComplCaseSensitivity
- mkUnmanagedWindow :: Display -> Screen -> Window -> Position -> Position -> Dimension -> Dimension -> IO Window
- fillDrawable :: Display -> Drawable -> GC -> Pixel -> Pixel -> Dimension -> Dimension -> Dimension -> IO ()
- mkComplFunFromList :: XPConfig -> [String] -> String -> IO [String]
- mkComplFunFromList' :: XPConfig -> [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 :: XPConfig -> X ComplFunction
- historyCompletionP :: XPConfig -> (String -> Bool) -> X 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
XPrompt
class. - a prompt configuration (
def
can be used as a starting point) - a completion function (
mkComplFunFromList
can 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.
Instances
Show XPType Source # | |
XPrompt XPType Source # | |
Defined in XMonad.Prompt showXPrompt :: XPType -> String Source # nextCompletion :: XPType -> String -> [String] -> String Source # commandToComplete :: XPType -> String -> String Source # completionToCommand :: XPType -> String -> String Source # |
data XPPosition Source #
Top | |
Bottom | |
CenteredAt | Prompt will be placed in the center horizontally and
in the certain place of screen vertically. If it's in the upper
part of the screen, completion window will be placed below (like
in |
Instances
Read XPPosition Source # | |
Defined in XMonad.Prompt readsPrec :: Int -> ReadS XPPosition # readList :: ReadS [XPPosition] # readPrec :: ReadPrec XPPosition # readListPrec :: ReadPrec [XPPosition] # | |
Show XPPosition Source # | |
Defined in XMonad.Prompt showsPrec :: Int -> XPPosition -> ShowS # show :: XPPosition -> String # showList :: [XPPosition] -> ShowS # |
XPC | |
|
class XPrompt t where Source #
A class for an abstract prompt. In order for your data type to be a valid prompt you _must_ make it an instance of this class.
The minimal complete definition is just showXPrompt
, i.e. the name
of the prompt. This string will be displayed in the command line
window (before the cursor).
As an example of a complete XPrompt
instance definition, we can
look at the Shell
prompt from
XMonad.Prompt.Shell:
data Shell = Shell instance XPrompt Shell where showXPrompt Shell = "Run: "
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.
vimLikeXPKeymap :: Map (KeyMask, KeySym) (XP ()) Source #
Vim-ish key bindings. Click on the "Source" link to the right to see the
complete list. See also vimLikeXPKeymap'
.
:: (XPColor -> XPColor) | Modifies the prompt color when entering normal mode.
The default is |
-> (String -> String) | Prompter to use in normal mode. The default of |
-> (String -> String) | Filter applied to the X Selection before pasting. The
default is |
-> (Char -> Bool) | Predicate identifying non-word characters. The default
is |
-> Map (KeyMask, KeySym) (XP ()) |
A variant of vimLikeXPKeymap
with customizable aspects:
promptSubmap :: XP () -> Map (KeyMask, KeySym) (XP ()) -> XP () Source #
Initiate a prompt sub-map event loop. Submaps are intended to provide alternate keybindings. Accepts a default action and a mapping from key combinations to actions. If no entry matches, the default action is run.
promptBuffer :: (String -> String -> (Bool, Bool)) -> XP String Source #
Initiate a prompt input buffer event loop. Input is sent to a buffer and
bypasses the prompt. The provided function is given the existing buffer and
the input keystring. The first field of the result determines whether the
input loop continues (if True
). The second field determines whether the
input is appended to the buffer, or dropped (if False
). If the loop is to
stop without keeping input - that is, (False,False)
- the event is
prepended to the event buffer to be processed by the parent loop. This
allows loop to process both fixed and indeterminate inputs.
Result given (continue,keep)
:
cont and keep
- grow input buffer
stop and keep
- grow input buffer
- stop loop
stop and drop
- buffer event
- stop loop
cont and drop
- do nothing
toHeadChar :: Direction1D -> String -> XP () Source #
Move the cursor in the given direction to the first instance of the first character of the given string, assuming the string is not empty. The starting cursor character is not considered, and the cursor is placed over the matching character.
bufferOne :: String -> String -> (Bool, Bool) Source #
Predicate instructing promptBuffer
to get (and keep) a single non-empty
KeyEvent
.
killBefore :: XP () Source #
Kill the portion of the command before the cursor
startOfLine :: XP () Source #
Put the cursor at the start of line
insertString :: String -> XP () Source #
Insert a character at the cursor position
pasteString :: XP () Source #
Insert the current X selection string at the cursor position. The X selection is not modified.
pasteString' :: (String -> String) -> XP () Source #
A variant of pasteString
which allows modifying the X selection before
pasting.
clipCursor :: XP () Source #
Ensure the cursor remains over the command by shifting left if necessary.
moveCursor :: Direction1D -> XP () Source #
Move the cursor one position.
moveCursorClip :: Direction1D -> XP () Source #
Move the cursor one position, but not beyond the command.
getInput :: XP String Source #
Returns the current input string. Intended for use in custom keymaps
where get
or similar can't be used to retrieve it.
Returns the offset of the current input string. Intended for use in custom
keys where get
or similar can't be used to retrieve it.
defaultColor :: XPConfig -> XPColor Source #
resetColor :: XP () Source #
Reset the prompt colors to those from XPConfig
.
modifyPrompter :: ((String -> String) -> String -> String) -> XP () Source #
Modify the prompter, i.e. for chaining prompters.
resetPrompter :: XP () Source #
Reset the prompter to the one from XPConfig
.
selectedCompletion :: XPState -> String Source #
Return the selected completion, i.e. the String
we actually act
upon after the user confirmed their selection (by pressing Enter
).
setCurrentCompletions :: Maybe [String] -> XP () Source #
Set the current completion list, or Nothing
to invalidate the current
completions.
moveWord :: Direction1D -> XP () Source #
moveWord' :: (Char -> Bool) -> Direction1D -> XP () Source #
Given a direction, move the cursor to just before the next
(predicate,not-predicate) character transition. This means a (not-word,word)
transition should be followed by a moveCursorClip
action. Always considers
the character under the current cursor position. This means a
(word,not-word) transition should be preceded by a moveCursorClip
action.
Calculated as the length of consecutive non-predicate characters starting
from the cursor position, plus the length of subsequent consecutive
predicate characters, plus when moving backwards the distance of the cursor
beyond the input. Reduced by one to avoid jumping off either end of the
input, when present.
Use these identities to retain the pre-0.14 behavior:
(oldMoveWord' p Prev) = (moveCursor Prev >> moveWord' p Prev)
(oldMoveWord' p Next) = (moveWord' p Next >> moveCursor Next)
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.
changeWord :: (Char -> Bool) -> XP () Source #
From Vim's :help cw
:
- Special case: When the cursor is in a word, "cw" and "cW" do not include the white space after a word, they only change up to the end of the word.
deleteString :: Direction1D -> XP () Source #
Remove a character at the cursor position
moveHistory :: (Stack String -> Stack String) -> XP () Source #
Set the prompt's input to an entry further up or further down the history
stack. Use Stack
functions from StackSet
, i.e. focusUp'
or
focusDown'
.
setSuccess :: Bool -> XP () Source #
Set True
to save the prompt's entry to history and run it via the
provided action.
setModeDone :: Bool -> XP () Source #
Set True
to leave the current event loop, i.e. submaps.
data Direction1D Source #
One-dimensional directions:
Instances
Read Direction1D Source # | |
Defined in XMonad.Util.Types readsPrec :: Int -> ReadS Direction1D # readList :: ReadS [Direction1D] # readPrec :: ReadPrec Direction1D # readListPrec :: ReadPrec [Direction1D] # | |
Show Direction1D Source # | |
Defined in XMonad.Util.Types showsPrec :: Int -> Direction1D -> ShowS # show :: Direction1D -> String # showList :: [Direction1D] -> ShowS # | |
Eq Direction1D Source # | |
Defined in XMonad.Util.Types (==) :: Direction1D -> Direction1D -> Bool # (/=) :: Direction1D -> Direction1D -> Bool # |
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 :: XPConfig -> [String] -> String -> IO [String] Source #
This function takes a list of possible completions and returns a
completions function to be used with mkXPrompt
mkComplFunFromList' :: XPConfig -> [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 #
Deprecated: Use XMonad.Prelude.chunksOf instead.
Given a maximum length, splits a list into sublists
uniqSort :: Ord a => [a] -> [a] Source #
Sort a list and remove duplicates. Like deleteAllDuplicates
, but trades off
laziness and stability for efficiency.
historyCompletion :: XPConfig -> X 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 the XMonad cache directory.
historyCompletionP :: XPConfig -> (String -> Bool) -> X 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) , .. }