dmenu-0.1.0.1: Complete bindings to the dmenu and dmenu2 command line tools.

Safe HaskellNone
LanguageHaskell2010

DMenu

Contents

Synopsis

Overview

This module provides complete bindings to the dmenu and dmenu2 command-line tools.

The dmenu command line tool

  1. takes command line Options and reads a list of strings from stdin,
  2. presents the list in a special overlay window, in which the user can select from the list via fuzzy matching, and
  3. prints the selected string to stdout or fails with exit code 1 if the user hit the ESC key.

Typical uses of dmenu are for example

  1. as a program launcher by piping the program names from PATH into dmenu and executing the selected program.
  2. as an interface for killing programs by piping process information from ps aux into dmenu, and running kill -9 on the selected process id.
  3. as an interface for mounting devices by piping the device files from /dev/ into dmenu, and running pmount on 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

selectM Source #

Arguments

:: MonadDMenu m 
=> [String]

List from which the user should select.

-> m (Either ProcessError String)

The selection made by the user, or a ProcessError, if the user canceled.

Run DMenu with the command line options from m and a list of Strings from which the user should choose.

select Source #

Arguments

:: MonadIO m 
=> DMenuT m ()

State Options action which changes the default command line options.

-> [String]

List from which the user should select.

-> m (Either ProcessError String)

The selection made by the user, or a ProcessError, if the user canceled.

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"

selectWithM Source #

Arguments

:: MonadDMenu m 
=> (a -> String)

How to display an a in dmenu.

-> [a]

List from which the user should select.

-> m (Either ProcessError a)

The selection made by the user, or a ProcessError, if the user canceled.

Same as selectM, but allows the user to select from a list of arbitrary elements, which have a String representation.

selectWith Source #

Arguments

:: MonadIO m 
=> DMenuT m ()

State Options action which changes the default command line options.

-> (a -> String)

How to display an a in dmenu.

-> [a]

List from which the user should select.

-> m (Either ProcessError a)

The selection made by the user, or a ProcessError, if the user canceled.

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

filterM Source #

Arguments

:: MonadDMenu m 
=> [String]

List from which the user should filter.

-> m (Either ProcessError [String])

The selection made by the user, or a ProcessError, if the user canceled.

Like selectM but uses the dmenu2 option filterMode, which returns not only the selected item, but all items which fuzzy match the input term.

filter Source #

Arguments

:: MonadIO m 
=> DMenuT m ()

State Options action which changes the default command line options.

-> [String]

List from which the user should select.

-> m (Either ProcessError [String])

The selection made by the user, or a ProcessError, if the user canceled.

Like select but uses the dmenu2 option filterMode, which returns not only the selected item, but all items which fuzzy match the input term.

filterWithM Source #

Arguments

:: MonadDMenu m 
=> (a -> String)

How to display an a in dmenu.

-> [a]

List from which the user should select.

-> m (Either ProcessError [a])

The selection made by the user, or a ProcessError, if the user canceled.

Like selectWithM but uses the dmenu2 option filterMode, which returns not only the selected item, but all items which fuzzy match the input term.

filterWith Source #

Arguments

:: MonadIO m 
=> DMenuT m ()

State Options action which changes the default command line options.

-> (a -> String)

How to display an a in dmenu.

-> [a]

List from which the user should select.

-> m (Either ProcessError [a])

The selection made by the user, or a ProcessError, if the user canceled.

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

data Options Source #

Contains the binary path and command line options of dmenu. The option descriptions are copied from the dmenu man page.

Constructors

Options 

Fields

  • _binaryPath :: FilePath

    Path to the the dmenu executable file. Default looks for dmenu in the PATH enviroment variable.

  • _displayAtBottom :: Bool

    -b; dmenu appears at the bottom of the screen.

  • _grabKeyboardBeforeStdin :: Bool

    -f; dmenu grabs the keyboard before reading stdin. This is faster, but will lock up X until stdin reaches end-of-file.

  • _caseInsensitive :: Bool

    -i; dmenu matches menu items case insensitively.

  • _spawnOnMonitor :: Int

    -m screen; dmenu is displayed on the monitor number supplied. Monitor numbers are starting from 0.

  • _numLines :: Int

    -l lines; dmenu lists items vertically, with the given number of lines.

  • _prompt :: String

    -p prompt; defines the prompt to be displayed to the left of the input field.

  • _font :: String

    -fn font; defines the font or font set used. eg. "fixed" or "Monospace-12:normal" (an xft font)

  • _normalBGColor :: Color

    -nb color; defines the normal background color. #RGB, #RRGGBB, and X color names are supported.

  • _normalFGColor :: Color

    -nf color; defines the normal foreground color.

  • _selectedBGColor :: Color

    -sb color; defines the selected background color.

  • _selectedFGColor :: Color

    -sf color; defines the selected foreground color.

  • _printVersionAndExit :: Bool

    -v; prints version information to stdout, then exits.

  • _dmenu2 :: Options2

    Extra options only available in the dmenu2 fork.

  • _noDMenu2 :: Bool

    When set to True, the dmenu2 options in _dmenu2 are ignored. This ensures compatibility with the normal dmenu. A user may set this flag in the configuration file.

Lenses

dmenu2-specific Command Line Options

data Options2 Source #

Contains the command line options of dmenu2 which are not part of dmenu. The _filterMode option is not listed; it can be implicitly used by using DMenu.filter instead of DMenu.select. The option descriptions are copied from the dmenu2 man page.

Constructors

Options2 

Fields

  • _displayNoItemsIfEmpty :: Bool

    -q; dmenu will not show any items if the search string is empty.

  • _filterMode :: Bool

    -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 :: Bool

    -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 :: Bool

    -t; dmenu uses space-separated tokens to match menu items. Using this overrides -z option.

  • _maskInputWithStar :: Bool

    -mask; dmenu masks input with asterisk characters (*).

  • _ignoreStdin :: Bool

    -noinput; dmenu ignores input from stdin (equivalent to: echo | dmenu).

  • _spawnOnScreen :: Int

    -s screen; dmenu apears on the specified screen number. Number given corespondes to screen number in X optionsuration.

  • _windowName :: String

    -name name; defines window name for dmenu. Defaults to "dmenu".

  • _windowClass :: String

    -class class; defines window class for dmenu. Defaults to "Dmenu".

  • _windowOpacity :: Double

    -o opacity; defines window opacity for dmenu. Defaults to 1.0.

  • _windowDimOpacity :: Double

    -dim opacity; enables screen dimming when dmenu appers. Takes dim opacity as argument.

  • _windowDimColor :: Color

    -dc color; defines color of screen dimming. Active only when -dim in effect. Defautls to black (#000000)

  • _heightInPixels :: Int

    -h height; defines the height of the bar in pixels.

  • _underlineHeightInPixels :: Int

    -uh height; defines the height of the underline in pixels.

  • _windowOffsetX :: Int

    -x xoffset; defines the offset from the left border of the screen.

  • _windowOffsetY :: Int

    -y yoffset; defines the offset from the top border of the screen.

  • _width :: Int

    -w width; defines the desired menu window width.

  • _underlineColor :: Color

    -uc color; defines the underline color.

  • _historyFile :: FilePath

    -hist histfile; the file to use for history

Lenses

Color

data Color Source #

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)
(.=) :: MonadState s m => Iso' s a       -> a -> m ()
(.=) :: MonadState s m => Lens' s a      -> a -> m ()
(.=) :: MonadState s m => Traversal' s a -> a -> m ()
(.=) :: MonadState s 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 shows an example ~/.haskell-dmenu file:

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 with Prelude.read except for Strings which don't need double quotes.