merge conflicts in X.L.Spacing

I should have just applied Anton Pirogov March 4 patch.
This commit is contained in:
Adam Vogt 2015-03-10 18:20:46 +00:00
parent 0857f71938
commit e4fde08a0a

View File

@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-}
{-# LANGUAGE PatternGuards #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
@ -21,12 +22,13 @@ module XMonad.Layout.Spacing (
spacingWithEdge, SpacingWithEdge, spacingWithEdge, SpacingWithEdge,
smartSpacing, SmartSpacing, smartSpacing, SmartSpacing,
smartSpacingWithEdge, SmartSpacingWithEdge, smartSpacingWithEdge, SmartSpacingWithEdge,
ModifySpacing(..), setSpacing, incSpacing
) where ) where
import Graphics.X11 (Rectangle(..)) import Graphics.X11 (Rectangle(..))
import Control.Arrow (second) import Control.Arrow (second)
import XMonad.Core (runLayout) import XMonad.Operations (sendMessage)
import XMonad.Core (runLayout,Message,fromMessage,Typeable)
import XMonad.StackSet (up, down, Workspace(..)) import XMonad.StackSet (up, down, Workspace(..))
import XMonad.Util.Font (fi) import XMonad.Util.Font (fi)
@ -49,10 +51,26 @@ spacing p = ModifiedLayout (Spacing p)
data Spacing a = Spacing Int deriving (Show, Read) data Spacing a = Spacing Int deriving (Show, Read)
-- | Message to dynamically modify (e.g. increase/decrease/set) the size of the window spacing
data ModifySpacing = ModifySpacing (Int -> Int) deriving (Typeable)
instance Message ModifySpacing
-- | Set spacing to given amount
setSpacing :: Int -> X ()
setSpacing n = sendMessage $ ModifySpacing $ const n
-- | Increase spacing by given amount
incSpacing :: Int -> X ()
incSpacing n = sendMessage $ ModifySpacing $ (+n)
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 (ModifySpacing f) <- fromMessage m = Just $ Spacing $ max 0 $ f px
| 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
@ -66,6 +84,10 @@ 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 (ModifySpacing f) <- fromMessage m = Just $ SpacingWithEdge $ max 0 $ f px
| 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