MultiToggle: add new XMonad.Layout.MultiToggle.Instances module for common instances of Transformer, update MultiToggle docs accordingly

This commit is contained in:
Brent Yorgey 2008-03-31 20:17:39 +00:00
parent f77f71512b
commit 110c3863e8
3 changed files with 67 additions and 25 deletions

View File

@ -15,7 +15,6 @@
-- currently focused window occupy the whole screen (\"zoom in\") then undo -- currently focused window occupy the whole screen (\"zoom in\") then undo
-- the transformation (\"zoom out\"). -- the transformation (\"zoom out\").
module XMonad.Layout.MultiToggle ( module XMonad.Layout.MultiToggle (
-- * Usage -- * Usage
-- $usage -- $usage
@ -24,7 +23,8 @@ module XMonad.Layout.MultiToggle (
(??), (??),
EOT(..), EOT(..),
single, single,
mkToggle mkToggle,
mkToggle1
) where ) where
import XMonad import XMonad
@ -46,18 +46,10 @@ import Data.Maybe
-- undo the current layout transformer, pass the message on to the base -- undo the current layout transformer, pass the message on to the base
-- layout, then reapply the transformer. -- layout, then reapply the transformer.
-- --
-- To use this module, you first have to define the transformers that you -- To use this module, you need some data types which represent
-- want to be handled by @MultiToggle@. For example, if the transformer is -- transformers; for some commonly used transformers (including
-- 'XMonad.Layout.Mirror': -- MIRROR, NOBORDERS, and FULL used in the examples below) you can
-- -- simply import "XMonad.Layout.MultiToggle.Instances".
-- > data MIRROR = MIRROR deriving (Read, Show, Eq, Typeable)
-- > instance Transformer MIRROR Window where
-- > transform _ x k = k (Mirror x)
--
-- @MIRROR@ can be any identifier (it has to start with an uppercase letter,
-- of course); I've chosen an all-uppercase version of the transforming
-- function's name here. You need to put @{-\# OPTIONS_GHC -fglasgow-exts \#-}@
-- at the beginning of your file to be able to derive "Data.Typeable".
-- --
-- Somewhere else in your file you probably have a definition of @layout@; -- Somewhere else in your file you probably have a definition of @layout@;
-- the default looks like this: -- the default looks like this:
@ -77,17 +69,7 @@ import Data.Maybe
-- (That should be part of your key bindings.) When you press @mod-x@, the -- (That should be part of your key bindings.) When you press @mod-x@, the
-- active layout is mirrored. Another @mod-x@ and it's back to normal. -- active layout is mirrored. Another @mod-x@ and it's back to normal.
-- --
-- It's also possible to stack @MultiToggle@s. Let's define a few more -- It's also possible to stack @MultiToggle@s. For example:
-- transformers ('XMonad.Layout.NoBorders.noBorders' is in
-- "XMonad.Layout.NoBorders"):
--
-- > data NOBORDERS = NOBORDERS deriving (Read, Show, Eq, Typeable)
-- > instance Transformer NOBORDERS Window where
-- > transform _ x k = k (noBorders x)
-- >
-- > data FULL = FULL deriving (Read, Show, Eq, Typeable)
-- > instance Transformer FULL Window where
-- > transform _ x k = k Full
-- --
-- @ -- @
-- layout = id -- layout = id
@ -100,6 +82,20 @@ import Data.Maybe
-- By binding a key to @(sendMessage $ Toggle FULL)@ you can temporarily -- By binding a key to @(sendMessage $ Toggle FULL)@ you can temporarily
-- maximize windows, in addition to being able to rotate layouts and remove -- maximize windows, in addition to being able to rotate layouts and remove
-- window borders. -- window borders.
--
-- You can also define your own transformers by creating a data type
-- which is an instance of the 'Transformer' class. For example, here
-- is the definition of @MIRROR@:
--
-- > data MIRROR = MIRROR deriving (Read, Show, Eq, Typeable)
-- > instance Transformer MIRROR Window where
-- > transform _ x k = k (Mirror x)
--
-- Note, you need to put @{-\# LANGUAGE DeriveDataTypeable \#-}@ at the
-- beginning of your file (ghc 6.8 only; with ghc 6.6 you can use
-- @{-\# OPTIONS_GHC -fglasgow-exts \#-}@ instead) to be able to
-- derive "Data.Typeable".
--
-- | A class to identify custom transformers (and look up transforming -- | A class to identify custom transformers (and look up transforming
-- functions by type). -- functions by type).
@ -157,6 +153,11 @@ instance (Show ts, Show (l a)) => Show (MultiToggle ts l a) where
mkToggle :: (LayoutClass l a) => ts -> l a -> MultiToggle ts l a mkToggle :: (LayoutClass l a) => ts -> l a -> MultiToggle ts l a
mkToggle ts l = MultiToggle l (EL l) Nothing id ts mkToggle ts l = MultiToggle l (EL l) Nothing id ts
-- | Construct a @MultiToggle@ layout from a single transformer and a base
-- layout.
mkToggle1 :: (LayoutClass l a) => t -> l a -> MultiToggle (HCons t EOT) l a
mkToggle1 t = mkToggle (single t)
-- | Marks the end of a transformer list. -- | Marks the end of a transformer list.
data EOT = EOT deriving (Read, Show) data EOT = EOT deriving (Read, Show)
data HCons a b = HCons a b deriving (Read, Show) data HCons a b = HCons a b deriving (Read, Show)

View File

@ -0,0 +1,40 @@
{-# OPTIONS_GHC -fglasgow-exts #-}
-- above is for compatibility with GHC 6.6.
{-# LANGUAGE TypeSynonymInstances, DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.MultiToggle.Instances
-- Copyright : (c) 2008 Brent Yorgey
-- License : BSD-style (see LICENSE)
--
-- Maintainer : <byorgey@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Some convenient common instances of the
-- 'XMonad.Layout.MultiToggle.Transformer' class, for use with
-- "XMonad.Layout.MultiToggle".
module XMonad.Layout.MultiToggle.Instances (
StdTransformers(..)
) where
import XMonad.Layout.MultiToggle
import XMonad
import XMonad.Layout.NoBorders
data StdTransformers = FULL -- ^ switch to Full layout
| NBFULL -- ^ switch to Full with no borders
| MIRROR -- ^ Mirror the current layout.
| NOBORDERS -- ^ Remove borders.
| SMARTBORDERS -- ^ Apply smart borders.
deriving (Read, Show, Eq, Typeable)
instance Transformer StdTransformers Window where
transform FULL _ k = k Full
transform NBFULL _ k = k (noBorders Full)
transform MIRROR x k = k (Mirror x)
transform NOBORDERS x k = k (noBorders x)
transform SMARTBORDERS x k = k (smartBorders x)

View File

@ -130,6 +130,7 @@ library
XMonad.Layout.Maximize XMonad.Layout.Maximize
XMonad.Layout.MosaicAlt XMonad.Layout.MosaicAlt
XMonad.Layout.MultiToggle XMonad.Layout.MultiToggle
XMonad.Layout.MultiToggle.Instances
XMonad.Layout.Named XMonad.Layout.Named
XMonad.Layout.NoBorders XMonad.Layout.NoBorders
XMonad.Layout.PerWorkspace XMonad.Layout.PerWorkspace