mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21:51 -07:00
Refer to the tutorial instead of X.D.Extending more often
Essentially, whenever the tutorial actually has decent material on the subject matter. The replacement is roughly done as follows: - logHook → tutorial - keybindings → tutorial, as this is thoroughly covered - manageHook → tutorial + X.D.Extending, as the manageHook stuff the tutorial talks about is a little bit of an afterthought. - X.D.Extending (on its own) → tutorial + X.D.Extending - layoutHook → tutorial + X.D.Extending, as the tutorial, while talking about layouts, doesn't necessarily have a huge focus there. - mouse bindings → leave this alone, as the tutorial does not at all talk about them.
This commit is contained in:
@@ -34,9 +34,9 @@ import Data.Ratio
|
||||
-- > myLayout = Accordion ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Accordion a = Accordion deriving ( Read, Show )
|
||||
|
||||
|
@@ -44,8 +44,9 @@ import qualified Data.Set as S
|
||||
--
|
||||
-- > layoutHook = ... ||| avoidFloats Full ||| ...
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- Then add appropriate key bindings, for example:
|
||||
--
|
||||
@@ -54,7 +55,7 @@ import qualified Data.Set as S
|
||||
-- > ,((modm .|. shiftMask .|. controlMask, xK_b), sendMessage (AvoidFloatSet False) >> sendMessage AvoidFloatClearItems)
|
||||
--
|
||||
-- For detailed instructions on editing your key bindings, see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
--
|
||||
-- Note that this module is incompatible with an old way of configuring
|
||||
-- "XMonad.Actions.FloatSnap". If you are having problems, please update your
|
||||
|
@@ -60,9 +60,9 @@ import qualified XMonad.StackSet as W
|
||||
-- > , ((modm, xK_k), focusDown)
|
||||
-- > , ((modm, xK_m), focusMaster)
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
|
||||
data BoringMessage = FocusUp | FocusDown | FocusMaster | IsBoring Window | ClearBoring
|
||||
|
@@ -38,7 +38,9 @@ import XMonad.Prelude (fi)
|
||||
--
|
||||
-- > myLayoutHook = centeredIfSingle 0.7 0.8 Grid ||| ...
|
||||
--
|
||||
-- For more information on configuring your layouts see "XMonad.Doc.Extending".
|
||||
-- For more information on configuring your layouts see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>
|
||||
-- and "XMonad.Doc.Extending".
|
||||
|
||||
|
||||
-- | Layout Modifier that places a window in the center of the screen,
|
||||
|
@@ -35,9 +35,9 @@ import XMonad.StackSet (integrate, peek)
|
||||
-- > myLayout = Circle ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Circle a = Circle deriving ( Read, Show )
|
||||
|
||||
|
@@ -40,9 +40,9 @@ import qualified XMonad.StackSet as W ( differentiate )
|
||||
--
|
||||
-- to your layouts.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- combineTwo is a new simple layout combinator. It allows the
|
||||
-- combination of two layouts using a third to split the screen
|
||||
@@ -57,7 +57,7 @@ import qualified XMonad.StackSet as W ( differentiate )
|
||||
-- > , ((modm .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
--
|
||||
-- These bindings will move a window into the sublayout that is
|
||||
-- up\/down\/left\/right of its current position. Note that there is some
|
||||
|
@@ -44,9 +44,9 @@ import qualified XMonad.StackSet as W
|
||||
-- to your layouts. This way all windows with class = \"Firefox\" will always go
|
||||
-- to the left pane, all others - to the right.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- 'combineTwoP' is a simple layout combinator based on 'combineTwo' from Combo, with
|
||||
-- addition of a 'Property' which tells where to put new windows. Windows mathing
|
||||
@@ -64,7 +64,7 @@ import qualified XMonad.StackSet as W
|
||||
-- > , ((modm .|. controlMask .|. shiftMask, xK_s ), sendMessage $ SwapWindow)
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data SwapWindow = SwapWindow -- ^ Swap window between panes
|
||||
| SwapWindowN Int -- ^ Swap window between panes in the N-th nested ComboP. @SwapWindowN 0@ equals to SwapWindow
|
||||
|
@@ -108,9 +108,9 @@ import XMonad.Layout.SimpleFloat
|
||||
--
|
||||
-- > main = xmonad def { layoutHook = someMadLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You can also edit the default theme:
|
||||
--
|
||||
|
@@ -36,9 +36,9 @@ import XMonad.Prelude (ap)
|
||||
-- > myLayout = Dishes 2 (1/6) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Dishes a = Dishes Int Rational deriving (Show, Read)
|
||||
instance LayoutClass Dishes a where
|
||||
|
@@ -44,9 +44,9 @@ import XMonad.Util.XUtils
|
||||
-- > myLayout = dragPane Horizontal 0.1 0.5 ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
halfHandleWidth :: Integral a => a
|
||||
halfHandleWidth = 1
|
||||
|
@@ -68,9 +68,9 @@ import XMonad.Util.Types ( Direction2D(..) )
|
||||
-- 1.1, is the factor by which the third parameter increases or decreases in
|
||||
-- response to Expand or Shrink messages.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | Layouts with geometrically decreasing window sizes. 'Spiral' and 'Dwindle'
|
||||
-- split the screen into a rectangle for the first window and a rectangle for
|
||||
|
@@ -40,9 +40,9 @@ import XMonad.Layout.Decoration
|
||||
-- > myL = dwmStyle shrinkText def (layoutHook def)
|
||||
-- > main = xmonad def { layoutHook = myL }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
|
@@ -53,8 +53,8 @@ import XMonad.Layout.LayoutHints
|
||||
-- depending on the size hints (for example for programs like mpv),
|
||||
-- see "XMonad.Layout.LayoutHints"
|
||||
--
|
||||
-- See "XMonad.Doc.Extending#Editing_the_layout_hook" for more info on
|
||||
-- the 'layoutHook'.
|
||||
-- See <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook" for more info on the 'layoutHook'.
|
||||
--
|
||||
-- You also want to add keybindings to set and clear the aspect ratio:
|
||||
--
|
||||
@@ -73,7 +73,7 @@ import XMonad.Layout.LayoutHints
|
||||
--
|
||||
-- > , ((modMask .|. shiftMask, xK_c), withFocused (sendMessage . ResetRatio) >> kill)
|
||||
--
|
||||
-- See "XMonad.Doc.Extending#Editing_key_bindings" for more info
|
||||
-- See <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> for more info
|
||||
-- on customizing the keybindings.
|
||||
--
|
||||
-- This layout also comes with a 'ManageHook' 'doFixAspect' to
|
||||
@@ -84,7 +84,8 @@ import XMonad.Layout.LayoutHints
|
||||
-- > ...
|
||||
-- > ]
|
||||
--
|
||||
-- Check "XMonad.Doc.Extending#Editing_the_manage_hook" for more information on
|
||||
-- Check <https://xmonad.org/TUTORIAL.html#final-touches the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_manage_hook" for more information on
|
||||
-- customizing the manage hook.
|
||||
|
||||
-- | Similar to 'layoutHintsWithReplacement', but relies on the user to
|
||||
|
@@ -37,9 +37,9 @@ import qualified XMonad.StackSet as W
|
||||
-- > myLayout = FixedColumn 1 20 80 10 ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | A tiling mode based on preserving a nice fixed width
|
||||
-- window. Supports 'Shrink', 'Expand' and 'IncMasterN'.
|
||||
|
@@ -40,9 +40,9 @@ import XMonad.StackSet
|
||||
--
|
||||
-- > myLayout = GridRatio (4/3) ||| etc.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Grid a = Grid | GridRatio Double deriving (Read, Show)
|
||||
|
||||
|
@@ -84,8 +84,8 @@ import XMonad.Layout.Simplest
|
||||
-- the "XMonad.Layout.Groups.Helpers" module, which are all
|
||||
-- re-exported by this module.
|
||||
--
|
||||
-- For more information on how to extend your layour hook and key bindings, see
|
||||
-- "XMonad.Doc.Extending".
|
||||
-- For more information on how to extend your layoutHook and key bindings, see
|
||||
-- <https://xmonad.org/TUTORIAL.html the tutorial> and "XMonad.Doc.Extending".
|
||||
|
||||
|
||||
-- * Helper: ZoomRow of Group elements
|
||||
|
@@ -83,8 +83,8 @@ import qualified Data.Map as M
|
||||
--
|
||||
-- > import qualified XMonad.Layout.Groups as G
|
||||
--
|
||||
-- For more information on how to extend your layour hook and key bindings, see
|
||||
-- "XMonad.Doc.Extending".
|
||||
-- For more information on how to extend your layoutHook and key bindings, see
|
||||
-- <https://xmonad.org/TUTORIAL.html the tutorial> and "XMonad.Doc.Extending".
|
||||
|
||||
-- ** Layout-generic actions
|
||||
-- #Layout-generic actions#
|
||||
|
@@ -79,8 +79,8 @@ import XMonad.Layout.Simplest
|
||||
--
|
||||
-- and so on.
|
||||
--
|
||||
-- For more information on how to extend your layout hook and key bindings, see
|
||||
-- "XMonad.Doc.Extending".
|
||||
-- For more information on how to extend your layoutHook and key bindings, see
|
||||
-- <https://xmonad.org/TUTORIAL.html the tutorial> and "XMonad.Doc.Extending".
|
||||
--
|
||||
-- Finally, you will probably want to be able to move focus and windows
|
||||
-- between groups in a consistent fashion. For this, you should take a look
|
||||
|
@@ -46,9 +46,9 @@ import qualified XMonad.StackSet as W
|
||||
-- > myLayout = hiddenWindows (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- In the key bindings, do something like:
|
||||
--
|
||||
@@ -58,7 +58,7 @@ import qualified XMonad.StackSet as W
|
||||
--
|
||||
-- For detailed instruction on editing the key bindings see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
newtype HiddenWindows a = HiddenWindows [Window] deriving (Show, Read)
|
||||
|
@@ -51,6 +51,7 @@ infixr 9 .
|
||||
-- > myLayout = GridRatio (4/3) False ||| etc.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | Automatic mirroring of hinted layouts doesn't work very well, so this
|
||||
|
@@ -46,9 +46,9 @@ import XMonad.Prelude
|
||||
-- built-in Tall with HintedTile, change @import Xmonad@ to
|
||||
-- @import Xmonad hiding (Tall)@.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data HintedTile a = HintedTile
|
||||
{ nmaster :: !Int -- ^ number of windows in the master pane
|
||||
|
@@ -55,9 +55,9 @@ import Control.Arrow (first)
|
||||
--
|
||||
-- Screenshot: <http://haskell.org/haskellwiki/Image:Xmonad-layout-im.png>
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- $hints
|
||||
--
|
||||
|
@@ -103,9 +103,9 @@ import XMonad.Util.WindowProperties
|
||||
--
|
||||
-- These examples require "XMonad.Layout.Tabbed".
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You may wish to add the following keybindings:
|
||||
--
|
||||
@@ -114,7 +114,7 @@ import XMonad.Util.WindowProperties
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- $selectWin
|
||||
|
@@ -61,9 +61,9 @@ import XMonad.Layout.DragPane
|
||||
-- > myLayout = (Tall 1 (3/100) (1/2) *//* Full) ||| (Tall 1 (3/100) (1/2) ***||** Full) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the @layoutHook@ see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the @layoutHook@ see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
|
||||
-- $combine
|
||||
|
@@ -66,9 +66,9 @@ import qualified Data.Set as Set
|
||||
--
|
||||
-- > myLayout = layoutHintsToCenter (Tall 1 (3/100) (1/2))
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- To make XMonad reflect changes in window hints immediately, add
|
||||
-- 'hintsEventHook' to your 'handleEventHook'.
|
||||
|
@@ -57,7 +57,7 @@ import qualified XMonad.StackSet as W
|
||||
-- > , ((modm .|. controlMask .|. shiftMask, xK_space), rescreen)
|
||||
--
|
||||
-- For detailed instructions on editing your key bindings, see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
-- | Modify all screens.
|
||||
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
|
||||
|
@@ -56,7 +56,7 @@ import qualified XMonad.StackSet as W
|
||||
-- actions.
|
||||
--
|
||||
-- For detailed instructions on editing your key bindings, see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
--
|
||||
-- See also 'XMonad.Layout.BoringWindows.boringAuto' for keybindings that skip
|
||||
-- the hidden windows.
|
||||
|
@@ -45,9 +45,9 @@ import qualified Data.Map as M
|
||||
-- > main = xmonad def { layoutHook = myLayout,
|
||||
-- > handleEventHook = promoteWarp }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | Create a new layout which automagically puts the focused window
|
||||
-- in the master area.
|
||||
|
@@ -76,9 +76,9 @@ import XMonad.StackSet
|
||||
-- functions in this module are essentially just creative applications
|
||||
-- of it.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- Magnifier supports some commands, see 'MagnifyMsg'. To use them add
|
||||
-- something like this to your key bindings:
|
||||
@@ -101,7 +101,7 @@ import XMonad.StackSet
|
||||
-- like @Mag.Toggle@, @Mag.magnifier@, and so on.
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
-- | Add magnification capabilities to a certain layout.
|
||||
--
|
||||
|
@@ -52,6 +52,7 @@ import Control.Arrow (first)
|
||||
-- Grid manage the right half.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- Like 'XMonad.Layout.Tall', 'withMaster' supports the
|
||||
|
@@ -46,9 +46,9 @@ import XMonad.Prelude ( partition )
|
||||
-- > myLayout = maximizeWithPadding 10 (Tall 1 (3/100) (1/2)) ||| Full ||| etc..)
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- In the key-bindings, do something like:
|
||||
--
|
||||
@@ -57,7 +57,7 @@ import XMonad.Prelude ( partition )
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data Maximize a = Maximize Dimension (Maybe Window) deriving ( Read, Show )
|
||||
maximize :: LayoutClass l Window => l Window -> ModifiedLayout Maximize l Window
|
||||
|
@@ -39,9 +39,9 @@ import qualified XMonad.Util.ExtensibleState as XS
|
||||
-- > myLayout = minimize (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- The module is designed to work together with "XMonad.Layout.BoringWindows" so
|
||||
-- that minimized windows will be skipped over when switching the focused window with
|
||||
|
@@ -58,9 +58,9 @@ import Control.Arrow(second, first)
|
||||
--
|
||||
-- > , ((modm, xK_r), sendMessage Reset)
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Aspect
|
||||
= Taller
|
||||
|
@@ -48,9 +48,9 @@ import Data.Ratio
|
||||
-- > myLayout = MosaicAlt M.empty ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- In the key-bindings, do something like:
|
||||
--
|
||||
@@ -63,7 +63,7 @@ import Data.Ratio
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data HandleWindowAlt =
|
||||
ShrinkWindowAlt Window
|
||||
|
@@ -53,9 +53,9 @@ import Graphics.X11 as X
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You may also want to add the following key bindings:
|
||||
--
|
||||
@@ -64,7 +64,7 @@ import Graphics.X11 as X
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
-- $mrtParameters
|
||||
-- The following functions are also labels for updating the @data@ (whose
|
||||
|
@@ -56,9 +56,9 @@ import XMonad.Prelude
|
||||
-- columns, the screen is instead split equally among all columns. Therefore,
|
||||
-- if equal size among all columns are desired, set the size to -0.5.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | Layout constructor.
|
||||
multiCol
|
||||
|
@@ -53,9 +53,9 @@ import XMonad.Prelude (ap)
|
||||
-- > |_______|
|
||||
-- > |___|___|
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data MultiDishes a = MultiDishes Int Int Rational deriving (Show, Read)
|
||||
instance LayoutClass MultiDishes a where
|
||||
|
@@ -37,9 +37,9 @@ import XMonad.Layout.Renamed
|
||||
-- > myLayout = named "real big" Full ||| (nameTail $ named "real big" $ Full) ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- Note that this module has been deprecated and may be removed in a future
|
||||
-- release, please use "XMonad.Layout.Renamed" instead.
|
||||
|
@@ -54,9 +54,9 @@ import qualified Data.Map as M
|
||||
--
|
||||
-- > layoutHook = ... ||| noBorders Full ||| ...
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- todo, use an InvisibleList.
|
||||
data WithBorder a = WithBorder Dimension [a] deriving ( Read, Show )
|
||||
|
@@ -55,9 +55,9 @@ import Data.Ratio
|
||||
--
|
||||
-- The ResizableThreeColMid variant places the main window between the slave columns.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
|
||||
-- | Arguments are nmaster, delta, fraction
|
||||
|
@@ -36,9 +36,9 @@ import qualified Data.Map as M
|
||||
-- > myLayout = ResizableTall 1 (3/100) (1/2) [] ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You may also want to add the following key bindings:
|
||||
--
|
||||
@@ -47,7 +47,7 @@ import qualified Data.Map as M
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data MirrorResize = MirrorShrink | MirrorExpand
|
||||
instance Message MirrorResize
|
||||
|
@@ -39,9 +39,9 @@ import XMonad.Layout.Decoration
|
||||
--
|
||||
-- > layoutHook = resizeHorizontal 40 Full
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
resizeHorizontal :: Int -> l a -> ModifiedLayout ResizeScreen l a
|
||||
resizeHorizontal i = ModifiedLayout (ResizeScreen L i)
|
||||
|
@@ -36,9 +36,9 @@ import Data.Ratio
|
||||
-- > myLayout = Roledex ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- $screenshot
|
||||
-- <<http://www.timthelion.com/rolodex.png>>
|
||||
|
@@ -41,9 +41,9 @@ import XMonad.Util.XUtils
|
||||
-- > myLayout = layoutHook def
|
||||
-- > main = xmonad def { layoutHook = showWName myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | A layout modifier to show the workspace name when switching
|
||||
showWName :: l a -> ModifiedLayout ShowWName l a
|
||||
|
@@ -42,9 +42,9 @@ import XMonad.Layout.Decoration
|
||||
-- > myL = simpleDeco shrinkText def (layoutHook def)
|
||||
-- > main = xmonad def { layoutHook = myL }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
|
@@ -42,9 +42,9 @@ import XMonad.Layout.WindowArranger
|
||||
-- > myLayout = simpleFloat ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | A simple floating layout where every window is placed according
|
||||
-- to the window's initial attributes.
|
||||
|
@@ -33,9 +33,9 @@ import qualified XMonad.StackSet as S
|
||||
-- > myLayout = Simplest ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data Simplest a = Simplest deriving (Show, Read)
|
||||
instance LayoutClass Simplest a where
|
||||
|
@@ -37,9 +37,9 @@ import XMonad.Layout.LayoutModifier
|
||||
-- > myLayout = simplestFloat ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | A simple floating layout where every window is placed according
|
||||
-- to the window's initial attributes.
|
||||
|
@@ -42,9 +42,9 @@ import XMonad.Util.WindowProperties
|
||||
-- > myLayout = sorted [ClassName "Firefox", ClassName "URxvt"] Grid
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
|
||||
-- | Modify a layout using a list of properties to sort its windows.
|
||||
|
@@ -40,9 +40,9 @@ import XMonad.StackSet ( integrate )
|
||||
-- > myLayout = spiral (6/7) ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
fibs :: [Integer]
|
||||
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
|
||||
|
@@ -41,7 +41,7 @@ import XMonad.StackSet ( integrate )
|
||||
-- > [(tabbed,3),(tabbed,30),(tabbed,1),(tabbed,1)]
|
||||
|
||||
-- For detailed instructions on editing your key bindings, see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data Square a = Square deriving ( Read, Show )
|
||||
|
||||
|
@@ -36,9 +36,9 @@ import XMonad.Prelude
|
||||
-- > myLayout = StackTile 1 (3/100) (1/2) ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
data StackTile a = StackTile !Int !Rational !Rational deriving (Show, Read)
|
||||
|
||||
|
@@ -75,9 +75,9 @@ import System.Posix.Signals
|
||||
-- layoutHook you have to provide manageHook from
|
||||
-- "XMonad.Util.RemoteWindows" module.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
signalWindow :: Signal -> Window -> X ()
|
||||
signalWindow s w = do
|
||||
|
@@ -163,10 +163,9 @@ import qualified Data.Set as S
|
||||
-- could not be used in the keybinding instead? It avoids having to explicitly
|
||||
-- pass the conf.
|
||||
--
|
||||
-- For more detailed instructions, see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- "XMonad.Doc.Extending#Adding_key_bindings"
|
||||
-- For more detailed instructions, see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>
|
||||
-- and "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
-- | The main layout modifier arguments:
|
||||
--
|
||||
|
@@ -39,9 +39,9 @@ import XMonad.Prompt ( XPPosition (..) )
|
||||
--
|
||||
-- > main = xmonad def { layoutHook = simpleTabBar $ layoutHook def}
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- 'tabBar' will give you the possibility of setting a custom shrinker
|
||||
-- and a custom theme.
|
||||
|
@@ -67,9 +67,9 @@ import XMonad.Util.Types (Direction2D(..))
|
||||
-- on the workspace. To have it always shown, use one of the layouts or
|
||||
-- modifiers ending in @Always@.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You can also edit the default configuration options.
|
||||
--
|
||||
|
@@ -51,9 +51,9 @@ import Data.Ratio
|
||||
--
|
||||
-- The ThreeColMid variant places the main window between the stack columns.
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
|
||||
-- $screenshot
|
||||
|
@@ -34,9 +34,9 @@ import XMonad.StackSet (Workspace (..))
|
||||
-- > myLayout = toggleLayouts Full (Tall 1 (3/100) (1/2)) ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- To toggle between layouts add a key binding like
|
||||
--
|
||||
@@ -48,7 +48,7 @@ import XMonad.StackSet (Workspace (..))
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
data ToggleLayouts lt lf a = ToggleLayouts Bool (lt a) (lf a) deriving (Read,Show)
|
||||
data ToggleLayout = ToggleLayout | Toggle String deriving (Read,Show)
|
||||
|
@@ -36,9 +36,9 @@ import XMonad.StackSet ( focus, up, down)
|
||||
-- > myLayout = TwoPane (3/100) (1/2) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data TwoPane a =
|
||||
TwoPane Rational Rational
|
||||
|
@@ -46,9 +46,9 @@ import XMonad.StackSet (integrate)
|
||||
--
|
||||
-- > layoutHook = ... ||| voidBorders Full ||| normalBorders Tall ...
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
|
||||
data VoidBorders a = VoidBorders deriving (Read, Show)
|
||||
|
||||
|
@@ -45,9 +45,9 @@ import Control.Arrow ((***), (>>>), (&&&), first)
|
||||
--
|
||||
-- > main = xmonad def { layoutHook = windowArrangeAll myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- You may also want to define some key binding to move or resize
|
||||
-- windows. These are good defaults:
|
||||
@@ -68,7 +68,7 @@ import Control.Arrow ((***), (>>>), (&&&), first)
|
||||
-- > , ((modm .|. controlMask .|. shiftMask, xK_Up ), sendMessage (DecreaseUp 1))
|
||||
--
|
||||
-- For detailed instructions on editing your key bindings, see
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
-- | A layout modifier to float the windows in a workspace
|
||||
windowArrange :: l a -> ModifiedLayout WindowArranger l a
|
||||
|
@@ -45,9 +45,9 @@ import XMonad.Util.XUtils
|
||||
-- > myLayout = windowNavigation (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the 'layoutHook' see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the 'layoutHook' see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- In keybindings:
|
||||
--
|
||||
@@ -62,7 +62,7 @@ import XMonad.Util.XUtils
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
|
||||
data MoveWindowToWindow a = MoveWindowToWindow a a deriving ( Read, Show)
|
||||
@@ -75,10 +75,10 @@ instance Message Navigate
|
||||
-- | Used with 'configurableNavigation' to specify how to show reachable windows'
|
||||
-- borders. You cannot create 'WNConfig' values directly; use 'def' or one of the following
|
||||
-- three functions to create one.
|
||||
--
|
||||
--
|
||||
-- 'def', and 'windowNavigation', uses the focused border color at 40% brightness, as if
|
||||
-- you had specified
|
||||
--
|
||||
--
|
||||
-- > configurableNavigation (navigateBrightness 0.4)
|
||||
data WNConfig =
|
||||
WNC { brightness :: Maybe Double -- Indicates a fraction of the focus color.
|
||||
|
@@ -51,9 +51,9 @@ import XMonad.StackSet ( tag, currentTag )
|
||||
-- > myLayout = workspaceDir "~" (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
|
||||
-- > main = xmonad def { layoutHook = myLayout }
|
||||
--
|
||||
-- For more detailed instructions on editing the layoutHook see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
-- For more detailed instructions on editing the layoutHook see
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
|
||||
--
|
||||
-- WorkspaceDir provides also a prompt. To use it you need to import
|
||||
-- "XMonad.Prompt" and add something like this to your key bindings:
|
||||
@@ -67,7 +67,7 @@ import XMonad.StackSet ( tag, currentTag )
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
|
||||
|
||||
newtype Chdir = Chdir String
|
||||
instance Message Chdir
|
||||
|
@@ -69,8 +69,9 @@ import Control.Arrow (second)
|
||||
-- > -- (Un)Maximize the focused window
|
||||
-- > , ((modMask , xK_f ), sendMessage ToggleZoomFull)
|
||||
--
|
||||
-- For more information on editing your layout hook and key bindings,
|
||||
-- see "XMonad.Doc.Extending".
|
||||
-- For more information on editing your layoutHook and key bindings,
|
||||
-- see <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>
|
||||
-- and "XMonad.Doc.Extending".
|
||||
|
||||
-- * Creation functions
|
||||
|
||||
|
Reference in New Issue
Block a user