dots-of-war/xmonad/.xmonad/lib/Rofi.hs

60 lines
2.1 KiB
Haskell
Raw Normal View History

2020-06-21 10:41:26 +00:00
{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
module Rofi
( asCommand
, promptSimple
, promptMap
, promptRunCommand
, showNormal
, showCombi
, RofiConfig(..)
)
where
import Data.List ( intercalate )
import qualified Data.Map as M
import XMonad
import qualified XMonad.Util.Dmenu as Dmenu
import qualified XMonad.Actions.Commands as XCommands
rofiCmd :: String
rofiCmd = "rofi"
data RofiConfig
2020-08-16 21:05:10 +00:00
= RofiConfig { caseInsensitive :: Bool, fuzzy :: Bool } deriving (Show, Eq)
2020-06-21 10:41:26 +00:00
instance Default RofiConfig where
2020-08-16 21:05:10 +00:00
def = RofiConfig { caseInsensitive = True, fuzzy = True }
2020-06-21 10:41:26 +00:00
toArgList :: RofiConfig -> [String]
toArgList RofiConfig {..} = concat
2020-08-16 21:05:10 +00:00
[addIf caseInsensitive ["-i"], addIf fuzzy ["-matching", "fuzzy"]]
2020-06-21 10:41:26 +00:00
where addIf check list = if check then list else []
-- |given an array of arguments, generate a string that would call rofi with the configuration and arguments
asCommand :: RofiConfig -> [String] -> String
asCommand config args = unwords $ rofiCmd : toArgList config ++ args
-- |Let the user choose an element of a list
promptSimple :: MonadIO m => RofiConfig -> [String] -> m String
promptSimple config = Dmenu.menuArgs rofiCmd ("-dmenu" : toArgList config)
-- |Let the user choose an entry of a map by key. return's the chosen value.
promptMap :: MonadIO m => RofiConfig -> M.Map String a -> m (Maybe a)
promptMap config = Dmenu.menuMapArgs rofiCmd ("-dmenu" : toArgList config)
-- |Display a list of commands, of which the chosen one will be executed. See `Xmonad.Actions.Commands.runCommandConfig`
promptRunCommand :: RofiConfig -> [(String, X ())] -> X ()
promptRunCommand config = XCommands.runCommandConfig (Rofi.promptSimple config)
-- |prompt a single rofi mode. ex: `showNormal def "run"`
showNormal :: RofiConfig -> String -> X ()
showNormal config mode =
2021-08-14 09:06:01 +00:00
spawn $ asCommand config ["-modi " ++ mode, "-show " ++ mode]
2020-06-21 10:41:26 +00:00
-- |Show a rofi combi prompt, combining all given modes
showCombi :: RofiConfig -> [String] -> X ()
showCombi config modi = spawn
2021-08-14 09:06:01 +00:00
$ asCommand config ["-show combi", "-combi-modi " ++ intercalate "," modi]