Added messages to adjust the gap dynamically

This commit is contained in:
anton.pirogov 2015-03-04 08:25:20 +00:00
parent 80348bb4b7
commit 0857f71938

View File

@ -1,5 +1,4 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -22,12 +21,12 @@ module XMonad.Layout.Spacing (
spacingWithEdge, SpacingWithEdge, spacingWithEdge, SpacingWithEdge,
smartSpacing, SmartSpacing, smartSpacing, SmartSpacing,
smartSpacingWithEdge, SmartSpacingWithEdge, smartSpacingWithEdge, SmartSpacingWithEdge,
SpacingMsg(..)
) where ) where
import Graphics.X11 (Rectangle(..)) import Graphics.X11 (Rectangle(..))
import Control.Arrow (second) import Control.Arrow (second)
import XMonad.Core (runLayout,Message,fromMessage,Typeable) import XMonad.Core (runLayout)
import XMonad.StackSet (up, down, Workspace(..)) import XMonad.StackSet (up, down, Workspace(..))
import XMonad.Util.Font (fi) import XMonad.Util.Font (fi)
@ -50,19 +49,10 @@ spacing p = ModifiedLayout (Spacing p)
data Spacing a = Spacing Int deriving (Show, Read) data Spacing a = Spacing Int deriving (Show, Read)
-- | Message to dynamically increase, decrease or set the size of the window spacing
data SpacingMsg = SetSpacing Int | IncSpacing Int deriving (Show,Read,Eq,Typeable)
instance Message SpacingMsg
instance LayoutModifier Spacing a where instance LayoutModifier Spacing a where
pureModifier (Spacing p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing) pureModifier (Spacing p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
pureMess (Spacing px) m
| Just (SetSpacing px') <- fromMessage m = Just $ Spacing (max 0 px')
| Just (IncSpacing n) <- fromMessage m = Just $ Spacing (max 0 (px+n))
| otherwise = Nothing
modifierDescription (Spacing p) = "Spacing " ++ show p modifierDescription (Spacing p) = "Spacing " ++ show p
-- | Surround all windows by a certain number of pixels of blank space, and -- | Surround all windows by a certain number of pixels of blank space, and
@ -76,11 +66,6 @@ instance LayoutModifier SpacingWithEdge a where
pureModifier (SpacingWithEdge p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing) pureModifier (SpacingWithEdge p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
pureMess (SpacingWithEdge px) m
| Just (SetSpacing px') <- fromMessage m = Just $ SpacingWithEdge (max 0 px')
| Just (IncSpacing n) <- fromMessage m = Just $ SpacingWithEdge (max 0 (px+n))
| otherwise = Nothing
modifyLayout (SpacingWithEdge p) w r = runLayout w (shrinkRect p r) modifyLayout (SpacingWithEdge p) w r = runLayout w (shrinkRect p r)
modifierDescription (SpacingWithEdge p) = "SpacingWithEdge " ++ show p modifierDescription (SpacingWithEdge p) = "SpacingWithEdge " ++ show p