| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DMenu
Contents
- type DMenuT = StateT Options
- type MonadDMenu m = (MonadIO m, MonadState Options m)
- type ProcessError = (Int, String)
- run :: MonadIO m => DMenuT m a -> m a
- selectM :: MonadDMenu m => [String] -> m (Either ProcessError String)
- select :: MonadIO m => DMenuT m () -> [String] -> m (Either ProcessError String)
- selectWithM :: MonadDMenu m => (a -> String) -> [a] -> m (Either ProcessError a)
- selectWith :: MonadIO m => DMenuT m () -> (a -> String) -> [a] -> m (Either ProcessError a)
- filterM :: MonadDMenu m => [String] -> m (Either ProcessError [String])
- filter :: MonadIO m => DMenuT m () -> [String] -> m (Either ProcessError [String])
- filterWithM :: MonadDMenu m => (a -> String) -> [a] -> m (Either ProcessError [a])
- filterWith :: MonadIO m => DMenuT m () -> (a -> String) -> [a] -> m (Either ProcessError [a])
- data Options
- binaryPath :: Lens' Options FilePath
- displayAtBottom :: Lens' Options Bool
- grabKeyboardBeforeStdin :: Lens' Options Bool
- caseInsensitive :: Lens' Options Bool
- spawnOnMonitor :: Lens' Options Int
- numLines :: Lens' Options Int
- prompt :: Lens' Options String
- font :: Lens' Options String
- normalBGColor :: Lens' Options Color
- normalFGColor :: Lens' Options Color
- selectedBGColor :: Lens' Options Color
- selectedFGColor :: Lens' Options Color
- printVersionAndExit :: Lens' Options Bool
- dmenu2 :: Lens' Options Options2
- noDMenu2 :: Lens' Options Bool
- extraArgs :: Lens' Options [String]
- forwardExtraArgs :: MonadDMenu m => m ()
- data Options2
- displayNoItemsIfEmpty :: Lens' Options2 Bool
- filterMode :: Lens' Options2 Bool
- fuzzyMatching :: Lens' Options2 Bool
- tokenMatching :: Lens' Options2 Bool
- maskInputWithStar :: Lens' Options2 Bool
- ignoreStdin :: Lens' Options2 Bool
- spawnOnScreen :: Lens' Options2 Int
- windowName :: Lens' Options2 String
- windowClass :: Lens' Options2 String
- windowOpacity :: Lens' Options2 Double
- windowDimOpacity :: Lens' Options2 Double
- windowDimColor :: Lens' Options2 Color
- heightInPixels :: Lens' Options2 Int
- underlineHeightInPixels :: Lens' Options2 Int
- windowOffsetX :: Lens' Options2 Int
- windowOffsetY :: Lens' Options2 Int
- width :: Lens' Options2 Int
- underlineColor :: Lens' Options2 Color
- historyFile :: Lens' Options2 FilePath
- data Color
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- configFileUsage :: String
Overview
This module provides complete bindings to the dmenu and dmenu2 command-line tools.

The dmenu command line tool
- takes command line
Optionsand reads a list of strings fromstdin, - presents the list in a special overlay window, in which the user can select from the list via fuzzy matching, and
- prints the selected string to
stdoutor fails with exit code1if the user hit theESCkey.
Typical uses of dmenu are for example
- as a program launcher by piping the program names from
PATHintodmenuand executing the selected program. - as an interface for killing programs by piping process information from
ps auxintodmenu, and runningkill -9on the selected process id. - as an interface for mounting devices by piping the device files from
/dev/intodmenu, and runningpmounton the selected device (shown in the image above).
dmenu2 is a fork of dmenu, which provides additional options, e.g. selecting
multiple items at once.
Ontop of the functionality of dmenu and dmenu2, this library
supports a configuration file for specifying default command line options for
dmenu. See the last section for more on the configuration file.
The simplest way to run dmenu is with the select function.
Note for stack users: When running programs using this library via
stack exec, the program may fail to find dmenu in the PATH.
This problem can be solved by running the program directly without stack, or
by temporarily using an absolute path for dmenu in the binaryPath option.
Types
type DMenuT = StateT Options Source #
A state monad transformer in which the command line options of dmenu can
be configured.
type MonadDMenu m = (MonadIO m, MonadState Options m) Source #
The MonadIO constraint additionally allows to spawn processes with
System.Process in between.
type ProcessError = (Int, String) Source #
When a spawned process fails, this type is used to represent the exit code
and stderr output.
Running dmenu
run :: MonadIO m => DMenuT m a -> m a Source #
Run a StateT Options m a action using the command line options from the
config file or an empty set of options as initial state.
For example
import qualified DMenu main :: IO () main = DMenu.run $ do DMenu.numLines .= 10 DMenu.prompt .= "run" liftIO . print =<< DMenu.selectM ["A","B","C"]
Selecting a single item
Arguments
| :: MonadDMenu m | |
| => [String] | List from which the user should select. |
| -> m (Either ProcessError String) | The selection made by the user, or a |
Run DMenu with the command line options from m and a list of Strings
from which the user should choose.
Arguments
| :: MonadIO m | |
| => DMenuT m () |
|
| -> [String] | List from which the user should select. |
| -> m (Either ProcessError String) | The selection made by the user, or a |
Convenience function combining run and selectM.
The following example has the same behavior as the example for run:
import qualified DMenu main :: IO () main = print =<< DMenu.select setOptions ["A","B","C"] setOptions :: DMenu.MonadDMenu m => m () setOptions = do DMenu.numLines .= 10 DMenu.prompt .= "run"
Arguments
| :: MonadDMenu m | |
| => (a -> String) | How to display an |
| -> [a] | List from which the user should select. |
| -> m (Either ProcessError a) | The selection made by the user, or a |
Arguments
| :: MonadIO m | |
| => DMenuT m () |
|
| -> (a -> String) | How to display an |
| -> [a] | List from which the user should select. |
| -> m (Either ProcessError a) | The selection made by the user, or a |
Same as select, but allows the user to select from a list of arbitrary
elements, which have a String representation.
For example
import qualified DMenu main :: IO () main = print =<< DMenu.selectWith setOptions show [1..10::Int] setOptions :: DMenu.MonadDMenu m => m () setOptions = do DMenu.numLines .= 10 DMenu.prompt .= "run"
Selecting multiple items
Arguments
| :: MonadDMenu m | |
| => [String] | List from which the user should filter. |
| -> m (Either ProcessError [String]) | The selection made by the user, or a |
Like selectM but uses the dmenu2 option filterMode, which
returns not only the selected item, but all items which fuzzy match the
input term.
Arguments
| :: MonadIO m | |
| => DMenuT m () |
|
| -> [String] | List from which the user should select. |
| -> m (Either ProcessError [String]) | The selection made by the user, or a |
Like select but uses the dmenu2 option filterMode, which
returns not only the selected item, but all items which fuzzy match the
input term.
Arguments
| :: MonadDMenu m | |
| => (a -> String) | How to display an |
| -> [a] | List from which the user should select. |
| -> m (Either ProcessError [a]) | The selection made by the user, or a |
Like selectWithM but uses the dmenu2 option filterMode, which
returns not only the selected item, but all items which fuzzy match the
input term.
Arguments
| :: MonadIO m | |
| => DMenuT m () |
|
| -> (a -> String) | How to display an |
| -> [a] | List from which the user should select. |
| -> m (Either ProcessError [a]) | The selection made by the user, or a |
Like selectWith but uses the dmenu2 option filterMode, which
returns not only the selected item, but all items which fuzzy match the
input term.
dmenu Command Line Options
Contains the binary path and command line options of dmenu.
The option descriptions are copied from the dmenu man page.
Lenses
binaryPath :: Lens' Options FilePath Source #
Path to the the dmenu executable file.
Default looks for dmenu in the PATH enviroment variable.
grabKeyboardBeforeStdin :: Lens' Options Bool Source #
-f; dmenu grabs the keyboard before reading stdin. This is faster, but
will lock up X until stdin reaches end-of-file.
spawnOnMonitor :: Lens' Options Int Source #
-m screen; dmenu is displayed on the monitor number supplied. Monitor
numbers are starting from 0.
numLines :: Lens' Options Int Source #
-l lines; dmenu lists items vertically, with the given number of lines.
prompt :: Lens' Options String Source #
-p prompt; defines the prompt to be displayed to the left of the input
field.
font :: Lens' Options String Source #
-fn font; defines the font or font set used. eg. "fixed" or
"Monospace-12:normal" (an xft font)
normalBGColor :: Lens' Options Color Source #
-nb color; defines the normal background color. #RGB, #RRGGBB, and X
color names are supported.
printVersionAndExit :: Lens' Options Bool Source #
-v; prints version information to stdout, then exits.
noDMenu2 :: Lens' Options Bool Source #
When set to True, the dmenu2 options are ignored. This
ensures compatibility with the normal dmenu. A user may set this flag
in the configuration file.
extraArgs :: Lens' Options [String] Source #
List of extra command line arguments to pass to dmenu.
This can be useful, when the client wants to forward some of its own command
line arguments directly to the executed dmenu processes.
Default: []
Forwarding Command Line Arguments
forwardExtraArgs :: MonadDMenu m => m () Source #
dmenu2-specific Command Line Options
Contains the command line options of dmenu2 which are not part of
dmenu. The option descriptions are copied from the dmenu2 man page.
Lenses
displayNoItemsIfEmpty :: Lens' Options2 Bool Source #
-q; dmenu will not show any items if the search string is empty.
filterMode :: Lens' Options2 Bool Source #
-r; activates filter mode. All matching items currently shown in the list
will be selected, starting with the item that is highlighted and wrapping around
to the beginning of the list. (Note: Instead of setting this flag yourself,
the dmenu filter functions can be used instead of the select functions.)
fuzzyMatching :: Lens' Options2 Bool Source #
-z; dmenu uses fuzzy matching. It matches items that have all characters
entered, in sequence they are entered, but there may be any number of characters
between matched characters. For example it takes "txt" makes it to
"*t*x*t" glob pattern and checks if it matches.
tokenMatching :: Lens' Options2 Bool Source #
-t; dmenu uses space-separated tokens to match menu items. Using this
overrides -z option.
maskInputWithStar :: Lens' Options2 Bool Source #
-mask; dmenu masks input with asterisk characters (*).
ignoreStdin :: Lens' Options2 Bool Source #
-noinput; dmenu ignores input from stdin (equivalent to: echo | dmenu).
spawnOnScreen :: Lens' Options2 Int Source #
-s screen; dmenu apears on the specified screen number. Number given
corespondes to screen number in X configuration.
windowName :: Lens' Options2 String Source #
-name name; defines window name for dmenu. Defaults to "dmenu".
windowClass :: Lens' Options2 String Source #
-class class; defines window class for dmenu. Defaults to "Dmenu".
windowOpacity :: Lens' Options2 Double Source #
-o opacity; defines window opacity for dmenu. Defaults to 1.0.
windowDimOpacity :: Lens' Options2 Double Source #
-dim opacity; enables screen dimming when dmenu appers. Takes dim opacity
as argument.
windowDimColor :: Lens' Options2 Color Source #
-dc color; defines color of screen dimming. Active only when -dim in
effect. Defautls to black (#000000)
underlineHeightInPixels :: Lens' Options2 Int Source #
-uh height; defines the height of the underline in pixels.
windowOffsetX :: Lens' Options2 Int Source #
-x xoffset; defines the offset from the left border of the screen.
windowOffsetY :: Lens' Options2 Int Source #
-y yoffset; defines the offset from the top border of the screen.
Color
Multiple representations for colors.
For example, green can be defined as
green1 = HexColor 0x00FF00 green2 = RGBColor 0 255 0 green3 = RGBColorF 0 1 0
Reexports from lens
(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 #
Replace the target of a Lens or all of the targets of a Setter
or Traversal in our monadic state with a new value, irrespective of the
old.
This is an infix version of assign.
>>>execState (do _1 .= c; _2 .= d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
(.=) ::MonadStates m =>Iso's a -> a -> m () (.=) ::MonadStates m =>Lens's a -> a -> m () (.=) ::MonadStates m =>Traversal's a -> a -> m () (.=) ::MonadStates m =>Setter's a -> a -> m ()
It puts the state in the monad or it gets the hose again.
Configuration File
The default Options used by run, select, etc. can be specified
in the ~/.haskell-dmenu file.
The following example shows the ~/.haskell-dmenu file used for the image from
the first section:
numLines 15 font "FiraMono:size=11" caseInsensitive True normalBGColor RGBColorF 0.02 0.02 0.02
The configuration file contains one line per option.
Each line consists of an option name and a value for the option.
The option names are identical to the corresponding lens names.
The values are read via their Read instances.
If reading a value fails, exitFailure is called and an error message is
presented to the user, e.g.
`caseInsensitive` must be a boolean, i.e. `True` or `False`.