diff --git a/CHANGES.md b/CHANGES.md index 47193cc0..675e80f8 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -104,6 +104,15 @@ argument. This fixes the interplay between this module and any layout that stores state. + * `XMonad.Layout.LayoutCombinators` + + - Moved the alternative `(|||)` function and `JumpToLayout` to the + xmonad core. They are re-exported by the module, but do not add any + new functionality. `NewSelect` now exists as a deprecated type + alias to `Choose`. + + - Removed the `Wrap` and `NextLayoutNoWrap` data constructors. + ### New Modules * `XMonad.Hooks.StatusBar.PP` diff --git a/XMonad/Actions/BluetileCommands.hs b/XMonad/Actions/BluetileCommands.hs index b410015f..0a2768a3 100644 --- a/XMonad/Actions/BluetileCommands.hs +++ b/XMonad/Actions/BluetileCommands.hs @@ -24,7 +24,6 @@ module XMonad.Actions.BluetileCommands ( import XMonad import qualified XMonad.StackSet as W -import XMonad.Layout.LayoutCombinators import System.Exit -- $usage diff --git a/XMonad/Actions/CycleSelectedLayouts.hs b/XMonad/Actions/CycleSelectedLayouts.hs index cea44c29..c3bf5e67 100644 --- a/XMonad/Actions/CycleSelectedLayouts.hs +++ b/XMonad/Actions/CycleSelectedLayouts.hs @@ -19,20 +19,15 @@ module XMonad.Actions.CycleSelectedLayouts ( import XMonad import XMonad.Prelude (findIndex, fromMaybe) -import XMonad.Layout.LayoutCombinators (JumpToLayout(..)) import qualified XMonad.StackSet as S -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- --- > import XMonad hiding ((|||)) --- > import XMonad.Layout.LayoutCombinators ((|||)) +-- > import XMonad -- > import XMonad.Actions.CycleSelectedLayouts -- -- > , ((modm, xK_t ), cycleThroughLayouts ["Tall", "Mirror Tall"]) --- --- Make sure you are using NewSelect from XMonad.Layout.LayoutCombinators, --- rather than the Select defined in xmonad core. cycleToNext :: (Eq a) => [a] -> a -> Maybe a cycleToNext lst a = do diff --git a/XMonad/Config/Arossato.hs b/XMonad/Config/Arossato.hs index 301b318e..acf8e6ed 100644 --- a/XMonad/Config/Arossato.hs +++ b/XMonad/Config/Arossato.hs @@ -22,7 +22,7 @@ module XMonad.Config.Arossato import qualified Data.Map as M -import XMonad hiding ( (|||) ) +import XMonad import qualified XMonad.StackSet as W import XMonad.Actions.CycleWS @@ -30,7 +30,6 @@ import XMonad.Hooks.DynamicLog hiding (xmobar) import XMonad.Hooks.ManageDocks import XMonad.Hooks.ServerMode import XMonad.Layout.Accordion -import XMonad.Layout.LayoutCombinators import XMonad.Layout.Magnifier import XMonad.Layout.NoBorders import XMonad.Layout.SimpleFloat diff --git a/XMonad/Config/Bluetile.hs b/XMonad/Config/Bluetile.hs index 8e94ab1b..cb166bd8 100644 --- a/XMonad/Config/Bluetile.hs +++ b/XMonad/Config/Bluetile.hs @@ -25,7 +25,7 @@ module XMonad.Config.Bluetile ( bluetileConfig ) where -import XMonad hiding ( (|||) ) +import XMonad import XMonad.Layout.BorderResize import XMonad.Layout.BoringWindows @@ -33,7 +33,6 @@ import XMonad.Layout.ButtonDecoration import XMonad.Layout.Decoration import XMonad.Layout.DecorationAddons import XMonad.Layout.DraggingVisualizer -import XMonad.Layout.LayoutCombinators import XMonad.Layout.Maximize import XMonad.Layout.Minimize import XMonad.Layout.MouseResizableTile diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs index 31f560ce..87bd8d4d 100644 --- a/XMonad/Config/Droundy.hs +++ b/XMonad/Config/Droundy.hs @@ -9,7 +9,7 @@ module XMonad.Config.Droundy ( config, mytab ) where -import XMonad hiding (keys, config, (|||)) +import XMonad hiding (keys, config) import qualified XMonad (keys) import qualified XMonad.StackSet as W diff --git a/XMonad/Layout/Groups/Examples.hs b/XMonad/Layout/Groups/Examples.hs index 1b62c0ff..da527e50 100644 --- a/XMonad/Layout/Groups/Examples.hs +++ b/XMonad/Layout/Groups/Examples.hs @@ -51,7 +51,7 @@ module XMonad.Layout.Groups.Examples ( -- * Usage , zoomRowG ) where -import XMonad hiding ((|||)) +import XMonad import qualified XMonad.Layout.Groups as G import XMonad.Layout.Groups.Helpers @@ -60,7 +60,6 @@ import XMonad.Layout.ZoomRow import XMonad.Layout.Tabbed import XMonad.Layout.Named import XMonad.Layout.Renamed -import XMonad.Layout.LayoutCombinators import XMonad.Layout.Decoration import XMonad.Layout.Simplest @@ -236,4 +235,3 @@ expandMasterGroups = sendMessage $ G.ToEnclosing $ SomeMessage $ Expand -- | Rotate the available outer layout algorithms nextOuterLayout :: X () nextOuterLayout = sendMessage $ G.ToEnclosing $ SomeMessage $ NextLayout - diff --git a/XMonad/Layout/Groups/Wmii.hs b/XMonad/Layout/Groups/Wmii.hs index 4c709e61..acbe39f2 100644 --- a/XMonad/Layout/Groups/Wmii.hs +++ b/XMonad/Layout/Groups/Wmii.hs @@ -33,7 +33,7 @@ module XMonad.Layout.Groups.Wmii ( -- * Usage , def , module XMonad.Layout.Groups.Helpers ) where -import XMonad hiding ((|||)) +import XMonad import qualified XMonad.Layout.Groups as G import XMonad.Layout.Groups.Examples @@ -42,7 +42,6 @@ import XMonad.Layout.Groups.Helpers import XMonad.Layout.Tabbed import XMonad.Layout.Named import XMonad.Layout.Renamed -import XMonad.Layout.LayoutCombinators import XMonad.Layout.MessageControl import XMonad.Layout.Simplest @@ -130,4 +129,3 @@ groupToTabbedLayout = sendMessage $ escape $ JumpToLayout "Tabs" -- | Switch the focused group to the \"column\" layout. groupToVerticalLayout :: X () groupToVerticalLayout = sendMessage $ escape $ JumpToLayout "Column" - diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs index 94060a2b..e70eca63 100644 --- a/XMonad/Layout/LayoutCombinators.hs +++ b/XMonad/Layout/LayoutCombinators.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Layout.LayoutCombinators @@ -10,10 +9,7 @@ -- Portability : portable -- -- The "XMonad.Layout.LayoutCombinators" module provides combinators --- for easily combining multiple layouts into one composite layout, as --- well as a way to jump directly to any particular layout (say, with --- a keybinding) without having to cycle through other layouts to get --- to it. +-- for easily combining multiple layouts into one composite layout. ----------------------------------------------------------------------------- module XMonad.Layout.LayoutCombinators @@ -43,26 +39,20 @@ module XMonad.Layout.LayoutCombinators , (*/*), (**/*),(***/*),(****/*),(***/**),(****/***) , (***/****),(*/****),(**/***),(*/***),(*/**) - -- * New layout choice combinator and 'JumpToLayout' - -- $jtl + -- * Re-exports for backwards compatibility , (|||) , JumpToLayout(..) - - -- * Types , NewSelect ) where -import XMonad.Prelude ( isJust, isNothing ) - -import XMonad hiding ((|||)) -import XMonad.StackSet (Workspace (..)) +import XMonad import XMonad.Layout.Combo import XMonad.Layout.DragPane -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- --- > import XMonad.Layout.LayoutCombinators hiding ( (|||) ) +-- > import XMonad.Layout.LayoutCombinators -- -- Then edit your @layoutHook@ to use the new layout combinators. For -- example: @@ -74,17 +64,6 @@ import XMonad.Layout.DragPane -- -- "XMonad.Doc.Extending#Editing_the_layout_hook" -- --- To use the 'JumpToLayout' message, hide the normal @|||@ operator instead: --- --- > import XMonad hiding ( (|||) ) --- > import XMonad.Layout.LayoutCombinators --- --- If you import XMonad.Layout, you will need to hide it from there as well. --- Then bind some keys to a 'JumpToLayout' message: --- --- > , ((modm .|. controlMask, xK_f), sendMessage $ JumpToLayout "Full") -- jump directly to the Full layout --- --- See below for more detailed documentation. -- $combine -- Each of the following combinators combines two layouts into a @@ -177,114 +156,5 @@ infixr 6 *||*, **||*, ***||*, ****||*, ***||**, ****||***, ***||****, *||****, * (*/***) = combineTwo (Mirror $ Tall 1 0.1 (1/4)) (*/**) = combineTwo (Mirror $ Tall 1 0.1 (1/3)) -infixr 5 ||| - --- $jtl --- The standard xmonad core exports a layout combinator @|||@ which --- represents layout choice. This is a reimplementation which also --- provides the capability to support 'JumpToLayout' messages. To use --- it, be sure to hide the import of @|||@ from the xmonad core; if either of --- these two lines appear in your configuration: --- --- > import XMonad --- > import XMonad.Layout --- --- replace them with these instead, respectively: --- --- > import XMonad hiding ( (|||) ) --- > import XMonad.Layout hiding ( (|||) ) --- --- The argument given to a 'JumpToLayout' message should be the --- @description@ of the layout to be selected. If you use --- "XMonad.Hooks.DynamicLog", this is the name of the layout displayed --- in your status bar. Alternatively, you can use GHCi to determine --- the proper name to use. For example: --- --- > $ ghci --- > GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help --- > Loading package base ... linking ... done. --- > :set prompt "> " -- don't show loaded module names --- > > :m +XMonad.Core -- load the xmonad core --- > > :m +XMonad.Layout.Grid -- load whatever module you want to use --- > > description Grid -- find out what it's called --- > "Grid" --- --- As yet another (possibly easier) alternative, you can use the --- "XMonad.Layout.Named" modifier to give custom names to your --- layouts, and use those. --- --- For the ability to select a layout from a prompt, see --- "XMonad.Prompt.Layout". - --- | A reimplementation of the combinator of the same name from the --- xmonad core, providing layout choice, and the ability to support --- 'JumpToLayout' messages. -(|||) :: (LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> NewSelect l1 l2 a -(|||) = NewSelect True - -data NewSelect l1 l2 a = NewSelect Bool (l1 a) (l2 a) deriving ( Read, Show ) - --- | -data JumpToLayout = JumpToLayout String -- ^ A message to jump to a particular layout - -- , specified by its description string.. - | NextLayoutNoWrap - | Wrap - deriving ( Read, Show, Typeable ) -instance Message JumpToLayout - -instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (NewSelect l1 l2) a where - runLayout (Workspace i (NewSelect True l1 l2) ms) r = do (wrs, ml1') <- runLayout (Workspace i l1 ms) r - return (wrs, (\l1' -> NewSelect True l1' l2) <$> ml1') - - runLayout (Workspace i (NewSelect False l1 l2) ms) r = do (wrs, ml2') <- runLayout (Workspace i l2 ms) r - return (wrs, (\l2' -> NewSelect False l1 l2') <$> ml2') - description (NewSelect True l1 _) = description l1 - description (NewSelect False _ l2) = description l2 - handleMessage l@(NewSelect False _ _) m - | Just Wrap <- fromMessage m = Just <$> (swap l >>= passOn m) - handleMessage l@(NewSelect amfirst _ _) m - | Just NextLayoutNoWrap <- fromMessage m = - if amfirst then when' isNothing (passOnM m l) $ - Just <$> (swap l >>= passOn (SomeMessage Wrap)) - else passOnM m l - handleMessage l m - | Just NextLayout <- fromMessage m = when' isNothing (passOnM (SomeMessage NextLayoutNoWrap) l) $ - Just <$> (swap l >>= passOn (SomeMessage Wrap)) - handleMessage l@(NewSelect True _ l2) m - | Just (JumpToLayout d) <- fromMessage m, d == description l2 = Just <$> swap l - handleMessage l@(NewSelect False l1 _) m - | Just (JumpToLayout d) <- fromMessage m, d == description l1 = Just <$> swap l - handleMessage l m - | Just (JumpToLayout _) <- fromMessage m = when' isNothing (passOnM m l) $ - do ml' <- passOnM m $ sw l - case ml' of - Nothing -> return Nothing - Just l' -> Just <$> swap (sw l') - handleMessage (NewSelect b l1 l2) m - | Just ReleaseResources <- fromMessage m = - do ml1' <- handleMessage l1 m - ml2' <- handleMessage l2 m - return $ if isJust ml1' || isJust ml2' - then Just $ NewSelect b (maybe l1 id ml1') (maybe l2 id ml2') - else Nothing - handleMessage l m = passOnM m l - -swap :: (LayoutClass l1 a, LayoutClass l2 a) => NewSelect l1 l2 a -> X (NewSelect l1 l2 a) -swap l = sw <$> passOn (SomeMessage Hide) l - -sw :: NewSelect l1 l2 a -> NewSelect l1 l2 a -sw (NewSelect b lt lf) = NewSelect (not b) lt lf - -passOn :: (LayoutClass l1 a, LayoutClass l2 a) => - SomeMessage -> NewSelect l1 l2 a -> X (NewSelect l1 l2 a) -passOn m l = maybe l id <$> passOnM m l - -passOnM :: (LayoutClass l1 a, LayoutClass l2 a) => - SomeMessage -> NewSelect l1 l2 a -> X (Maybe (NewSelect l1 l2 a)) -passOnM m (NewSelect True lt lf) = do mlt' <- handleMessage lt m - return $ (\lt' -> NewSelect True lt' lf) <$> mlt' -passOnM m (NewSelect False lt lf) = do mlf' <- handleMessage lf m - return $ (\lf' -> NewSelect False lt lf') <$> mlf' - -when' :: Monad m => (a -> Bool) -> m a -> m a -> m a -when' f a b = do a1 <- a; if f a1 then b else return a1 +type NewSelect = Choose +{-# DEPRECATED NewSelect "Use 'Choose' instead." #-} diff --git a/XMonad/Layout/MessageControl.hs b/XMonad/Layout/MessageControl.hs index e32fc88b..e5f1b06e 100644 --- a/XMonad/Layout/MessageControl.hs +++ b/XMonad/Layout/MessageControl.hs @@ -45,7 +45,6 @@ import Control.Arrow (second) -- -- > import XMonad.Layout.Master (mastered) -- > import XMonad.Layout.Tabbed (simpleTabbed) --- > import XMonad.Layout.LayoutCombinators ((|||)) -- > -- > myLayout = Tall ||| unEscape (mastered 0.01 0.5 $ Full ||| simpleTabbed) -- @@ -62,9 +61,6 @@ import Control.Arrow (second) -- > unEscape $ mastered 0.01 0.5 -- > $ Full ||| simpleTabbed) -- --- /IMPORTANT NOTE:/ The standard '(|||)' operator from "XMonad.Layout" --- does not behave correctly with 'ignore'. Make sure you use the one --- from "XMonad.Layout.LayoutCombinators". -- | the Ignore layout modifier. Prevents its inner layout from receiving -- messages of a certain type. diff --git a/XMonad/Prompt/Layout.hs b/XMonad/Prompt/Layout.hs index f419830a..b575e490 100644 --- a/XMonad/Prompt/Layout.hs +++ b/XMonad/Prompt/Layout.hs @@ -23,7 +23,6 @@ import XMonad hiding ( workspaces ) import XMonad.Prompt import XMonad.Prompt.Workspace ( Wor(..) ) import XMonad.StackSet ( workspaces, layout ) -import XMonad.Layout.LayoutCombinators ( JumpToLayout(..) ) -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: