mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
X.U.EZConfig: Use X.U.Parser
Using X.U.Parser works almost as a drop-in replacement for ReadP here. In some places (like `parseSpecial`) we need to be a little bit more careful when constructing the parser, but this is offset a much simpler `readKeySequence`.
This commit is contained in:
parent
b1532e666f
commit
8abeb81fd0
@ -4,6 +4,12 @@
|
||||
|
||||
### Breaking Changes
|
||||
|
||||
* `XMonad.Util.EZConfig`
|
||||
|
||||
- The functions `parseKey`, `parseKeyCombo`, and `parseKeySequence`
|
||||
now return a `Parser` (from `XMonad.Util.Parser`) instead of a
|
||||
`ReadP`.
|
||||
|
||||
### New Modules
|
||||
|
||||
* `XMonad.Layout.CenteredIfSingle`
|
||||
|
@ -39,16 +39,15 @@ module XMonad.Util.EZConfig (
|
||||
|
||||
import XMonad
|
||||
import XMonad.Actions.Submap
|
||||
import XMonad.Prelude hiding (many)
|
||||
import XMonad.Prelude
|
||||
|
||||
import XMonad.Util.NamedActions
|
||||
import XMonad.Util.Parser
|
||||
|
||||
import Control.Arrow (first, (&&&))
|
||||
import qualified Data.Map as M
|
||||
import Data.Ord (comparing)
|
||||
|
||||
import Text.ParserCombinators.ReadP
|
||||
|
||||
-- $usage
|
||||
-- To use this module, first import it into your @~\/.xmonad\/xmonad.hs@:
|
||||
--
|
||||
@ -408,16 +407,15 @@ readKeymap c = mapMaybe (maybeKeys . first (readKeySequence c))
|
||||
-- | Parse a sequence of keys, returning Nothing if there is
|
||||
-- a parse failure (no parse, or ambiguous parse).
|
||||
readKeySequence :: XConfig l -> String -> Maybe [(KeyMask, KeySym)]
|
||||
readKeySequence c = listToMaybe . parses
|
||||
where parses = map fst . filter (null.snd) . readP_to_S (parseKeySequence c)
|
||||
readKeySequence c = runParser (parseKeySequence c)
|
||||
|
||||
-- | Parse a sequence of key combinations separated by spaces, e.g.
|
||||
-- @\"M-c x C-S-2\"@ (mod+c, x, ctrl+shift+2).
|
||||
parseKeySequence :: XConfig l -> ReadP [(KeyMask, KeySym)]
|
||||
parseKeySequence c = sepBy1 (parseKeyCombo c) (many1 $ char ' ')
|
||||
parseKeySequence :: XConfig l -> Parser [(KeyMask, KeySym)]
|
||||
parseKeySequence c = parseKeyCombo c `sepBy1` many1 (char ' ')
|
||||
|
||||
-- | Parse a modifier-key combination such as "M-C-s" (mod+ctrl+s).
|
||||
parseKeyCombo :: XConfig l -> ReadP (KeyMask, KeySym)
|
||||
parseKeyCombo :: XConfig l -> Parser (KeyMask, KeySym)
|
||||
parseKeyCombo c = do mods <- many (parseModifier c)
|
||||
k <- parseKey
|
||||
return (foldl' (.|.) 0 mods, k)
|
||||
@ -425,23 +423,23 @@ parseKeyCombo c = do mods <- many (parseModifier c)
|
||||
-- | Parse a modifier: either M- (user-defined mod-key),
|
||||
-- C- (control), S- (shift), or M#- where # is an integer
|
||||
-- from 1 to 5 (mod1Mask through mod5Mask).
|
||||
parseModifier :: XConfig l -> ReadP KeyMask
|
||||
parseModifier c = (string "M-" >> return (modMask c))
|
||||
+++ (string "C-" >> return controlMask)
|
||||
+++ (string "S-" >> return shiftMask)
|
||||
+++ do _ <- char 'M'
|
||||
parseModifier :: XConfig l -> Parser KeyMask
|
||||
parseModifier c = (string "M-" $> modMask c)
|
||||
<> (string "C-" $> controlMask)
|
||||
<> (string "S-" $> shiftMask)
|
||||
<> do _ <- char 'M'
|
||||
n <- satisfy (`elem` ['1'..'5'])
|
||||
_ <- char '-'
|
||||
return $ indexMod (read [n] - 1)
|
||||
where indexMod = (!!) [mod1Mask,mod2Mask,mod3Mask,mod4Mask,mod5Mask]
|
||||
|
||||
-- | Parse an unmodified basic key, like @\"x\"@, @\"<F1>\"@, etc.
|
||||
parseKey :: ReadP KeySym
|
||||
parseKey = parseRegular +++ parseSpecial
|
||||
parseKey :: Parser KeySym
|
||||
parseKey = parseSpecial <> parseRegular
|
||||
|
||||
-- | Parse a regular key name (represented by itself).
|
||||
parseRegular :: ReadP KeySym
|
||||
parseRegular = choice [ char s >> return k
|
||||
parseRegular :: Parser KeySym
|
||||
parseRegular = choice [ char s $> k
|
||||
| (s,k) <- zip ['!' .. '~' ] -- ASCII
|
||||
[xK_exclam .. xK_asciitilde]
|
||||
|
||||
@ -450,13 +448,11 @@ parseRegular = choice [ char s >> return k
|
||||
]
|
||||
|
||||
-- | Parse a special key name (one enclosed in angle brackets).
|
||||
parseSpecial :: ReadP KeySym
|
||||
parseSpecial :: Parser KeySym
|
||||
parseSpecial = do _ <- char '<'
|
||||
key <- choice [ string name >> return k
|
||||
| (name,k) <- keyNames
|
||||
choice [ k <$ string name <* char '>'
|
||||
| (name, k) <- keyNames
|
||||
]
|
||||
_ <- char '>'
|
||||
return key
|
||||
|
||||
-- | A list of all special key names and their associated KeySyms.
|
||||
keyNames :: [(String, KeySym)]
|
||||
|
@ -28,10 +28,10 @@ import Graphics.X11
|
||||
import Graphics.X11.Xlib.Extras (none, setEventType, setKeyEvent)
|
||||
import Control.Monad.Reader (asks)
|
||||
import XMonad.Operations (withFocused)
|
||||
import XMonad.Prelude (isUpper, listToMaybe)
|
||||
import XMonad.Prelude (isUpper, fromMaybe)
|
||||
import XMonad.Util.XSelection (getSelection)
|
||||
import XMonad.Util.EZConfig (parseKey)
|
||||
import Text.ParserCombinators.ReadP (readP_to_S)
|
||||
import XMonad.Util.Parser (runParser)
|
||||
|
||||
{- $usage
|
||||
|
||||
@ -72,8 +72,8 @@ pasteString = mapM_ (\x -> if isUpper x || x `elem` "~!@#$%^&*()_+{}|:\"<>?" the
|
||||
outside ASCII.
|
||||
-}
|
||||
pasteChar :: KeyMask -> Char -> X ()
|
||||
pasteChar m c = sendKey m $ maybe (unicodeToKeysym c) fst
|
||||
$ listToMaybe $ readP_to_S parseKey [c]
|
||||
pasteChar m c = sendKey m $ fromMaybe (unicodeToKeysym c)
|
||||
$ runParser parseKey [c]
|
||||
|
||||
-- | Send a key with a modifier to the currently focused window.
|
||||
sendKey :: KeyMask -> KeySym -> X ()
|
||||
|
Loading…
x
Reference in New Issue
Block a user