diff options
author | Andrea Rossato <andrea.rossato@unibz.it> | 2008-01-25 16:20:15 +0100 |
---|---|---|
committer | Andrea Rossato <andrea.rossato@unibz.it> | 2008-01-25 16:20:15 +0100 |
commit | 6cb9fc74d97b5b7a0497c3b27c047435a8cbb0e1 (patch) | |
tree | da53b642ca0535f7f44af1c62a4037796f8ce377 /XMonad | |
parent | cd1744c9f65203215131f463301dc3f1def58d41 (diff) | |
download | XMonadContrib-6cb9fc74d97b5b7a0497c3b27c047435a8cbb0e1.tar.gz XMonadContrib-6cb9fc74d97b5b7a0497c3b27c047435a8cbb0e1.tar.xz XMonadContrib-6cb9fc74d97b5b7a0497c3b27c047435a8cbb0e1.zip |
Add Layout.Simplest, the simplest layout
darcs-hash:20080125152015-32816-678e0595c75eb62e0124152509accefdf782ae5d.gz
Diffstat (limited to 'XMonad')
-rw-r--r-- | XMonad/Layout/Simplest.hs | 41 |
1 files changed, 41 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) |