aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorezyang <ezyang@cs.stanford.edu>2015-05-02 06:53:53 +0200
committerezyang <ezyang@cs.stanford.edu>2015-05-02 06:53:53 +0200
commit099bde5d7318929075ffa44636be5f7f816dddcc (patch)
treea65d9803e08e3eb4c819c1870ae28c865392c338
parent7a1ee5feeb06d304809f6296751370abf4982230 (diff)
downloadXMonadContrib-099bde5d7318929075ffa44636be5f7f816dddcc.tar.gz
XMonadContrib-099bde5d7318929075ffa44636be5f7f816dddcc.tar.xz
XMonadContrib-099bde5d7318929075ffa44636be5f7f816dddcc.zip
Add XMonad.Layout.PerScreen
Ignore-this: 52ebaa3d4fec91526c0bea19fa3824de darcs-hash:20150502045353-51a2f-9e77342ed81eee393a140e6e4f8248b5bb08dac0.gz
-rw-r--r--XMonad/Layout/PerScreen.hs74
-rw-r--r--xmonad-contrib.cabal1
2 files changed, 75 insertions, 0 deletions
diff --git a/XMonad/Layout/PerScreen.hs b/XMonad/Layout/PerScreen.hs
new file mode 100644
index 0000000..b062dc4
--- /dev/null
+++ b/XMonad/Layout/PerScreen.hs
@@ -0,0 +1,74 @@
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.PerScreen
+-- Copyright : (c) Edward Z. Yang
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : <ezyang@cs.stanford.edu>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Configure layouts based on the width of your screen; use your
+-- favorite multi-column layout for wide screens and a full-screen
+-- layout for small ones.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.PerScreen
+ ( -- * Usage
+ -- $usage
+ PerScreen,
+ ifWider
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+
+import Data.Maybe (fromMaybe)
+
+-- $usage
+-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
+--
+-- > import XMonad.Layout.PerScreen
+--
+-- and modifying your layoutHook as follows (for example):
+--
+-- > layoutHook = ifWider 1280 (Tall 1 (3/100) (1/2) ||| Full) Full
+--
+-- Replace any of the layouts with any arbitrarily complicated layout.
+-- ifWider can also be used inside other layout combinators.
+
+ifWider :: (LayoutClass l1 a, LayoutClass l2 a)
+ => Dimension -- ^ target screen width
+ -> (l1 a) -- ^ layout to use when the screen is wide enough
+ -> (l2 a) -- ^ layout to use otherwise
+ -> PerScreen l1 l2 a
+ifWider w = PerScreen w False
+
+data PerScreen l1 l2 a = PerScreen Dimension Bool (l1 a) (l2 a) deriving (Read, Show)
+
+-- | Construct new PerScreen values with possibly modified layouts.
+mkNewPerScreenT :: PerScreen l1 l2 a -> Maybe (l1 a) ->
+ PerScreen l1 l2 a
+mkNewPerScreenT (PerScreen w _ lt lf) mlt' =
+ (\lt' -> PerScreen w True lt' lf) $ fromMaybe lt mlt'
+
+mkNewPerScreenF :: PerScreen l1 l2 a -> Maybe (l2 a) ->
+ PerScreen l1 l2 a
+mkNewPerScreenF (PerScreen w _ lt lf) mlf' =
+ (\lf' -> PerScreen w False lt lf') $ fromMaybe lf mlf'
+
+instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerScreen l1 l2) a where
+ runLayout (W.Workspace i p@(PerScreen w _ lt lf) ms) r
+ | rect_width r > w = do (wrs, mlt') <- runLayout (W.Workspace i lt ms) r
+ return (wrs, Just $ mkNewPerScreenT p mlt')
+ | otherwise = do (wrs, mlt') <- runLayout (W.Workspace i lf ms) r
+ return (wrs, Just $ mkNewPerScreenF p mlt')
+
+ handleMessage (PerScreen w bool lt lf) m
+ | bool = handleMessage lt m >>= maybe (return Nothing) (\nt -> return . Just $ PerScreen w bool nt lf)
+ | otherwise = handleMessage lf m >>= maybe (return Nothing) (\nf -> return . Just $ PerScreen w bool lt nf)
+
+ description (PerScreen _ True l1 _) = description l1
+ description (PerScreen _ _ _ l2) = description l2
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index cc437c6..6399c5d 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -252,6 +252,7 @@ library
XMonad.Layout.NoFrillsDecoration
XMonad.Layout.OnHost
XMonad.Layout.OneBig
+ XMonad.Layout.PerScreen
XMonad.Layout.PerWorkspace
XMonad.Layout.PositionStoreFloat
XMonad.Layout.Reflect