-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.DecorationMadness
-- Description :  A collection of decorated layouts.
-- Copyright   :  (c) 2007 Andrea Rossato
-- License     :  BSD-style (see xmonad/LICENSE)
--
-- Maintainer  :  andrea.rossato@unibz.it
-- Stability   :  unstable
-- Portability :  unportable
--
-- A collection of decorated layouts: some of them may be nice, some
-- usable, others just funny.
-----------------------------------------------------------------------------

module XMonad.Layout.DecorationMadness
    ( -- * Usage
      -- $usage

      -- * Decorated layouts based on Circle
      -- $circle
      circleSimpleDefault
    , circleDefault
    , circleSimpleDefaultResizable
    , circleDefaultResizable
    , circleSimpleDeco
    , circleSimpleDecoResizable
    , circleDeco
    , circleDecoResizable
    , circleSimpleDwmStyle
    , circleDwmStyle
    , circleSimpleTabbed
    , circleTabbed
    -- * Decorated layouts based on Accordion
    -- $accordion
    , accordionSimpleDefault
    , accordionDefault
    , accordionSimpleDefaultResizable
    , accordionDefaultResizable
    , accordionSimpleDeco
    , accordionSimpleDecoResizable
    , accordionDeco
    , accordionDecoResizable
    , accordionSimpleDwmStyle
    , accordionDwmStyle
    , accordionSimpleTabbed
    , accordionTabbed
    -- * Tall decorated layouts
    -- $tall
    , tallSimpleDefault
    , tallDefault
    , tallSimpleDefaultResizable
    , tallDefaultResizable
    , tallSimpleDeco
    , tallDeco
    , tallSimpleDecoResizable
    , tallDecoResizable
    , tallSimpleDwmStyle
    , tallDwmStyle
    , tallSimpleTabbed
    , tallTabbed
    -- * Mirror Tall decorated layouts
    -- $mirror
    , mirrorTallSimpleDefault
    , mirrorTallDefault
    , mirrorTallSimpleDefaultResizable
    , mirrorTallDefaultResizable
    , mirrorTallSimpleDeco
    , mirrorTallDeco
    , mirrorTallSimpleDecoResizable
    , mirrorTallDecoResizable
    , mirrorTallSimpleDwmStyle
    , mirrorTallDwmStyle
    , mirrorTallSimpleTabbed
    , mirrorTallTabbed
    -- * Floating decorated layouts
    -- $float
    , floatSimpleSimple
    , floatSimple
    , floatSimpleDefault
    , floatDefault
    , floatSimpleDwmStyle
    , floatDwmStyle
    , floatSimpleTabbed
    , floatTabbed
    , def, shrinkText
    ) where

import XMonad
import XMonad.Actions.MouseResize
import XMonad.Layout.Decoration
import XMonad.Layout.DwmStyle
import XMonad.Layout.SimpleDecoration
import XMonad.Layout.TabBarDecoration

import XMonad.Layout.Accordion
import XMonad.Layout.Circle
import XMonad.Layout.WindowArranger
import XMonad.Layout.SimpleFloat

-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.DecorationMadness
--
-- Then edit your @layoutHook@ by adding the layout you want:
--
-- > main = xmonad def { layoutHook = someMadLayout }
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
--
-- You can also edit the default theme:
--
-- > myTheme = def { inactiveBorderColor = "#FF0000"
-- >                        , activeTextColor     = "#00FF00" }
--
-- and
--
-- > mylayout = tabbed shrinkText myTheme ||| Full ||| etc..
--
-- When a layout is resizable, this means two different things: you
-- can grab a window's decoration with the pointer and move it around,
-- and you can move and resize windows with the keyboard. For setting
-- up the key bindings, please read the documentation of
-- "XMonad.Layout.WindowArranger"
--
-- The default theme can be dynamically change with the xmonad theme
-- selector. See "XMonad.Prompt.Theme". For more themes, look at
-- "XMonad.Util.Themes"

-- $circle
-- Here you will find 'Circle' based decorated layouts.

-- | A 'Circle' layout with the xmonad default decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefault.png>
circleSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Circle Window
circleSimpleDefault :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker) Circle Window
circleSimpleDefault = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> Circle Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Circle Window
forall a. Circle a
Circle

-- | Similar to 'circleSimpleDefault' but with the possibility of
-- setting a custom shrinker and a custom theme.
circleDefault :: Shrinker s => s -> Theme
              -> ModifiedLayout (Decoration DefaultDecoration s) Circle Window
circleDefault :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration DefaultDecoration s) Circle Window
circleDefault s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> Circle Window
-> ModifiedLayout (Decoration DefaultDecoration s) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Circle Window
forall a. Circle a
Circle

-- | A 'Circle' layout with the xmonad simple decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDeco.png>
circleSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Circle Window
circleSimpleDeco :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker) Circle Window
circleSimpleDeco = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> Circle Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Circle Window
forall a. Circle a
Circle

-- | Similar to 'circleSimpleDece' but with the possibility of
-- setting a custom shrinker and a custom theme.
circleDeco :: Shrinker s => s -> Theme
           -> ModifiedLayout (Decoration SimpleDecoration s) Circle Window
circleDeco :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration SimpleDecoration s) Circle Window
circleDeco s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> Circle Window
-> ModifiedLayout (Decoration SimpleDecoration s) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Circle Window
forall a. Circle a
Circle

-- | A 'Circle' layout with the xmonad default decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefaultResizable.png>
circleSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
                                (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window
circleSimpleDefaultResizable :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker)
  (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
  Window
circleSimpleDefaultResizable = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Circle Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Circle) Window)
-> ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall a b. (a -> b) -> a -> b
$ Circle Window -> ModifiedLayout WindowArranger Circle Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Circle Window
forall a. Circle a
Circle)

-- | Similar to 'circleSimpleDefaultResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
circleDefaultResizable :: Shrinker s => s -> Theme
                       -> ModifiedLayout (Decoration DefaultDecoration s)
                          (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window
circleDefaultResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
circleDefaultResizable s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Circle Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Circle) Window)
-> ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall a b. (a -> b) -> a -> b
$ Circle Window -> ModifiedLayout WindowArranger Circle Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Circle Window
forall a. Circle a
Circle)

-- | A 'Circle' layout with the xmonad simple decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDecoResizable.png>
circleSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
                             (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window
circleSimpleDecoResizable :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
  Window
circleSimpleDecoResizable = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Circle Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Circle) Window)
-> ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall a b. (a -> b) -> a -> b
$ Circle Window -> ModifiedLayout WindowArranger Circle Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Circle Window
forall a. Circle a
Circle)

-- | Similar to 'circleSimpleDecoResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
circleDecoResizable :: Shrinker s => s -> Theme
                    -> ModifiedLayout (Decoration SimpleDecoration s)
                       (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window
circleDecoResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
circleDecoResizable s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Circle Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Circle) Window)
-> ModifiedLayout WindowArranger Circle Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Circle) Window
forall a b. (a -> b) -> a -> b
$ Circle Window -> ModifiedLayout WindowArranger Circle Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Circle Window
forall a. Circle a
Circle)

-- | A 'Circle' layout with the xmonad DwmStyle decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleDwmStyle.png>
circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Circle Window
circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Circle Window
circleSimpleDwmStyle = DefaultShrinker
-> Theme
-> DwmStyle Window
-> Circle Window
-> ModifiedLayout
     (Decoration DwmStyle DefaultShrinker) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DwmStyle Window
forall a. DwmStyle a
Dwm Circle Window
forall a. Circle a
Circle

-- | Similar to 'circleSimpleDwmStyle' but with the
-- possibility of setting a custom shrinker and a custom theme.
circleDwmStyle :: Shrinker s => s -> Theme
               -> ModifiedLayout (Decoration DwmStyle s) Circle Window
circleDwmStyle :: forall s.
Shrinker s =>
s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Circle Window
circleDwmStyle s
s Theme
t = s
-> Theme
-> DwmStyle Window
-> Circle Window
-> ModifiedLayout (Decoration DwmStyle s) Circle Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DwmStyle Window
forall a. DwmStyle a
Dwm Circle Window
forall a. Circle a
Circle

-- | A 'Circle' layout with the xmonad tabbed decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/circleSimpleTabbed.png>
circleSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Circle) Window
circleSimpleTabbed :: ModifiedLayout
  (Decoration TabBarDecoration DefaultShrinker)
  (ModifiedLayout ResizeScreen Circle)
  Window
circleSimpleTabbed = Circle Window
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen Circle)
     Window
forall a (l :: * -> *).
Eq a =>
l a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen l)
     a
simpleTabBar Circle Window
forall a. Circle a
Circle

-- | Similar to 'circleSimpleTabbed' but with the
-- possibility of setting a custom shrinker and a custom theme.
circleTabbed :: Shrinker s => s -> Theme
             -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Circle) Window
circleTabbed :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Circle)
     Window
circleTabbed s
s Theme
t = s
-> Theme
-> XPPosition
-> ModifiedLayout ResizeScreen Circle Window
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Circle)
     Window
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s
s Theme
t XPPosition
Top (Int -> Circle Window -> ModifiedLayout ResizeScreen Circle Window
forall (l :: * -> *) a.
Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Int) -> Dimension -> Int
forall a b. (a -> b) -> a -> b
$ Theme -> Dimension
decoHeight Theme
t) Circle Window
forall a. Circle a
Circle)


-- $accordion
-- Here you will find decorated layouts based on the 'Accordion'
-- layout.

-- | An 'Accordion' layout with the xmonad default decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDefault.png>
accordionSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Accordion Window
accordionSimpleDefault :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker) Accordion Window
accordionSimpleDefault = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> Accordion Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Accordion Window
forall a. Accordion a
Accordion

-- | Similar to 'accordionSimpleDefault' but with the possibility of
-- setting a custom shrinker and a custom theme.
accordionDefault :: Shrinker s => s -> Theme
                 -> ModifiedLayout (Decoration DefaultDecoration s) Accordion Window
accordionDefault :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration DefaultDecoration s) Accordion Window
accordionDefault s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> Accordion Window
-> ModifiedLayout (Decoration DefaultDecoration s) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Accordion Window
forall a. Accordion a
Accordion

-- | An 'Accordion' layout with the xmonad simple decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDeco.png>
accordionSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Accordion Window
accordionSimpleDeco :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker) Accordion Window
accordionSimpleDeco = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> Accordion Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Accordion Window
forall a. Accordion a
Accordion

-- | Similar to 'accordionSimpleDece' but with the possibility of
-- setting a custom shrinker and a custom theme.
accordionDeco :: Shrinker s => s -> Theme
              -> ModifiedLayout (Decoration SimpleDecoration s) Accordion Window
accordionDeco :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration SimpleDecoration s) Accordion Window
accordionDeco s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> Accordion Window
-> ModifiedLayout (Decoration SimpleDecoration s) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Accordion Window
forall a. Accordion a
Accordion

-- | An 'Accordion' layout with the xmonad default decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
accordionSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
                                   (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window
accordionSimpleDefaultResizable :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion))
  Window
accordionSimpleDefaultResizable = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Accordion Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Accordion) Window)
-> ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall a b. (a -> b) -> a -> b
$ Accordion Window -> ModifiedLayout WindowArranger Accordion Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Accordion Window
forall a. Accordion a
Accordion)

-- | Similar to 'accordionSimpleDefaultResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
accordionDefaultResizable :: Shrinker s => s -> Theme
                          -> ModifiedLayout (Decoration DefaultDecoration s)
                             (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window
accordionDefaultResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
accordionDefaultResizable s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Accordion Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Accordion) Window)
-> ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall a b. (a -> b) -> a -> b
$ Accordion Window -> ModifiedLayout WindowArranger Accordion Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Accordion Window
forall a. Accordion a
Accordion)

-- | An 'Accordion' layout with the xmonad simple decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
accordionSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
                                (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window
accordionSimpleDecoResizable :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion))
  Window
accordionSimpleDecoResizable = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Accordion Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Accordion) Window)
-> ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall a b. (a -> b) -> a -> b
$ Accordion Window -> ModifiedLayout WindowArranger Accordion Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Accordion Window
forall a. Accordion a
Accordion)

-- | Similar to 'accordionSimpleDecoResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
accordionDecoResizable :: Shrinker s => s -> Theme
                       -> ModifiedLayout (Decoration SimpleDecoration s)
                          (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window
accordionDecoResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
accordionDecoResizable s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger Accordion))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Accordion Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Accordion) Window)
-> ModifiedLayout WindowArranger Accordion Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Accordion) Window
forall a b. (a -> b) -> a -> b
$ Accordion Window -> ModifiedLayout WindowArranger Accordion Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Accordion Window
forall a. Accordion a
Accordion)

-- | An 'Accordion' layout with the xmonad DwmStyle decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDwmStyle.png>
accordionSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Accordion Window
accordionSimpleDwmStyle :: ModifiedLayout
  (Decoration DwmStyle DefaultShrinker) Accordion Window
accordionSimpleDwmStyle = DefaultShrinker
-> Theme
-> DwmStyle Window
-> Accordion Window
-> ModifiedLayout
     (Decoration DwmStyle DefaultShrinker) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DwmStyle Window
forall a. DwmStyle a
Dwm Accordion Window
forall a. Accordion a
Accordion

-- | Similar to 'accordionSimpleDwmStyle' but with the
-- possibility of setting a custom shrinker and a custom theme.
accordionDwmStyle :: Shrinker s => s -> Theme
                  -> ModifiedLayout (Decoration DwmStyle s) Accordion Window
accordionDwmStyle :: forall s.
Shrinker s =>
s
-> Theme -> ModifiedLayout (Decoration DwmStyle s) Accordion Window
accordionDwmStyle s
s Theme
t = s
-> Theme
-> DwmStyle Window
-> Accordion Window
-> ModifiedLayout (Decoration DwmStyle s) Accordion Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DwmStyle Window
forall a. DwmStyle a
Dwm Accordion Window
forall a. Accordion a
Accordion

-- | An 'Accordion' layout with the xmonad tabbed decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/accordionSimpleTabbed.png>
accordionSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Accordion) Window
accordionSimpleTabbed :: ModifiedLayout
  (Decoration TabBarDecoration DefaultShrinker)
  (ModifiedLayout ResizeScreen Accordion)
  Window
accordionSimpleTabbed = Accordion Window
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen Accordion)
     Window
forall a (l :: * -> *).
Eq a =>
l a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen l)
     a
simpleTabBar Accordion Window
forall a. Accordion a
Accordion

-- | Similar to 'accordionSimpleTabbed' but with the
-- possibility of setting a custom shrinker and a custom theme.
accordionTabbed :: Shrinker s => s -> Theme
                -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Accordion) Window
accordionTabbed :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Accordion)
     Window
accordionTabbed s
s Theme
t = s
-> Theme
-> XPPosition
-> ModifiedLayout ResizeScreen Accordion Window
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Accordion)
     Window
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s
s Theme
t XPPosition
Top (Int
-> Accordion Window -> ModifiedLayout ResizeScreen Accordion Window
forall (l :: * -> *) a.
Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Int) -> Dimension -> Int
forall a b. (a -> b) -> a -> b
$ Theme -> Dimension
decoHeight Theme
t) Accordion Window
forall a. Accordion a
Accordion)


-- $tall
-- In this section you will find decorated layouts based on the
-- 'Tall' layout.

tall :: Tall Window
tall :: Tall Window
tall = Int -> Rational -> Rational -> Tall Window
forall a. Int -> Rational -> Rational -> Tall a
Tall Int
1 (Rational
3Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
100) (Rational
1Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
2)

-- | A 'Tall' layout with the xmonad default decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefault.png>
tallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Tall Window
tallSimpleDefault :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker) Tall Window
tallSimpleDefault = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> Tall Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Tall Window
tall

-- | Similar to 'tallSimpleDefault' but with the possibility of
-- setting a custom shrinker and a custom theme.
tallDefault :: Shrinker s => s -> Theme
            -> ModifiedLayout (Decoration DefaultDecoration s) Tall Window
tallDefault :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration DefaultDecoration s) Tall Window
tallDefault s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> Tall Window
-> ModifiedLayout (Decoration DefaultDecoration s) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Tall Window
tall

-- | A 'Tall' layout with the xmonad simple decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleDeco.png>
tallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Tall Window
tallSimpleDeco :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker) Tall Window
tallSimpleDeco = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> Tall Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Tall Window
tall

-- | Similar to 'tallSimpleDece' but with the possibility of
-- setting a custom shrinker and a custom theme.
tallDeco :: Shrinker s => s -> Theme
         -> ModifiedLayout (Decoration SimpleDecoration s) Tall Window
tallDeco :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration SimpleDecoration s) Tall Window
tallDeco s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> Tall Window
-> ModifiedLayout (Decoration SimpleDecoration s) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Tall Window
tall

-- | A 'Tall' layout with the xmonad default decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefaultResizable.png>
tallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
                              (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window
tallSimpleDefaultResizable :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker)
  (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
  Window
tallSimpleDefaultResizable = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Tall Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Tall) Window)
-> ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall a b. (a -> b) -> a -> b
$ Tall Window -> ModifiedLayout WindowArranger Tall Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Tall Window
tall)

-- | Similar to 'tallSimpleDefaultResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
tallDefaultResizable :: Shrinker s => s -> Theme
                     -> ModifiedLayout (Decoration DefaultDecoration s)
                        (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window
tallDefaultResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
tallDefaultResizable s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Tall Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Tall) Window)
-> ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall a b. (a -> b) -> a -> b
$ Tall Window -> ModifiedLayout WindowArranger Tall Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Tall Window
tall)

-- | A 'Tall' layout with the xmonad simple decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleDecoResizable.png>
tallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
                           (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window
tallSimpleDecoResizable :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
  Window
tallSimpleDecoResizable = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Tall Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Tall) Window)
-> ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall a b. (a -> b) -> a -> b
$ Tall Window -> ModifiedLayout WindowArranger Tall Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Tall Window
tall)

-- | Similar to 'tallSimpleDecoResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
tallDecoResizable :: Shrinker s => s -> Theme
                  -> ModifiedLayout (Decoration SimpleDecoration s)
                     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window
tallDecoResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
tallDecoResizable s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger Tall Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger Tall) Window)
-> ModifiedLayout WindowArranger Tall Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger Tall) Window
forall a b. (a -> b) -> a -> b
$ Tall Window -> ModifiedLayout WindowArranger Tall Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Tall Window
tall)

-- | A 'Tall' layout with the xmonad DwmStyle decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleDwmStyle.png>
tallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Tall Window
tallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Tall Window
tallSimpleDwmStyle = DefaultShrinker
-> Theme
-> DwmStyle Window
-> Tall Window
-> ModifiedLayout (Decoration DwmStyle DefaultShrinker) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DwmStyle Window
forall a. DwmStyle a
Dwm Tall Window
tall

-- | Similar to 'tallSimpleDwmStyle' but with the
-- possibility of setting a custom shrinker and a custom theme.
tallDwmStyle :: Shrinker s => s -> Theme
             -> ModifiedLayout (Decoration DwmStyle s) Tall Window
tallDwmStyle :: forall s.
Shrinker s =>
s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Tall Window
tallDwmStyle s
s Theme
t = s
-> Theme
-> DwmStyle Window
-> Tall Window
-> ModifiedLayout (Decoration DwmStyle s) Tall Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DwmStyle Window
forall a. DwmStyle a
Dwm Tall Window
tall

-- | A 'Tall' layout with the xmonad tabbed decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/tallSimpleTabbed.png>
tallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Tall) Window
tallSimpleTabbed :: ModifiedLayout
  (Decoration TabBarDecoration DefaultShrinker)
  (ModifiedLayout ResizeScreen Tall)
  Window
tallSimpleTabbed = Tall Window
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen Tall)
     Window
forall a (l :: * -> *).
Eq a =>
l a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen l)
     a
simpleTabBar Tall Window
tall

-- | Similar to 'tallSimpleTabbed' but with the
-- possibility of setting a custom shrinker and a custom theme.
tallTabbed :: Shrinker s => s -> Theme
           -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Tall) Window
tallTabbed :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Tall)
     Window
tallTabbed s
s Theme
t = s
-> Theme
-> XPPosition
-> ModifiedLayout ResizeScreen Tall Window
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen Tall)
     Window
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s
s Theme
t XPPosition
Top (Int -> Tall Window -> ModifiedLayout ResizeScreen Tall Window
forall (l :: * -> *) a.
Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Int) -> Dimension -> Int
forall a b. (a -> b) -> a -> b
$ Theme -> Dimension
decoHeight Theme
t) Tall Window
tall)

-- $mirror
-- In this section you will find decorated layouts based on the
-- 'Mirror' layout modifier applied to 'Tall'.

mirrorTall :: Mirror Tall Window
mirrorTall :: Mirror Tall Window
mirrorTall = Tall Window -> Mirror Tall Window
forall (l :: * -> *) a. l a -> Mirror l a
Mirror Tall Window
tall

-- | A 'Mirror Tall' layout with the xmonad default decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefault.png>
mirrorTallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDefault :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDefault = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> Mirror Tall Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Mirror Tall Window
mirrorTall

-- | Similar to 'mirrorTallSimpleDefault' but with the possibility of
-- setting a custom shrinker and a custom theme.
mirrorTallDefault :: Shrinker s => s -> Theme
                  -> ModifiedLayout (Decoration DefaultDecoration s) (Mirror Tall) Window
mirrorTallDefault :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s) (Mirror Tall) Window
mirrorTallDefault s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> Mirror Tall Window
-> ModifiedLayout
     (Decoration DefaultDecoration s) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration Mirror Tall Window
mirrorTall

-- | A 'Mirror Tall' layout with the xmonad simple decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDeco.png>
mirrorTallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDeco :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDeco = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> Mirror Tall Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Mirror Tall Window
mirrorTall

-- | Similar to 'mirrorTallSimpleDece' but with the possibility of
-- setting a custom shrinker and a custom theme.
mirrorTallDeco :: Shrinker s => s -> Theme
               -> ModifiedLayout (Decoration SimpleDecoration s) (Mirror Tall) Window
mirrorTallDeco :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s) (Mirror Tall) Window
mirrorTallDeco s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> Mirror Tall Window
-> ModifiedLayout
     (Decoration SimpleDecoration s) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) Mirror Tall Window
mirrorTall

-- | A 'Mirror Tall' layout with the xmonad default decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefaultResizable.png>
mirrorTallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
                                    (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window
mirrorTallSimpleDefaultResizable :: ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
  Window
mirrorTallSimpleDefaultResizable = DefaultShrinker
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger (Mirror Tall) Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window)
-> ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall a b. (a -> b) -> a -> b
$ Mirror Tall Window
-> ModifiedLayout WindowArranger (Mirror Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Mirror Tall Window
mirrorTall)

-- | Similar to 'mirrorTallSimpleDefaultResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
mirrorTallDefaultResizable :: Shrinker s => s -> Theme
                           -> ModifiedLayout (Decoration DefaultDecoration s)
                              (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window
mirrorTallDefaultResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
mirrorTallDefaultResizable s
s Theme
t = s
-> Theme
-> DefaultDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration Window
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger (Mirror Tall) Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window)
-> ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall a b. (a -> b) -> a -> b
$ Mirror Tall Window
-> ModifiedLayout WindowArranger (Mirror Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Mirror Tall Window
mirrorTall)

-- | A 'Mirror Tall' layout with the xmonad simple decoration, default
-- theme and default shrinker, but with the possibility of moving
-- windows with the mouse, and resize\/move them with the keyboard.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDecoResizable.png>
mirrorTallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
                                 (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window
mirrorTallSimpleDecoResizable :: ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
  Window
mirrorTallSimpleDecoResizable = DefaultShrinker
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
-> ModifiedLayout
     (Decoration SimpleDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger (Mirror Tall) Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window)
-> ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall a b. (a -> b) -> a -> b
$ Mirror Tall Window
-> ModifiedLayout WindowArranger (Mirror Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Mirror Tall Window
mirrorTall)

-- | Similar to 'mirrorTallSimpleDecoResizable' but with the
-- possibility of setting a custom shrinker and a custom theme.
mirrorTallDecoResizable :: Shrinker s => s -> Theme
                        -> ModifiedLayout (Decoration SimpleDecoration s)
                           (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window
mirrorTallDecoResizable :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
mirrorTallDecoResizable s
s Theme
t = s
-> Theme
-> SimpleDecoration Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger (Mirror Tall)))
     Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t (Bool -> SimpleDecoration Window
forall a. Bool -> SimpleDecoration a
Simple Bool
True) (ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger (Mirror Tall) Window
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window)
-> ModifiedLayout WindowArranger (Mirror Tall) Window
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger (Mirror Tall)) Window
forall a b. (a -> b) -> a -> b
$ Mirror Tall Window
-> ModifiedLayout WindowArranger (Mirror Tall) Window
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrange Mirror Tall Window
mirrorTall)

-- | A 'Mirror Tall' layout with the xmonad DwmStyle decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDwmStyle.png>
mirrorTallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDwmStyle :: ModifiedLayout
  (Decoration DwmStyle DefaultShrinker) (Mirror Tall) Window
mirrorTallSimpleDwmStyle = DefaultShrinker
-> Theme
-> DwmStyle Window
-> Mirror Tall Window
-> ModifiedLayout
     (Decoration DwmStyle DefaultShrinker) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DwmStyle Window
forall a. DwmStyle a
Dwm Mirror Tall Window
mirrorTall

-- | Similar to 'mirrorTallSimpleDwmStyle' but with the
-- possibility of setting a custom shrinker and a custom theme.
mirrorTallDwmStyle :: Shrinker s => s -> Theme
                   -> ModifiedLayout (Decoration DwmStyle s) (Mirror Tall) Window
mirrorTallDwmStyle :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout (Decoration DwmStyle s) (Mirror Tall) Window
mirrorTallDwmStyle s
s Theme
t = s
-> Theme
-> DwmStyle Window
-> Mirror Tall Window
-> ModifiedLayout (Decoration DwmStyle s) (Mirror Tall) Window
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DwmStyle Window
forall a. DwmStyle a
Dwm Mirror Tall Window
mirrorTall

-- | A 'Mirror Tall' layout with the xmonad tabbed decoration, default
-- theme and default shrinker.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleTabbed.png>
mirrorTallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen (Mirror Tall)) Window
mirrorTallSimpleTabbed :: ModifiedLayout
  (Decoration TabBarDecoration DefaultShrinker)
  (ModifiedLayout ResizeScreen (Mirror Tall))
  Window
mirrorTallSimpleTabbed = Mirror Tall Window
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen (Mirror Tall))
     Window
forall a (l :: * -> *).
Eq a =>
l a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen l)
     a
simpleTabBar Mirror Tall Window
mirrorTall

-- | Similar to 'mirrorTallSimpleTabbed' but with the
-- possibility of setting a custom shrinker and a custom theme.
mirrorTallTabbed :: Shrinker s => s -> Theme
                 -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen (Mirror Tall)) Window
mirrorTallTabbed :: forall s.
Shrinker s =>
s
-> Theme
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen (Mirror Tall))
     Window
mirrorTallTabbed s
s Theme
t = s
-> Theme
-> XPPosition
-> ModifiedLayout ResizeScreen (Mirror Tall) Window
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout ResizeScreen (Mirror Tall))
     Window
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s
s Theme
t XPPosition
Top (Int
-> Mirror Tall Window
-> ModifiedLayout ResizeScreen (Mirror Tall) Window
forall (l :: * -> *) a.
Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical (Dimension -> Int
forall a b. (Integral a, Num b) => a -> b
fi (Dimension -> Int) -> Dimension -> Int
forall a b. (a -> b) -> a -> b
$ Theme -> Dimension
decoHeight Theme
t) Mirror Tall Window
mirrorTall)

-- $float
-- Here you will find decorated layout based on the SimpleFloating
-- layout

-- | A simple floating layout where every window is placed according
-- to the window's initial attributes.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/floatSimpleSimple.png>
floatSimpleSimple :: (Show a, Eq a) => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker)
                 (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimpleSimple :: forall a.
(Show a, Eq a) =>
ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
floatSimpleSimple = ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
forall a.
Eq a =>
ModifiedLayout
  (Decoration SimpleDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
simpleFloat

floatSimple :: (Show a, Eq a, Shrinker s) => s -> Theme ->
               ModifiedLayout (Decoration SimpleDecoration s)
          (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimple :: forall a s.
(Show a, Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
floatSimple = s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
     (Decoration SimpleDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
simpleFloat'

-- | This version is decorated with the 'DefaultDecoration' style.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/floatSimpleDefault.png>
floatSimpleDefault :: (Show a, Eq a) => ModifiedLayout (Decoration DefaultDecoration DefaultShrinker)
                  (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimpleDefault :: forall a.
(Show a, Eq a) =>
ModifiedLayout
  (Decoration DefaultDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
floatSimpleDefault = DefaultShrinker
-> Theme
-> DefaultDecoration a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration DefaultDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DefaultDecoration a
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF Dimension
20)

-- | Same as 'floatSimpleDefault', but with the possibility of setting a
-- custom shrinker and a custom theme.
floatDefault :: (Show a, Eq a, Shrinker s) => s -> Theme ->
                ModifiedLayout (Decoration DefaultDecoration s)
           (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatDefault :: forall a s.
(Show a, Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
floatDefault s
s Theme
t = s
-> Theme
-> DefaultDecoration a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration DefaultDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DefaultDecoration a
forall a. DefaultDecoration a
DefaultDecoration (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF (Theme -> Dimension
decoHeight Theme
t))

-- | This version is decorated with the 'DwmStyle'. Note that this is
-- a keyboard only floating layout.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/floatSimpleDwmStyle.png>
floatSimpleDwmStyle :: (Show a, Eq a) => ModifiedLayout (Decoration DwmStyle DefaultShrinker)
                   (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimpleDwmStyle :: forall a.
(Show a, Eq a) =>
ModifiedLayout
  (Decoration DwmStyle DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
floatSimpleDwmStyle = DefaultShrinker
-> Theme
-> DwmStyle a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration DwmStyle DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration DefaultShrinker
shrinkText Theme
forall a. Default a => a
def DwmStyle a
forall a. DwmStyle a
Dwm (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF Dimension
20)

-- | Same as 'floatSimpleDwmStyle', but with the possibility of setting a
-- custom shrinker and a custom theme.
floatDwmStyle :: (Show a, Eq a, Shrinker s) => s -> Theme ->
                 ModifiedLayout (Decoration DwmStyle s)
            (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatDwmStyle :: forall a s.
(Show a, Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
     (Decoration DwmStyle s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
floatDwmStyle s
s Theme
t = s
-> Theme
-> DwmStyle a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration DwmStyle s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall (ds :: * -> *) a s (l :: * -> *).
(DecorationStyle ds a, Shrinker s) =>
s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
decoration s
s Theme
t DwmStyle a
forall a. DwmStyle a
Dwm (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF (Theme -> Dimension
decoHeight Theme
t))

-- | This version is decorated with the 'TabbedDecoration' style.
-- | Mouse dragging is somehow weird.
--
-- Here you can find a screen shot:
--
-- <http://code.haskell.org/~arossato/xmonadShots/floatSimpleTabbed.png>
floatSimpleTabbed :: (Show a, Eq a) => ModifiedLayout (Decoration TabBarDecoration DefaultShrinker)
                 (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatSimpleTabbed :: forall a.
(Show a, Eq a) =>
ModifiedLayout
  (Decoration TabBarDecoration DefaultShrinker)
  (ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat))
  a
floatSimpleTabbed = DefaultShrinker
-> Theme
-> XPPosition
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar DefaultShrinker
shrinkText Theme
forall a. Default a => a
def XPPosition
Top (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF Dimension
20)

-- | Same as 'floatSimpleTabbed', but with the possibility of setting a
-- custom shrinker and a custom theme.
floatTabbed :: (Show a, Eq a, Shrinker s) => s -> Theme ->
               ModifiedLayout (Decoration TabBarDecoration s)
          (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
floatTabbed :: forall a s.
(Show a, Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
floatTabbed s
s Theme
t = s
-> Theme
-> XPPosition
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
-> ModifiedLayout
     (Decoration TabBarDecoration s)
     (ModifiedLayout
        MouseResize (ModifiedLayout WindowArranger SimpleFloat))
     a
forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> XPPosition
-> l a
-> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s
s Theme
t XPPosition
Top (ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall (l :: * -> *) a. l a -> ModifiedLayout MouseResize l a
mouseResize (ModifiedLayout WindowArranger SimpleFloat a
 -> ModifiedLayout
      MouseResize (ModifiedLayout WindowArranger SimpleFloat) a)
-> ModifiedLayout WindowArranger SimpleFloat a
-> ModifiedLayout
     MouseResize (ModifiedLayout WindowArranger SimpleFloat) a
forall a b. (a -> b) -> a -> b
$ SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall (l :: * -> *) a. l a -> ModifiedLayout WindowArranger l a
windowArrangeAll (SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a)
-> SimpleFloat a -> ModifiedLayout WindowArranger SimpleFloat a
forall a b. (a -> b) -> a -> b
$ Dimension -> SimpleFloat a
forall a. Dimension -> SimpleFloat a
SF (Theme -> Dimension
decoHeight Theme
t))