aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--XMonad/Layout/Simplest.hs41
-rw-r--r--xmonad-contrib.cabal1
2 files changed, 42 insertions, 0 deletions
diff --git a/XMonad/Layout/Simplest.hs b/XMonad/Layout/Simplest.hs
new file mode 100644
index 0000000..5370013
--- /dev/null
+++ b/XMonad/Layout/Simplest.hs
@@ -0,0 +1,41 @@
+{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Simplest
+-- Copyright : (c) 2007 Andrea Rossato
+-- License : BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer : andrea.rossato@unibz.it
+-- Stability : unstable
+-- Portability : unportable
+--
+-- A very simple layout. The simplest, afaik.
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Simplest
+ ( -- * Usage:
+ -- $usage
+ Simplest (..)
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as S
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.Simplest
+--
+-- Then edit your @layoutHook@ by adding the Simplest layout:
+--
+-- > myLayouts = Simplest ||| Full ||| etc..
+-- > main = xmonad defaultConfig { layoutHook = myLayouts }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+data Simplest a = Simplest deriving (Show, Read)
+instance LayoutClass Simplest Window where
+ pureLayout Simplest rec (S.Stack w l r) = zip (w : reverse l ++ r) (repeat rec)
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 1529a75..3b217fb 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -117,6 +117,7 @@ library
XMonad.Layout.Reflect
XMonad.Layout.ResizableTile
XMonad.Layout.Roledex
+ XMonad.Layout.Simplest
XMonad.Layout.Spiral
XMonad.Layout.Square
XMonad.Layout.ShowWName