center single window with layout 3
This commit is contained in:
parent
0d46fe9c68
commit
45a0d52120
2
xmonad
2
xmonad
|
@ -1 +1 @@
|
|||
Subproject commit eb2ee340e4180d1f7741605d846b154e777b509b
|
||||
Subproject commit e25d090112f2a76364a10b88a729b8586c18145b
|
|
@ -1 +1 @@
|
|||
Subproject commit 28aa164abd853a237e409d0fbb9f3819f253cf56
|
||||
Subproject commit 061faf17485cbeeb9372e68394572ba4d58ab53e
|
33
xmonad.hs
33
xmonad.hs
|
@ -1,3 +1,8 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
|
||||
import Control.Arrow (second)
|
||||
import Control.Monad (liftM2)
|
||||
import Data.List (isInfixOf)
|
||||
import qualified Data.Monoid
|
||||
|
@ -8,6 +13,7 @@ import XMonad
|
|||
Full (Full),
|
||||
Mirror (Mirror),
|
||||
Query,
|
||||
Rectangle (Rectangle),
|
||||
Tall (Tall),
|
||||
WindowSet,
|
||||
WindowSpace,
|
||||
|
@ -72,6 +78,7 @@ import XMonad.Hooks.EwmhDesktops
|
|||
import XMonad.Hooks.InsertPosition (Focus (Newer), Position (End), insertPosition)
|
||||
import XMonad.Hooks.ManageHelpers (doRectFloat)
|
||||
import XMonad.Hooks.Place (placeHook, simpleSmart)
|
||||
import XMonad.Hooks.SetWMName (setWMName)
|
||||
import XMonad.Hooks.StatusBar
|
||||
( defToggleStrutsKey,
|
||||
statusBarProp,
|
||||
|
@ -79,9 +86,11 @@ import XMonad.Hooks.StatusBar
|
|||
)
|
||||
import XMonad.Layout (Resize (Expand, Shrink))
|
||||
import XMonad.Layout.Fullscreen (fullscreenEventHook)
|
||||
import XMonad.Layout.LayoutModifier
|
||||
import qualified XMonad.Layout.LayoutModifier
|
||||
import XMonad.Layout.Named (named)
|
||||
import XMonad.Layout.NoBorders
|
||||
import XMonad.Layout.ResizableTile (MirrorResize (MirrorExpand), ResizableTall (ResizableTall))
|
||||
import XMonad.Layout.Spacing
|
||||
( Border (Border),
|
||||
Spacing,
|
||||
|
@ -92,13 +101,13 @@ import XMonad.Layout.WindowNavigation
|
|||
Navigate (Go),
|
||||
windowNavigation,
|
||||
)
|
||||
import XMonad.StackSet (RationalRect (RationalRect), Workspace (tag), currentTag, greedyView, integrate', shift, stack)
|
||||
import XMonad.StackSet (RationalRect (RationalRect), Stack (Stack), Workspace (tag), currentTag, greedyView, integrate', shift, stack)
|
||||
import XMonad.Util.EZConfig (additionalKeysP)
|
||||
import XMonad.Util.Loggers (logTitles)
|
||||
import XMonad.Util.Font (fi)
|
||||
import XMonad.Util.Loggers (logTitles, wrapL)
|
||||
import XMonad.Util.SpawnOnce (spawnOnce)
|
||||
import XMonad.Util.Ungrab (unGrab)
|
||||
import XMonad.Util.WorkspaceCompare (getSortByIndex)
|
||||
import XMonad.Hooks.SetWMName (setWMName)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
@ -123,7 +132,7 @@ main = do
|
|||
("M-f", runOrRaise "brave" (className =? "Brave-browser")),
|
||||
("M-i", raise (className =? "jetbrains-idea")),
|
||||
("M-<Space>", spawn "rofi -show drun"),
|
||||
("M-p", spawn "dmen"),
|
||||
("M-p", spawn "dmenu-with-suggestions"),
|
||||
-- audio settings
|
||||
("<XF86AudioLowerVolume>", spawn "amixer set Master 5%- unmute"),
|
||||
("<XF86AudioRaiseVolume>", spawn "amixer set Master 5%+ unmute"),
|
||||
|
@ -184,7 +193,6 @@ myXmobarPP colors =
|
|||
|
||||
myStartupHook :: X ()
|
||||
myStartupHook = do
|
||||
setWMName "LG3D"
|
||||
spawnOnce "picom &"
|
||||
spawnOnce "sh $HOME/.fehbg"
|
||||
spawnOnce "setxkbmap -option caps:escape"
|
||||
|
@ -203,7 +211,7 @@ mySpacing' i = spacingRaw True (Border i 0 i i) True (Border i 0 i i) True
|
|||
myWorkspaces :: [String]
|
||||
myWorkspaces = show <$> ([1 .. 9] :: [Integer])
|
||||
|
||||
myLayout = smartBorders $ windowNavigation tiled ||| smartBorders Full ||| Mirror tiled
|
||||
myLayout = smartBorders $ windowNavigation tiled ||| smartBorders Full ||| Mirror (fullWSpacing 8 $ Tall nmaster delta ratio)
|
||||
where
|
||||
tiled = named "Tall" $ mySpacing' 8 $ Tall nmaster delta ratio
|
||||
nmaster = 1 -- Default number of windows in the master pane
|
||||
|
@ -248,3 +256,16 @@ myManageHook =
|
|||
-- IntelliJ fix
|
||||
(~=?) :: Eq a => Query [a] -> [a] -> Query Bool
|
||||
q ~=? x = fmap (isInfixOf x) q
|
||||
|
||||
fullWSpacing :: Int -> l a -> ModifiedLayout FullWSpacing l a
|
||||
fullWSpacing p = ModifiedLayout (FullWSpacing p)
|
||||
|
||||
data FullWSpacing a = FullWSpacing Int deriving (Show, Read)
|
||||
|
||||
instance LayoutModifier FullWSpacing a where
|
||||
pureModifier (FullWSpacing _) _ (Just (Stack f _ _)) [(param, rect)] = ([(param, shrinkRect 250 rect)], Nothing)
|
||||
pureModifier (FullWSpacing p) _ _ wrs = (map (second $ shrinkRect p) wrs, Nothing)
|
||||
modifierDescription (FullWSpacing p) = "Tall center"
|
||||
|
||||
shrinkRect :: Int -> Rectangle -> Rectangle
|
||||
shrinkRect p (Rectangle x y w h) = Rectangle (x + fi (p `div` 2)) (y + fi p) (fi $ max 1 $ fi w -2 * (p `div` 2)) (fi $ max 1 $ fi h -2 * p)
|
||||
|
|
Loading…
Reference in New Issue