mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Add a GSCONFIG class to overload defaultGSConfig.
This uses -XOverlappingInstances to provide a fallback instance which uses the focusedBorderColor and normalBorderColor, but that part is optional. User's configs should use -XNoMonomorphismRestriction if they want to avoid writing a type signature for myGSConfig. Also, type variables become ambiguous in expressions like: > myGSConfig = defaultGSConfig { gs_navigate = neiu `M.union` gs_navigate defaultGSConfig } > where neiu = M.map (\(x,y) (a,b) -> (x+a,y+b)) $ M.fromList > [((0,xK_n),(-1,0)) ,((0,xK_e),(0,1)) ,((0,xK_i),(1,0)) ,((0,xK_u),(0,-1))] But that can be resolved with the appropriate (`asTypeOf`myGSConfig) applied to the second defaultGSConfig, or the use of some other method for modifying existing fields.
This commit is contained in:
parent
fb7539d74b
commit
4509a8b696
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE ScopedTypeVariables, GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE ScopedTypeVariables, GeneralizedNewtypeDeriving, TypeSynonymInstances, FlexibleInstances, OverlappingInstances #-}
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Actions.GridSelect
|
-- Module : XMonad.Actions.GridSelect
|
||||||
@ -20,10 +20,9 @@ module XMonad.Actions.GridSelect (
|
|||||||
|
|
||||||
-- * Configuration
|
-- * Configuration
|
||||||
GSConfig(..),
|
GSConfig(..),
|
||||||
|
GSCONFIG(defaultGSConfig),
|
||||||
NavigateMap,
|
NavigateMap,
|
||||||
TwoDPosition,
|
TwoDPosition,
|
||||||
defaultGSConfig,
|
|
||||||
defaultGSSpawnConfig,
|
|
||||||
buildDefaultGSConfig,
|
buildDefaultGSConfig,
|
||||||
|
|
||||||
-- * Variations on 'gridselect'
|
-- * Variations on 'gridselect'
|
||||||
@ -75,7 +74,7 @@ import Data.Word (Word8)
|
|||||||
-- the user select from it. E.g. to spawn an application from a given list, you
|
-- the user select from it. E.g. to spawn an application from a given list, you
|
||||||
-- can use the following:
|
-- can use the following:
|
||||||
--
|
--
|
||||||
-- > , ((modMask x, xK_s), spawnSelected defaultGSSpawnConfig ["xterm","gmplayer","gvim"])
|
-- > , ((modMask x, xK_s), spawnSelected defaultGSConfig ["xterm","gmplayer","gvim"])
|
||||||
|
|
||||||
-- $screenshots
|
-- $screenshots
|
||||||
--
|
--
|
||||||
@ -98,6 +97,31 @@ data GSConfig a = GSConfig {
|
|||||||
gs_originFractY :: Double
|
gs_originFractY :: Double
|
||||||
}
|
}
|
||||||
|
|
||||||
|
class GSCONFIG a where
|
||||||
|
defaultGSConfig :: GSConfig a -- ^ A basic configuration for 'gridselect'.
|
||||||
|
-- To configure your own colorizer, use
|
||||||
|
-- 'buildDefaultGSConfig', otherwise the
|
||||||
|
-- default colorizer with the correct type
|
||||||
|
-- will be used.
|
||||||
|
--
|
||||||
|
-- That is 'fromClassName' if
|
||||||
|
-- you are selecting a 'Window', or
|
||||||
|
-- 'defaultColorizer' if you are selecting a
|
||||||
|
-- 'String'. The catch-all instance @GSCONFIG
|
||||||
|
-- a@ uses the 'focusedBorderColor' and
|
||||||
|
-- 'normalBorderColor' colors.
|
||||||
|
|
||||||
|
instance GSCONFIG Window where
|
||||||
|
defaultGSConfig = buildDefaultGSConfig fromClassName
|
||||||
|
|
||||||
|
instance GSCONFIG String where
|
||||||
|
defaultGSConfig = buildDefaultGSConfig defaultColorizer
|
||||||
|
|
||||||
|
instance GSCONFIG a where
|
||||||
|
defaultGSConfig = buildDefaultGSConfig $ \_ isFg -> do
|
||||||
|
let getColor = if isFg then focusedBorderColor else normalBorderColor
|
||||||
|
asks $ flip (,) "black" . getColor . config
|
||||||
|
|
||||||
type NavigateMap = M.Map (KeyMask,KeySym) (TwoDPosition -> TwoDPosition)
|
type NavigateMap = M.Map (KeyMask,KeySym) (TwoDPosition -> TwoDPosition)
|
||||||
|
|
||||||
type TwoDPosition = (Integer, Integer)
|
type TwoDPosition = (Integer, Integer)
|
||||||
@ -334,9 +358,8 @@ gridselect gsconfig elmap =
|
|||||||
font <- initXMF (gs_font gsconfig)
|
font <- initXMF (gs_font gsconfig)
|
||||||
let screenWidth = toInteger $ rect_width s;
|
let screenWidth = toInteger $ rect_width s;
|
||||||
screenHeight = toInteger $ rect_height s;
|
screenHeight = toInteger $ rect_height s;
|
||||||
selectedElement <- if (status == grabSuccess) then
|
selectedElement <- if (status == grabSuccess) then do
|
||||||
do
|
let restriction ss cs = (fromInteger ss/fromInteger (cs gsconfig)-1)/2 :: Double
|
||||||
let restriction ss cs = ((fromInteger ss)/(fromInteger $ cs gsconfig)-1)/2
|
|
||||||
restrictX = floor $ restriction screenWidth gs_cellwidth
|
restrictX = floor $ restriction screenWidth gs_cellwidth
|
||||||
restrictY = floor $ restriction screenHeight gs_cellheight
|
restrictY = floor $ restriction screenHeight gs_cellheight
|
||||||
originPosX = floor $ ((gs_originFractX gsconfig) - (1/2)) * 2 * fromIntegral restrictX
|
originPosX = floor $ ((gs_originFractX gsconfig) - (1/2)) * 2 * fromIntegral restrictX
|
||||||
@ -386,10 +409,6 @@ decorateName' :: Window -> X String
|
|||||||
decorateName' w = do
|
decorateName' w = do
|
||||||
fmap show $ getName w
|
fmap show $ getName w
|
||||||
|
|
||||||
-- | The default 'GSConfig' to use when selecting windows.
|
|
||||||
defaultGSConfig :: GSConfig Window
|
|
||||||
defaultGSConfig = buildDefaultGSConfig fromClassName
|
|
||||||
|
|
||||||
-- | Builds a default gs config from a colorizer function.
|
-- | Builds a default gs config from a colorizer function.
|
||||||
buildDefaultGSConfig :: (a -> Bool -> X (String,String)) -> GSConfig a
|
buildDefaultGSConfig :: (a -> Bool -> X (String,String)) -> GSConfig a
|
||||||
buildDefaultGSConfig col = GSConfig 50 130 10 col "xft:Sans-8" defaultGSNav (1/2) (1/2)
|
buildDefaultGSConfig col = GSConfig 50 130 10 col "xft:Sans-8" defaultGSNav (1/2) (1/2)
|
||||||
@ -420,9 +439,6 @@ bringSelected = withSelectedWindow $ \w -> do
|
|||||||
goToSelected :: GSConfig Window -> X ()
|
goToSelected :: GSConfig Window -> X ()
|
||||||
goToSelected = withSelectedWindow $ windows . W.focusWindow
|
goToSelected = withSelectedWindow $ windows . W.focusWindow
|
||||||
|
|
||||||
defaultGSSpawnConfig :: GSConfig String
|
|
||||||
defaultGSSpawnConfig = buildDefaultGSConfig defaultColorizer
|
|
||||||
|
|
||||||
-- | Select an application to spawn from a given list
|
-- | Select an application to spawn from a given list
|
||||||
spawnSelected :: GSConfig String -> [String] -> X ()
|
spawnSelected :: GSConfig String -> [String] -> X ()
|
||||||
spawnSelected conf lst = gridselect conf (zip lst lst) >>= flip whenJust spawn
|
spawnSelected conf lst = gridselect conf (zip lst lst) >>= flip whenJust spawn
|
||||||
|
@ -41,21 +41,14 @@ import XMonad.Util.XUtils (fi)
|
|||||||
--
|
--
|
||||||
-- > , ((modMask x, xK_o ), windowMenu)
|
-- > , ((modMask x, xK_o ), windowMenu)
|
||||||
|
|
||||||
simpleColorizer :: (Monad m) => t -> t -> t1 -> Bool -> m (t, [Char])
|
|
||||||
simpleColorizer nBC _ _ False = return (nBC, "black")
|
|
||||||
simpleColorizer _ fBC _ True = return (fBC, "black")
|
|
||||||
|
|
||||||
windowMenu :: X ()
|
windowMenu :: X ()
|
||||||
windowMenu = withFocused $ \w -> do
|
windowMenu = withFocused $ \w -> do
|
||||||
nBC <- asks (normalBorderColor . config)
|
|
||||||
fBC <- asks (focusedBorderColor . config)
|
|
||||||
tags <- asks (workspaces . config)
|
tags <- asks (workspaces . config)
|
||||||
Rectangle x y wh ht <- getSize w
|
Rectangle x y wh ht <- getSize w
|
||||||
Rectangle sx sy swh sht <- gets $ screenRect . W.screenDetail . W.current . windowset
|
Rectangle sx sy swh sht <- gets $ screenRect . W.screenDetail . W.current . windowset
|
||||||
let originFractX = (fi x - fi sx + fi wh / 2) / fi swh
|
let originFractX = (fi x - fi sx + fi wh / 2) / fi swh
|
||||||
originFractY = (fi y - fi sy + fi ht / 2) / fi sht
|
originFractY = (fi y - fi sy + fi ht / 2) / fi sht
|
||||||
colorizer = simpleColorizer nBC fBC
|
gsConfig = defaultGSConfig
|
||||||
gsConfig = (buildDefaultGSConfig colorizer)
|
|
||||||
{ gs_originFractX = originFractX
|
{ gs_originFractX = originFractX
|
||||||
, gs_originFractY = originFractY }
|
, gs_originFractY = originFractY }
|
||||||
actions = [ ("Cancel menu", return ())
|
actions = [ ("Cancel menu", return ())
|
||||||
|
Loading…
x
Reference in New Issue
Block a user