Skip to content

Commit

Permalink
change all the spacing at once with "M-<Space>"; remove Local.Overwri…
Browse files Browse the repository at this point in the history
…te.Layout when xmonad/xmonad#219 gets accepted
  • Loading branch information
jumper149 committed Mar 31, 2020
1 parent c96fc31 commit 9f43542
Show file tree
Hide file tree
Showing 3 changed files with 175 additions and 13 deletions.
12 changes: 8 additions & 4 deletions .config/xmonad/lib/Local/Keys.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,14 +10,14 @@ import XMonad.Actions.CycleWS ( nextWS
)
import XMonad.Actions.SpawnOn ( spawnOn
)
import XMonad.Layout.Spacing ( toggleWindowSpacingEnabled
, toggleScreenSpacingEnabled
)
import XMonad.Util.EZConfig ( additionalKeysP
, removeKeysP
)

import Local.Workspace
import Local.LayoutHook ( toggleGaps
, cycleLayout
)

myKeys :: [(String , X ())]
myKeys = [ ("M-S-q" , kill)
Expand All @@ -29,9 +29,11 @@ myKeys = [ ("M-S-q" , kill)
, ("M-S-h" , sendMessage Shrink)
, ("M-S-l" , sendMessage Expand)
, ("M-<Backspace>" , withFocused $ windows . S.sink)
, ("M-S-t" , toggleWindowSpacingEnabled >> toggleScreenSpacingEnabled)
, ("M-S-t" , toggleGaps)
, ("M-<Tab>" , nextWS)
, ("M-S-<Tab>" , prevWS)
, ("M-<Space>" , cycleLayout) -- TODO: only necessary because https://github.com/xmonad/xmonad/pull/219 is not merged; fix in 'Overwrite.Layout';
-- maybe also don't clear the default-keybinds "M-<Space>" and "M-S-<Space>"
, ("M-h" , screenWorkspace 0 >>= flip whenJust (windows . S.view))
, ("M-<Left>" , screenWorkspace 0 >>= flip whenJust (windows . S.view))
, ("M-l" , screenWorkspace 1 >>= flip whenJust (windows . S.view))
Expand Down Expand Up @@ -103,6 +105,8 @@ terminalFromConf = reader $ terminal . config
myRemovedKeys :: [String]
myRemovedKeys = [ "M-q" -- quit
, "M-S-q" -- restart
, "M-<Space>" -- cycle layouts
, "M-S-<Space>" -- reset current layout
, "M-w" -- Xinerama 1
, "M-S-w"
, "M-e" -- Xinerama 2
Expand Down
73 changes: 64 additions & 9 deletions .config/xmonad/lib/Local/LayoutHook.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,16 @@
module Local.LayoutHook where
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

import XMonad
module Local.LayoutHook ( myLayoutHook
, toggleGaps
, cycleLayout
) where

import XMonad hiding ( Choose
, (|||)
, ChangeLayout ( NextLayout
)
)
import XMonad.StackSet as S
import XMonad.Hooks.ManageDocks ( avoidStruts
)
import XMonad.Layout.Decoration ( Theme (..)
Expand All @@ -12,10 +22,19 @@ import XMonad.Layout.PerWorkspace ( onWorkspace
)
import XMonad.Layout.Spacing ( Border (..)
, spacingRaw
, SpacingModifier (..)
)
import XMonad.Layout.Tabbed ( tabbed
)

import Data.Foldable (traverse_)
import Data.Maybe (fromMaybe)

import Local.Overwrite.Layout ( Choose (..)
, (|||)
, ChangeLayout (..)
)

import Local.Color
import Local.Workspace

Expand All @@ -32,9 +51,9 @@ myTabTheme = def { activeColor = color2 colors
, fontName = "xft:Inconsolata:size=12:style=Bold:antialias=true"
}

myMainLayout = avoidStruts tiled
||| avoidStruts (Mirror tiled)
||| noBorders Full
myMainLayout = avoidStruts tiled
|||| avoidStruts (Mirror tiled)
|||| noBorders Full
where tiled = spacingRaw False
(Border outer outer outer outer) True
(Border inner inner inner inner) True
Expand All @@ -43,11 +62,11 @@ myMainLayout = avoidStruts tiled
outer = 20
inner = 10

myBrowserLayout = avoidStruts (noBorders (tabbed shrinkText myTabTheme))
||| noBorders Full
myBrowserLayout = avoidStruts (noBorders (tabbed shrinkText myTabTheme))
|||| noBorders Full

myWritingLayout = myMainLayout
||| avoidStruts single
myWritingLayout = myMainLayout
|||| avoidStruts single
where single = spacingRaw False
(Border topbot topbot sides sides) True
(Border 0 0 0 0 ) False
Expand All @@ -58,3 +77,39 @@ myWritingLayout = myMainLayout
myLayoutHook = onWorkspace (show WsBrowser) myBrowserLayout
. onWorkspace (show WsWriting) myWritingLayout
$ myMainLayout

-- | Toggle gaps on all workspaces.
toggleGaps :: X ()
toggleGaps = do traverse_ broadcastMessage messages
refresh
where messages = [ ModifyWindowBorderEnabled not
, ModifyScreenBorderEnabled not
]

cycleLayout :: X ()
cycleLayout = sendMessage NextLayout

newtype MyChoose l r a = MyChoose (Choose l r a)
deriving (Read, Show)

(||||) :: l a -> r a -> MyChoose l r a
(||||) l r = MyChoose $ l ||| r
infixr 5 ||||

instance (LayoutClass l a, LayoutClass r a) => LayoutClass (MyChoose l r) a where

runLayout (S.Workspace i (MyChoose c) a) r = do (ls , mbC) <- runLayout (S.Workspace i c a) r
return (ls , MyChoose <$> mbC)

description (MyChoose c) = description c

handleMessage (MyChoose (Choose d l r)) sm =
let sendBoth = do ml <- handleMessage l sm
mr <- handleMessage r sm
let l' = fromMaybe l $ ml
r' = fromMaybe r $ mr
return . Just . MyChoose $ Choose d l' r'
in case fromMessage sm of
Just (ModifyWindowBorderEnabled _) -> sendBoth
Just (ModifyScreenBorderEnabled _) -> sendBoth
_ -> do fmap MyChoose <$> handleMessage (Choose d l r) sm
103 changes: 103 additions & 0 deletions .config/xmonad/lib/Local/Overwrite/Layout.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,103 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

module Local.Overwrite.Layout ( Choose (..)
, LR (..)
, (|||)
, ChangeLayout (..)
) where

import XMonad hiding ( Choose
, (|||)
, ChangeLayout (..)
, hide
)
import qualified XMonad.StackSet as W

import Control.Arrow ( second
)
import Control.Monad
import Data.Maybe ( fromMaybe
)

------------------------------------------------------------------------
-- LayoutClass selection manager
-- Layouts that transition between other layouts

-- | Messages to change the current layout.
data ChangeLayout = FirstLayout | NextLayout deriving (Eq, Show, Typeable)

instance Message ChangeLayout

-- | The layout choice combinator
(|||) :: l a -> r a -> Choose l r a
(|||) = Choose L
infixr 5 |||

-- | A layout that allows users to switch between various layout options.
data Choose l r a = Choose LR (l a) (r a) deriving (Read, Show)

-- | Are we on the left or right sub-layout?
data LR = L | R deriving (Read, Show, Eq)

data NextNoWrap = NextNoWrap deriving (Eq, Show, Typeable)
instance Message NextNoWrap

-- | A small wrapper around handleMessage, as it is tedious to write
-- SomeMessage repeatedly.
handle :: (LayoutClass l a, Message m) => l a -> m -> X (Maybe (l a))
handle l m = handleMessage l (SomeMessage m)

-- | A smart constructor that takes some potential modifications, returns a
-- new structure if any fields have changed, and performs any necessary cleanup
-- on newly non-visible layouts.
choose :: (LayoutClass l a, LayoutClass r a)
=> Choose l r a-> LR -> Maybe (l a) -> Maybe (r a) -> X (Maybe (Choose l r a))
choose (Choose d _ _) d' Nothing Nothing | d == d' = return Nothing
choose (Choose d l r) d' ml mr = f lr
where
(l', r') = (fromMaybe l ml, fromMaybe r mr)
lr = case (d, d') of
(L, R) -> (hide l' , return r')
(R, L) -> (return l', hide r' )
(_, _) -> (return l', return r')
f (x,y) = fmap Just $ liftM2 (Choose d') x y
hide x = fmap (fromMaybe x) $ handle x Hide

instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
runLayout (W.Workspace i (Choose L l r) ms) =
fmap (second . fmap $ flip (Choose L) r) . runLayout (W.Workspace i l ms)
runLayout (W.Workspace i (Choose R l r) ms) =
fmap (second . fmap $ Choose R l) . runLayout (W.Workspace i r ms)

description (Choose L l _) = description l
description (Choose R _ r) = description r

handleMessage lr m | Just NextLayout <- fromMessage m = do
mlr' <- handle lr NextNoWrap
maybe (handle lr FirstLayout) (return . Just) mlr'

handleMessage c@(Choose d l r) m | Just NextNoWrap <- fromMessage m =
case d of
L -> do
ml <- handle l NextNoWrap
case ml of
Just _ -> choose c L ml Nothing
Nothing -> choose c R Nothing =<< handle r FirstLayout

R -> choose c R Nothing =<< handle r NextNoWrap

handleMessage c@(Choose _ l _) m | Just FirstLayout <- fromMessage m =
flip (choose c L) Nothing =<< handle l FirstLayout

handleMessage c@(Choose d l r) m | Just ReleaseResources <- fromMessage m =
join $ liftM2 (choose c d) (handle l ReleaseResources) (handle r ReleaseResources)

handleMessage c@(Choose d l r) m = do
ml' <- case d of
L -> handleMessage l m
R -> return Nothing
mr' <- case d of
L -> return Nothing
R -> handleMessage r m
choose c d ml' mr'

0 comments on commit 9f43542

Please sign in to comment.