Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 = Options {
- _binaryPath :: FilePath
- _displayAtBottom :: Bool
- _grabKeyboardBeforeStdin :: Bool
- _caseInsensitive :: Bool
- _spawnOnMonitor :: Int
- _numLines :: Int
- _prompt :: String
- _font :: String
- _normalBGColor :: Color
- _normalFGColor :: Color
- _selectedBGColor :: Color
- _selectedFGColor :: Color
- _printVersionAndExit :: Bool
- _dmenu2 :: Options2
- _noDMenu2 :: Bool
- 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
- data Options2 = Options2 {
- _displayNoItemsIfEmpty :: Bool
- _filterMode :: Bool
- _fuzzyMatching :: Bool
- _tokenMatching :: Bool
- _maskInputWithStar :: Bool
- _ignoreStdin :: Bool
- _spawnOnScreen :: Int
- _windowName :: String
- _windowClass :: String
- _windowOpacity :: Double
- _windowDimOpacity :: Double
- _windowDimColor :: Color
- _heightInPixels :: Int
- _underlineHeightInPixels :: Int
- _windowOffsetX :: Int
- _windowOffsetY :: Int
- _width :: Int
- _underlineColor :: Color
- _historyFile :: FilePath
- 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 ()
Overview
This module provides complete bindings to the dmenu and dmenu2 command-line tools.
The dmenu
command line tool
- takes command line
Options
and 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
stdout
or fails with exit code1
if the user hit theESC
key.
Typical uses of dmenu
are for example
- as a program launcher by piping the program names from
PATH
intodmenu
and executing the selected program. - as an interface for killing programs by piping process information from
ps aux
intodmenu
, and runningkill -9
on the selected process id. - as an interface for mounting devices by piping the device files from
/dev/
intodmenu
, and runningpmount
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
:: 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 String
s
from which the user should choose.
:: 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"
:: 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 |
:: 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
:: 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.
:: 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.
:: 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.
:: 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.
Options | |
|
Lenses
dmenu2
-specific Command Line Options
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.
Options2 | |
|
Lenses
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)
(.=
) ::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 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 with Prelude.read
except for Strings
which don't need double quotes.