{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.Tabbed
-- Description :  A tabbed layout.
-- Copyright   :  (c) 2007 David Roundy, Andrea Rossato
-- License     :  BSD-style (see xmonad/LICENSE)
--
-- Maintainer  :  andrea.rossato@unibz.it
-- Stability   :  unstable
-- Portability :  unportable
--
-- A tabbed layout for the Xmonad Window Manager
--
-----------------------------------------------------------------------------

module XMonad.Layout.Tabbed
    ( -- * Usage:
      -- $usage
      simpleTabbed, tabbed, addTabs
    , simpleTabbedAlways, tabbedAlways, addTabsAlways
    , simpleTabbedBottom, tabbedBottom, addTabsBottom
    , simpleTabbedLeft, tabbedLeft, addTabsLeft
    , simpleTabbedRight, tabbedRight, addTabsRight
    , simpleTabbedBottomAlways, tabbedBottomAlways, addTabsBottomAlways
    , simpleTabbedLeftAlways, tabbedLeftAlways, addTabsLeftAlways
    , simpleTabbedRightAlways, tabbedRightAlways, addTabsRightAlways
    , Theme (..)
    , def
    , TabbedDecoration (..)
    , shrinkText, CustomShrink(CustomShrink)
    , Shrinker(..)
    , TabbarShown, Direction2D(..)
    ) where

import XMonad.Prelude

import XMonad
import qualified XMonad.StackSet as S
import XMonad.Layout.Decoration
import XMonad.Layout.Simplest ( Simplest(Simplest) )
import XMonad.Util.Types (Direction2D(..))

-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.Tabbed
--
-- Then edit your @layoutHook@ by adding the Tabbed layout:
--
-- > myLayout = simpleTabbed ||| Full ||| etc..
--
-- or, if you want a specific theme for you tabbed layout:
--
-- > myLayout = tabbed shrinkText def ||| Full ||| etc..
--
-- and then:
--
-- > main = xmonad def { layoutHook = myLayout }
--
-- This layout has hardcoded behaviour for mouse clicks on tab decorations:
-- Left click on the tab switches focus to that window.
-- Middle click on the tab closes the window.
--
-- The default Tabbar behaviour is to hide it when only one window is open
-- on the workspace.  To have it always shown, use one of the layouts or
-- modifiers ending in @Always@.
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
--
-- You can also edit the default configuration options.
--
-- > myTabConfig = def { inactiveBorderColor = "#FF0000"
-- >                   , activeTextColor = "#00FF00"}
--
-- and
--
-- > mylayout = tabbed shrinkText myTabConfig ||| Full ||| etc..

-- Layouts

-- | A tabbed layout with the default xmonad Theme.
--
-- This is a minimal working configuration:
--
-- > import XMonad
-- > import XMonad.Layout.Tabbed
-- > main = xmonad def { layoutHook = simpleTabbed }
simpleTabbed :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbed :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbed = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbed DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

simpleTabbedAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedAlways :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedAlways = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedAlways DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottom :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedBottom :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedBottom = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottom DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottomAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedBottomAlways :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedBottomAlways = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottomAlways DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedLeft, simpleTabbedRight :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker)
                                        Simplest Window
simpleTabbedLeft :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedLeft = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeft DefaultShrinker
shrinkText Theme
forall a. Default a => a
def
simpleTabbedRight :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedRight = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedRight DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedLeftAlways, simpleTabbedRightAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker)
                                                  Simplest Window
simpleTabbedLeftAlways :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedLeftAlways = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeftAlways DefaultShrinker
shrinkText Theme
forall a. Default a => a
def
simpleTabbedRightAlways :: ModifiedLayout
  (Decoration TabbedDecoration DefaultShrinker) Simplest Window
simpleTabbedRightAlways = DefaultShrinker
-> Theme
-> ModifiedLayout
     (Decoration TabbedDecoration DefaultShrinker) Simplest Window
forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedRightAlways DefaultShrinker
shrinkText Theme
forall a. Default a => a
def

-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbed     :: (Eq a, Shrinker s) => s -> Theme
           -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbed :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbed s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabs s
s Theme
c Simplest a
forall a. Simplest a
Simplest

tabbedAlways     :: (Eq a, Shrinker s) => s -> Theme
                 -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedAlways :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedAlways s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsAlways s
s Theme
c Simplest a
forall a. Simplest a
Simplest

-- | A layout decorated with tabs at the bottom and the possibility to set a custom
-- shrinker and theme.
tabbedBottom     :: (Eq a, Shrinker s) => s -> Theme
                 -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottom :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottom s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottom s
s Theme
c Simplest a
forall a. Simplest a
Simplest

tabbedBottomAlways     :: (Eq a, Shrinker s) => s -> Theme
                       -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottomAlways :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedBottomAlways s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottomAlways s
s Theme
c Simplest a
forall a. Simplest a
Simplest

-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedLeft, tabbedRight :: (Eq a, Shrinker s) => s -> Theme
                        -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeft :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeft s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsLeft s
s Theme
c Simplest a
forall a. Simplest a
Simplest
tabbedRight :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedRight s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRight s
s Theme
c Simplest a
forall a. Simplest a
Simplest

-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedLeftAlways, tabbedRightAlways :: (Eq a, Shrinker s) => s -> Theme
                                    -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeftAlways :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedLeftAlways s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsLeftAlways s
s Theme
c Simplest a
forall a. Simplest a
Simplest
tabbedRightAlways :: forall a s.
(Eq a, Shrinker s) =>
s
-> Theme
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
tabbedRightAlways s
s Theme
c = s
-> Theme
-> Simplest a
-> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRightAlways s
s Theme
c Simplest a
forall a. Simplest a
Simplest

-- Layout Modifiers

-- | A layout modifier that uses the provided shrinker and theme to add tabs to any layout.
addTabs :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
        -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabs :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabs = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
WhenPlural Direction2D
U

addTabsAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
              -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsAlways :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsAlways = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
Always Direction2D
U

-- | A layout modifier that uses the provided shrinker and theme to add tabs to the bottom of any layout.
addTabsBottom :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
              -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottom :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottom = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
WhenPlural Direction2D
D

addTabsBottomAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
                    -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottomAlways :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsBottomAlways = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
Always Direction2D
D

-- | A layout modifier that uses the provided shrinker and theme to add tabs to the side of any layout.
addTabsRight, addTabsLeft :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
                            -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRight :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRight = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
WhenPlural Direction2D
R
addTabsLeft :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsLeft = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
WhenPlural Direction2D
L

addTabsRightAlways, addTabsLeftAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a
                                      -> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRightAlways :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsRightAlways = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
Always Direction2D
R
addTabsLeftAlways :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
addTabsLeftAlways = TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
Always Direction2D
L

-- Tab creation abstractions.  Internal use only.

-- Create tabbar when required at the given location with the given
-- shrinker and theme to the supplied layout.
createTabs                ::(Eq a, LayoutClass l a, Shrinker s) => TabbarShown -> Direction2D -> s
                          -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a

createTabs :: forall a (l :: * -> *) s.
(Eq a, LayoutClass l a, Shrinker s) =>
TabbarShown
-> Direction2D
-> s
-> Theme
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l a
createTabs TabbarShown
sh Direction2D
loc s
tx Theme
th = s
-> Theme
-> TabbedDecoration a
-> l a
-> ModifiedLayout (Decoration TabbedDecoration s) l 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
tx Theme
th (Direction2D -> TabbarShown -> TabbedDecoration a
forall a. Direction2D -> TabbarShown -> TabbedDecoration a
Tabbed Direction2D
loc TabbarShown
sh)

data TabbarShown = Always | WhenPlural deriving (ReadPrec [TabbarShown]
ReadPrec TabbarShown
Int -> ReadS TabbarShown
ReadS [TabbarShown]
(Int -> ReadS TabbarShown)
-> ReadS [TabbarShown]
-> ReadPrec TabbarShown
-> ReadPrec [TabbarShown]
-> Read TabbarShown
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TabbarShown]
$creadListPrec :: ReadPrec [TabbarShown]
readPrec :: ReadPrec TabbarShown
$creadPrec :: ReadPrec TabbarShown
readList :: ReadS [TabbarShown]
$creadList :: ReadS [TabbarShown]
readsPrec :: Int -> ReadS TabbarShown
$creadsPrec :: Int -> ReadS TabbarShown
Read, Int -> TabbarShown -> ShowS
[TabbarShown] -> ShowS
TabbarShown -> String
(Int -> TabbarShown -> ShowS)
-> (TabbarShown -> String)
-> ([TabbarShown] -> ShowS)
-> Show TabbarShown
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TabbarShown] -> ShowS
$cshowList :: [TabbarShown] -> ShowS
show :: TabbarShown -> String
$cshow :: TabbarShown -> String
showsPrec :: Int -> TabbarShown -> ShowS
$cshowsPrec :: Int -> TabbarShown -> ShowS
Show, TabbarShown -> TabbarShown -> Bool
(TabbarShown -> TabbarShown -> Bool)
-> (TabbarShown -> TabbarShown -> Bool) -> Eq TabbarShown
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TabbarShown -> TabbarShown -> Bool
$c/= :: TabbarShown -> TabbarShown -> Bool
== :: TabbarShown -> TabbarShown -> Bool
$c== :: TabbarShown -> TabbarShown -> Bool
Eq)

data TabbedDecoration a = Tabbed Direction2D TabbarShown deriving (ReadPrec [TabbedDecoration a]
ReadPrec (TabbedDecoration a)
Int -> ReadS (TabbedDecoration a)
ReadS [TabbedDecoration a]
(Int -> ReadS (TabbedDecoration a))
-> ReadS [TabbedDecoration a]
-> ReadPrec (TabbedDecoration a)
-> ReadPrec [TabbedDecoration a]
-> Read (TabbedDecoration a)
forall a. ReadPrec [TabbedDecoration a]
forall a. ReadPrec (TabbedDecoration a)
forall a. Int -> ReadS (TabbedDecoration a)
forall a. ReadS [TabbedDecoration a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TabbedDecoration a]
$creadListPrec :: forall a. ReadPrec [TabbedDecoration a]
readPrec :: ReadPrec (TabbedDecoration a)
$creadPrec :: forall a. ReadPrec (TabbedDecoration a)
readList :: ReadS [TabbedDecoration a]
$creadList :: forall a. ReadS [TabbedDecoration a]
readsPrec :: Int -> ReadS (TabbedDecoration a)
$creadsPrec :: forall a. Int -> ReadS (TabbedDecoration a)
Read, Int -> TabbedDecoration a -> ShowS
[TabbedDecoration a] -> ShowS
TabbedDecoration a -> String
(Int -> TabbedDecoration a -> ShowS)
-> (TabbedDecoration a -> String)
-> ([TabbedDecoration a] -> ShowS)
-> Show (TabbedDecoration a)
forall a. Int -> TabbedDecoration a -> ShowS
forall a. [TabbedDecoration a] -> ShowS
forall a. TabbedDecoration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TabbedDecoration a] -> ShowS
$cshowList :: forall a. [TabbedDecoration a] -> ShowS
show :: TabbedDecoration a -> String
$cshow :: forall a. TabbedDecoration a -> String
showsPrec :: Int -> TabbedDecoration a -> ShowS
$cshowsPrec :: forall a. Int -> TabbedDecoration a -> ShowS
Show)

instance Eq a => DecorationStyle TabbedDecoration a where
    describeDeco :: TabbedDecoration a -> String
describeDeco (Tabbed Direction2D
U TabbarShown
_ ) = String
"Tabbed"
    describeDeco (Tabbed Direction2D
D TabbarShown
_ ) = String
"Tabbed Bottom"
    describeDeco (Tabbed Direction2D
L TabbarShown
_ ) = String
"Tabbed Left"
    describeDeco (Tabbed Direction2D
R TabbarShown
_ ) = String
"Tabbed Right"
    decorationEventHook :: TabbedDecoration a -> DecorationState -> Event -> X ()
decorationEventHook TabbedDecoration a
_ DecorationState
ds ButtonEvent { ev_window :: Event -> Window
ev_window     = Window
ew
                                         , ev_event_type :: Event -> Dimension
ev_event_type = Dimension
et
                                         , ev_button :: Event -> Dimension
ev_button     = Dimension
eb }
        | Dimension
et Dimension -> Dimension -> Bool
forall a. Eq a => a -> a -> Bool
== Dimension
buttonPress
        , Just ((Window
w,Rectangle
_),(Window, Maybe Rectangle)
_) <- Window
-> DecorationState
-> Maybe ((Window, Rectangle), (Window, Maybe Rectangle))
findWindowByDecoration Window
ew DecorationState
ds =
           if Dimension
eb Dimension -> Dimension -> Bool
forall a. Eq a => a -> a -> Bool
== Dimension
button2
               then Window -> X ()
killWindow Window
w
               else Window -> X ()
focus Window
w
    decorationEventHook TabbedDecoration a
_ DecorationState
_ Event
_ = () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

    pureDecoration :: TabbedDecoration a
-> Dimension
-> Dimension
-> Rectangle
-> Stack a
-> [(a, Rectangle)]
-> (a, Rectangle)
-> Maybe Rectangle
pureDecoration (Tabbed Direction2D
lc TabbarShown
sh) Dimension
wt Dimension
ht Rectangle
_ Stack a
s [(a, Rectangle)]
wrs (a
w,r :: Rectangle
r@(Rectangle Position
x Position
y Dimension
wh Dimension
hh))
        = if (TabbarShown
sh TabbarShown -> TabbarShown -> Bool
forall a. Eq a => a -> a -> Bool
== TabbarShown
Always Bool -> Bool -> Bool
&& Int
numWindows Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) Bool -> Bool -> Bool
|| Int
numWindows Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
          then Rectangle -> Maybe Rectangle
forall a. a -> Maybe a
Just (Rectangle -> Maybe Rectangle) -> Rectangle -> Maybe Rectangle
forall a b. (a -> b) -> a -> b
$ case Direction2D
lc of
                        Direction2D
U -> Rectangle
upperTab
                        Direction2D
D -> Rectangle
lowerTab
                        Direction2D
L -> Rectangle
leftTab
                        Direction2D
R -> Rectangle
rightTab
          else Maybe Rectangle
forall a. Maybe a
Nothing
        where ws :: [a]
ws = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((a, Rectangle) -> a) -> [(a, Rectangle)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a, Rectangle) -> a
forall a b. (a, b) -> a
fst (((a, Rectangle) -> Bool) -> [(a, Rectangle)] -> [(a, Rectangle)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Rectangle -> Rectangle -> Bool
forall a. Eq a => a -> a -> Bool
==Rectangle
r) (Rectangle -> Bool)
-> ((a, Rectangle) -> Rectangle) -> (a, Rectangle) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, Rectangle) -> Rectangle
forall a b. (a, b) -> b
snd) [(a, Rectangle)]
wrs)) (Stack a -> [a]
forall a. Stack a -> [a]
S.integrate Stack a
s)
              loc :: a -> a -> a -> a
loc a
k a
h a
i = a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a b. (Integral a, Num b) => a -> b
fi ((a
h a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a b. (Integral a, Num b) => a -> b
fi a
i) a -> a -> a
forall a. Integral a => a -> a -> a
`div` a -> a -> a
forall a. Ord a => a -> a -> a
max a
1 (Int -> a
forall a b. (Integral a, Num b) => a -> b
fi (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws))
              esize :: a -> a -> b
esize a
k a
h = a -> b
forall a b. (Integral a, Num b) => a -> b
fi (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
$ a -> (Int -> a) -> Maybe Int -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
k (\Int
i -> a -> a -> Int -> a
forall {a} {a} {a}.
(Integral a, Integral a, Num a) =>
a -> a -> a -> a
loc a
k a
h (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) a -> a -> a
forall a. Num a => a -> a -> a
- a -> a -> Int -> a
forall {a} {a} {a}.
(Integral a, Integral a, Num a) =>
a -> a -> a -> a
loc a
k a
h Int
i) (Maybe Int -> a) -> Maybe Int -> a
forall a b. (a -> b) -> a -> b
$ a
w a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
`elemIndex` [a]
ws
              wid :: Dimension
wid = Position -> Dimension -> Dimension
forall {a} {a} {b}. (Integral a, Integral a, Num b) => a -> a -> b
esize Position
x Dimension
wh
              n :: a -> a -> a
n a
k a
h = a -> (Int -> a) -> Maybe Int -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
k (a -> a -> Int -> a
forall {a} {a} {a}.
(Integral a, Integral a, Num a) =>
a -> a -> a -> a
loc a
k a
h) (Maybe Int -> a) -> Maybe Int -> a
forall a b. (a -> b) -> a -> b
$ a
w a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
`elemIndex` [a]
ws
              nx :: Position
nx = Position -> Dimension -> Position
forall {a} {a}. (Integral a, Num a) => a -> a -> a
n Position
x Dimension
wh
              upperTab :: Rectangle
upperTab = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
nx  Position
y Dimension
wid (Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht)
              lowerTab :: Rectangle
lowerTab = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
nx (Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi (Dimension
hh Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
ht)) Dimension
wid (Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht)
              fixHeightLoc :: a -> Position
fixHeightLoc a
i = Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht Position -> Position -> Position
forall a. Num a => a -> a -> a
* a -> Position
forall a b. (Integral a, Num b) => a -> b
fi a
i
              fixHeightTab :: Position -> Rectangle
fixHeightTab Position
k = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
k
                (Position -> (Int -> Position) -> Maybe Int -> Position
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Position
y Int -> Position
forall {a}. Integral a => a -> Position
fixHeightLoc
                 (Maybe Int -> Position) -> Maybe Int -> Position
forall a b. (a -> b) -> a -> b
$ a
w a -> [a] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
`elemIndex` [a]
ws) (Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
wt) (Dimension -> Dimension
forall a b. (Integral a, Num b) => a -> b
fi Dimension
ht)
              rightTab :: Rectangle
rightTab = Position -> Rectangle
fixHeightTab (Position
x Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi (Dimension
wh Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
wt))
              leftTab :: Rectangle
leftTab = Position -> Rectangle
fixHeightTab Position
x
              numWindows :: Int
numWindows = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ws
    shrink :: TabbedDecoration a -> Rectangle -> Rectangle -> Rectangle
shrink (Tabbed Direction2D
loc TabbarShown
_ ) (Rectangle Position
_ Position
_ Dimension
dw Dimension
dh) (Rectangle Position
x Position
y Dimension
w Dimension
h)
        = case Direction2D
loc of
            Direction2D
U -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x (Position
y Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
dh) Dimension
w (Dimension
h Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
dh)
            Direction2D
D -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y Dimension
w (Dimension
h Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
dh)
            Direction2D
L -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
x Position -> Position -> Position
forall a. Num a => a -> a -> a
+ Dimension -> Position
forall a b. (Integral a, Num b) => a -> b
fi Dimension
dw) Position
y (Dimension
w Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
dw) Dimension
h
            Direction2D
R -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y (Dimension
w Dimension -> Dimension -> Dimension
forall a. Num a => a -> a -> a
- Dimension
dw) Dimension
h