{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
module XMonad.Layout.DecorationEx.TabbedGeometry (
textTabbed,
TabbedGeometry (..),
HorizontalTabPlacement (..),
VerticalTabPlacement (..),
HorizontalTabWidth (..),
HorizontalTabsAlignment (..),
SingleTabMode (..)
) where
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Prelude
import XMonad.Layout.Decoration (ModifiedLayout, Shrinker (..))
import XMonad.Layout.DecorationEx.LayoutModifier
import XMonad.Layout.DecorationEx.Common
import XMonad.Layout.DecorationEx.Geometry
import XMonad.Layout.DecorationEx.Widgets
import XMonad.Layout.DecorationEx.TextEngine
data HorizontalTabPlacement = Top | Bottom
deriving (HorizontalTabPlacement -> HorizontalTabPlacement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HorizontalTabPlacement -> HorizontalTabPlacement -> Bool
$c/= :: HorizontalTabPlacement -> HorizontalTabPlacement -> Bool
== :: HorizontalTabPlacement -> HorizontalTabPlacement -> Bool
$c== :: HorizontalTabPlacement -> HorizontalTabPlacement -> Bool
Eq, ReadPrec [HorizontalTabPlacement]
ReadPrec HorizontalTabPlacement
Int -> ReadS HorizontalTabPlacement
ReadS [HorizontalTabPlacement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HorizontalTabPlacement]
$creadListPrec :: ReadPrec [HorizontalTabPlacement]
readPrec :: ReadPrec HorizontalTabPlacement
$creadPrec :: ReadPrec HorizontalTabPlacement
readList :: ReadS [HorizontalTabPlacement]
$creadList :: ReadS [HorizontalTabPlacement]
readsPrec :: Int -> ReadS HorizontalTabPlacement
$creadsPrec :: Int -> ReadS HorizontalTabPlacement
Read, Int -> HorizontalTabPlacement -> ShowS
[HorizontalTabPlacement] -> ShowS
HorizontalTabPlacement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HorizontalTabPlacement] -> ShowS
$cshowList :: [HorizontalTabPlacement] -> ShowS
show :: HorizontalTabPlacement -> String
$cshow :: HorizontalTabPlacement -> String
showsPrec :: Int -> HorizontalTabPlacement -> ShowS
$cshowsPrec :: Int -> HorizontalTabPlacement -> ShowS
Show)
data VerticalTabPlacement = TabsAtLeft | TabsAtRight
deriving (VerticalTabPlacement -> VerticalTabPlacement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerticalTabPlacement -> VerticalTabPlacement -> Bool
$c/= :: VerticalTabPlacement -> VerticalTabPlacement -> Bool
== :: VerticalTabPlacement -> VerticalTabPlacement -> Bool
$c== :: VerticalTabPlacement -> VerticalTabPlacement -> Bool
Eq, ReadPrec [VerticalTabPlacement]
ReadPrec VerticalTabPlacement
Int -> ReadS VerticalTabPlacement
ReadS [VerticalTabPlacement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VerticalTabPlacement]
$creadListPrec :: ReadPrec [VerticalTabPlacement]
readPrec :: ReadPrec VerticalTabPlacement
$creadPrec :: ReadPrec VerticalTabPlacement
readList :: ReadS [VerticalTabPlacement]
$creadList :: ReadS [VerticalTabPlacement]
readsPrec :: Int -> ReadS VerticalTabPlacement
$creadsPrec :: Int -> ReadS VerticalTabPlacement
Read, Int -> VerticalTabPlacement -> ShowS
[VerticalTabPlacement] -> ShowS
VerticalTabPlacement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerticalTabPlacement] -> ShowS
$cshowList :: [VerticalTabPlacement] -> ShowS
show :: VerticalTabPlacement -> String
$cshow :: VerticalTabPlacement -> String
showsPrec :: Int -> VerticalTabPlacement -> ShowS
$cshowsPrec :: Int -> VerticalTabPlacement -> ShowS
Show)
data HorizontalTabWidth =
AutoWidth
| FixedWidth !Dimension
deriving (HorizontalTabWidth -> HorizontalTabWidth -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HorizontalTabWidth -> HorizontalTabWidth -> Bool
$c/= :: HorizontalTabWidth -> HorizontalTabWidth -> Bool
== :: HorizontalTabWidth -> HorizontalTabWidth -> Bool
$c== :: HorizontalTabWidth -> HorizontalTabWidth -> Bool
Eq, ReadPrec [HorizontalTabWidth]
ReadPrec HorizontalTabWidth
Int -> ReadS HorizontalTabWidth
ReadS [HorizontalTabWidth]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HorizontalTabWidth]
$creadListPrec :: ReadPrec [HorizontalTabWidth]
readPrec :: ReadPrec HorizontalTabWidth
$creadPrec :: ReadPrec HorizontalTabWidth
readList :: ReadS [HorizontalTabWidth]
$creadList :: ReadS [HorizontalTabWidth]
readsPrec :: Int -> ReadS HorizontalTabWidth
$creadsPrec :: Int -> ReadS HorizontalTabWidth
Read, Int -> HorizontalTabWidth -> ShowS
[HorizontalTabWidth] -> ShowS
HorizontalTabWidth -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HorizontalTabWidth] -> ShowS
$cshowList :: [HorizontalTabWidth] -> ShowS
show :: HorizontalTabWidth -> String
$cshow :: HorizontalTabWidth -> String
showsPrec :: Int -> HorizontalTabWidth -> ShowS
$cshowsPrec :: Int -> HorizontalTabWidth -> ShowS
Show)
data HorizontalTabsAlignment = AlignTabsLeft | AlignTabsCenter | AlignTabsRight
deriving (HorizontalTabsAlignment -> HorizontalTabsAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HorizontalTabsAlignment -> HorizontalTabsAlignment -> Bool
$c/= :: HorizontalTabsAlignment -> HorizontalTabsAlignment -> Bool
== :: HorizontalTabsAlignment -> HorizontalTabsAlignment -> Bool
$c== :: HorizontalTabsAlignment -> HorizontalTabsAlignment -> Bool
Eq, ReadPrec [HorizontalTabsAlignment]
ReadPrec HorizontalTabsAlignment
Int -> ReadS HorizontalTabsAlignment
ReadS [HorizontalTabsAlignment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HorizontalTabsAlignment]
$creadListPrec :: ReadPrec [HorizontalTabsAlignment]
readPrec :: ReadPrec HorizontalTabsAlignment
$creadPrec :: ReadPrec HorizontalTabsAlignment
readList :: ReadS [HorizontalTabsAlignment]
$creadList :: ReadS [HorizontalTabsAlignment]
readsPrec :: Int -> ReadS HorizontalTabsAlignment
$creadsPrec :: Int -> ReadS HorizontalTabsAlignment
Read, Int -> HorizontalTabsAlignment -> ShowS
[HorizontalTabsAlignment] -> ShowS
HorizontalTabsAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HorizontalTabsAlignment] -> ShowS
$cshowList :: [HorizontalTabsAlignment] -> ShowS
show :: HorizontalTabsAlignment -> String
$cshow :: HorizontalTabsAlignment -> String
showsPrec :: Int -> HorizontalTabsAlignment -> ShowS
$cshowsPrec :: Int -> HorizontalTabsAlignment -> ShowS
Show)
data SingleTabMode = ShowTab | HideTab
deriving (SingleTabMode -> SingleTabMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleTabMode -> SingleTabMode -> Bool
$c/= :: SingleTabMode -> SingleTabMode -> Bool
== :: SingleTabMode -> SingleTabMode -> Bool
$c== :: SingleTabMode -> SingleTabMode -> Bool
Eq, ReadPrec [SingleTabMode]
ReadPrec SingleTabMode
Int -> ReadS SingleTabMode
ReadS [SingleTabMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SingleTabMode]
$creadListPrec :: ReadPrec [SingleTabMode]
readPrec :: ReadPrec SingleTabMode
$creadPrec :: ReadPrec SingleTabMode
readList :: ReadS [SingleTabMode]
$creadList :: ReadS [SingleTabMode]
readsPrec :: Int -> ReadS SingleTabMode
$creadsPrec :: Int -> ReadS SingleTabMode
Read, Int -> SingleTabMode -> ShowS
[SingleTabMode] -> ShowS
SingleTabMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SingleTabMode] -> ShowS
$cshowList :: [SingleTabMode] -> ShowS
show :: SingleTabMode -> String
$cshow :: SingleTabMode -> String
showsPrec :: Int -> SingleTabMode -> ShowS
$cshowsPrec :: Int -> SingleTabMode -> ShowS
Show)
data TabbedGeometry a =
HorizontalTabs {
forall a. TabbedGeometry a -> SingleTabMode
showIfSingleWindow :: !SingleTabMode
, forall a. TabbedGeometry a -> HorizontalTabPlacement
hTabPlacement :: !HorizontalTabPlacement
, forall a. TabbedGeometry a -> HorizontalTabsAlignment
hTabAlignment :: !HorizontalTabsAlignment
, forall a. TabbedGeometry a -> HorizontalTabWidth
hTabWidth :: !HorizontalTabWidth
, forall a. TabbedGeometry a -> Dimension
hTabHeight :: !Dimension
}
| VerticalTabs {
showIfSingleWindow :: !SingleTabMode
, forall a. TabbedGeometry a -> VerticalTabPlacement
vTabPlacement :: !VerticalTabPlacement
, forall a. TabbedGeometry a -> Dimension
vTabWidth :: !Dimension
, forall a. TabbedGeometry a -> Dimension
vTabHeight :: !Dimension
}
deriving (Int -> TabbedGeometry a -> ShowS
forall a. Int -> TabbedGeometry a -> ShowS
forall a. [TabbedGeometry a] -> ShowS
forall a. TabbedGeometry a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TabbedGeometry a] -> ShowS
$cshowList :: forall a. [TabbedGeometry a] -> ShowS
show :: TabbedGeometry a -> String
$cshow :: forall a. TabbedGeometry a -> String
showsPrec :: Int -> TabbedGeometry a -> ShowS
$cshowsPrec :: forall a. Int -> TabbedGeometry a -> ShowS
Show, ReadPrec [TabbedGeometry a]
ReadPrec (TabbedGeometry a)
ReadS [TabbedGeometry a]
forall a. ReadPrec [TabbedGeometry a]
forall a. ReadPrec (TabbedGeometry a)
forall a. Int -> ReadS (TabbedGeometry a)
forall a. ReadS [TabbedGeometry a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TabbedGeometry a]
$creadListPrec :: forall a. ReadPrec [TabbedGeometry a]
readPrec :: ReadPrec (TabbedGeometry a)
$creadPrec :: forall a. ReadPrec (TabbedGeometry a)
readList :: ReadS [TabbedGeometry a]
$creadList :: forall a. ReadS [TabbedGeometry a]
readsPrec :: Int -> ReadS (TabbedGeometry a)
$creadsPrec :: forall a. Int -> ReadS (TabbedGeometry a)
Read)
instance Default (TabbedGeometry a) where
def :: TabbedGeometry a
def = forall a.
SingleTabMode
-> HorizontalTabPlacement
-> HorizontalTabsAlignment
-> HorizontalTabWidth
-> Dimension
-> TabbedGeometry a
HorizontalTabs SingleTabMode
ShowTab HorizontalTabPlacement
Top HorizontalTabsAlignment
AlignTabsLeft HorizontalTabWidth
AutoWidth Dimension
20
instance DecorationGeometry TabbedGeometry Window where
describeGeometry :: TabbedGeometry Window -> String
describeGeometry TabbedGeometry Window
_ = String
"Tabbed"
pureDecoration :: TabbedGeometry Window
-> Rectangle
-> Stack Window
-> [(Window, Rectangle)]
-> (Window, Rectangle)
-> Maybe Rectangle
pureDecoration TabbedGeometry Window
tabs Rectangle
_ Stack Window
stack [(Window, Rectangle)]
wrs (Window
window, Rectangle
windowRect) =
let Rectangle Position
windowX Position
windowY Dimension
windowWidth Dimension
windowHeight = Rectangle
windowRect
tabbedWindows :: [Window]
tabbedWindows = forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst (forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
==Rectangle
windowRect) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(Window, Rectangle)]
wrs)) (forall a. Stack a -> [a]
W.integrate Stack Window
stack)
mbWindowIndex :: Maybe Int
mbWindowIndex = Window
window forall a. Eq a => a -> [a] -> Maybe Int
`elemIndex` [Window]
tabbedWindows
numWindows :: Int
numWindows = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Window]
tabbedWindows
in if Int
numWindows forall a. Ord a => a -> a -> Bool
> Int
1 Bool -> Bool -> Bool
|| (forall a. TabbedGeometry a -> SingleTabMode
showIfSingleWindow TabbedGeometry Window
tabs forall a. Eq a => a -> a -> Bool
== SingleTabMode
ShowTab Bool -> Bool -> Bool
&& Int
numWindows forall a. Ord a => a -> a -> Bool
> Int
0)
then
case TabbedGeometry Window
tabs of
HorizontalTabs {Dimension
SingleTabMode
HorizontalTabsAlignment
HorizontalTabWidth
HorizontalTabPlacement
hTabHeight :: Dimension
hTabWidth :: HorizontalTabWidth
hTabAlignment :: HorizontalTabsAlignment
hTabPlacement :: HorizontalTabPlacement
showIfSingleWindow :: SingleTabMode
hTabHeight :: forall a. TabbedGeometry a -> Dimension
hTabWidth :: forall a. TabbedGeometry a -> HorizontalTabWidth
hTabAlignment :: forall a. TabbedGeometry a -> HorizontalTabsAlignment
hTabPlacement :: forall a. TabbedGeometry a -> HorizontalTabPlacement
showIfSingleWindow :: forall a. TabbedGeometry a -> SingleTabMode
..} ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ case HorizontalTabPlacement
hTabPlacement of
HorizontalTabPlacement
Top -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
decoX Position
windowY Dimension
effectiveTabWidth Dimension
hTabHeight
HorizontalTabPlacement
Bottom -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
decoX (Position
windowY forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi (Dimension
windowHeight forall a. Num a => a -> a -> a
- Dimension
hTabHeight)) Dimension
effectiveTabWidth Dimension
hTabHeight
where
decoX :: Position
decoX = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Position
windowX Int -> Position
tabX Maybe Int
mbWindowIndex
hTabWidth' :: HorizontalTabWidth
hTabWidth' =
case HorizontalTabWidth
hTabWidth of
HorizontalTabWidth
AutoWidth -> HorizontalTabWidth
AutoWidth
FixedWidth Dimension
tabWidth
| Dimension
tabWidth forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fi Int
numWindows forall a. Ord a => a -> a -> Bool
> Dimension
windowWidth -> HorizontalTabWidth
AutoWidth
| Bool
otherwise -> Dimension -> HorizontalTabWidth
FixedWidth Dimension
tabWidth
effectiveTabWidth :: Dimension
effectiveTabWidth =
case HorizontalTabWidth
hTabWidth' of
HorizontalTabWidth
AutoWidth -> forall a b. (Integral a, Num b) => a -> b
fi forall a b. (a -> b) -> a -> b
$ forall b a. b -> (a -> b) -> Maybe a -> b
maybe Position
windowX (\Int
i -> Int -> Position
tabX (Int
iforall a. Num a => a -> a -> a
+Int
1) forall a. Num a => a -> a -> a
- Int -> Position
tabX Int
i) Maybe Int
mbWindowIndex
FixedWidth Dimension
tabWidth -> Dimension
tabWidth
allTabsWidth :: Position
allTabsWidth =
case HorizontalTabWidth
hTabWidth' of
HorizontalTabWidth
AutoWidth -> forall a b. (Integral a, Num b) => a -> b
fi Dimension
windowWidth
FixedWidth Dimension
_ -> forall a b. (Integral a, Num b) => a -> b
fi forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> a -> a
min Dimension
windowWidth forall a b. (a -> b) -> a -> b
$ Dimension
effectiveTabWidth forall a. Num a => a -> a -> a
* forall a. Ord a => a -> a -> a
max Dimension
1 (forall a b. (Integral a, Num b) => a -> b
fi Int
numWindows)
tabsStartX :: Position
tabsStartX =
case HorizontalTabsAlignment
hTabAlignment of
HorizontalTabsAlignment
AlignTabsLeft -> Position
windowX
HorizontalTabsAlignment
AlignTabsRight -> Position
windowX forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi Dimension
windowWidth forall a. Num a => a -> a -> a
- Position
allTabsWidth
HorizontalTabsAlignment
AlignTabsCenter -> Position
windowX forall a. Num a => a -> a -> a
+ (forall a b. (Integral a, Num b) => a -> b
fi Dimension
windowWidth forall a. Num a => a -> a -> a
- Position
allTabsWidth) forall a. Integral a => a -> a -> a
`div` Position
2
tabX :: Int -> Position
tabX Int
i = Position
tabsStartX forall a. Num a => a -> a -> a
+
case HorizontalTabWidth
hTabWidth' of
HorizontalTabWidth
AutoWidth -> forall a b. (Integral a, Num b) => a -> b
fi ((Dimension
windowWidth forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fi Int
i) forall a. Integral a => a -> a -> a
`div` forall a. Ord a => a -> a -> a
max Dimension
1 (forall a b. (Integral a, Num b) => a -> b
fi Int
numWindows))
FixedWidth Dimension
_ -> forall a b. (Integral a, Num b) => a -> b
fi Dimension
effectiveTabWidth forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fi Int
i
VerticalTabs {Dimension
SingleTabMode
VerticalTabPlacement
vTabHeight :: Dimension
vTabWidth :: Dimension
vTabPlacement :: VerticalTabPlacement
showIfSingleWindow :: SingleTabMode
vTabHeight :: forall a. TabbedGeometry a -> Dimension
vTabWidth :: forall a. TabbedGeometry a -> Dimension
vTabPlacement :: forall a. TabbedGeometry a -> VerticalTabPlacement
showIfSingleWindow :: forall a. TabbedGeometry a -> SingleTabMode
..} ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ case VerticalTabPlacement
vTabPlacement of
VerticalTabPlacement
TabsAtLeft -> Position -> Rectangle
fixHeightTab Position
windowX
VerticalTabPlacement
TabsAtRight -> Position -> Rectangle
fixHeightTab (Position
windowX forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi (Dimension
windowWidth forall a. Num a => a -> a -> a
- Dimension
vTabWidth))
where
fixHeightLoc :: Int -> Position
fixHeightLoc Int
i = Position
windowY forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi Dimension
vTabHeight forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fi Int
i
fixHeightTab :: Position -> Rectangle
fixHeightTab Position
x = Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x
(forall b a. b -> (a -> b) -> Maybe a -> b
maybe Position
windowY Int -> Position
fixHeightLoc Maybe Int
mbWindowIndex) Dimension
vTabWidth Dimension
vTabHeight
else forall a. Maybe a
Nothing
shrinkWindow :: TabbedGeometry Window -> Rectangle -> Rectangle -> Rectangle
shrinkWindow TabbedGeometry Window
tabs (Rectangle Position
_ Position
_ Dimension
dw Dimension
dh) (Rectangle Position
x Position
y Dimension
w Dimension
h) =
case TabbedGeometry Window
tabs of
HorizontalTabs {Dimension
SingleTabMode
HorizontalTabsAlignment
HorizontalTabWidth
HorizontalTabPlacement
hTabHeight :: Dimension
hTabWidth :: HorizontalTabWidth
hTabAlignment :: HorizontalTabsAlignment
hTabPlacement :: HorizontalTabPlacement
showIfSingleWindow :: SingleTabMode
hTabHeight :: forall a. TabbedGeometry a -> Dimension
hTabWidth :: forall a. TabbedGeometry a -> HorizontalTabWidth
hTabAlignment :: forall a. TabbedGeometry a -> HorizontalTabsAlignment
hTabPlacement :: forall a. TabbedGeometry a -> HorizontalTabPlacement
showIfSingleWindow :: forall a. TabbedGeometry a -> SingleTabMode
..} ->
case HorizontalTabPlacement
hTabPlacement of
HorizontalTabPlacement
Top -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x (Position
y forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi Dimension
dh) Dimension
w (Dimension
h forall a. Num a => a -> a -> a
- Dimension
dh)
HorizontalTabPlacement
Bottom -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y Dimension
w (Dimension
h forall a. Num a => a -> a -> a
- Dimension
dh)
VerticalTabs {Dimension
SingleTabMode
VerticalTabPlacement
vTabHeight :: Dimension
vTabWidth :: Dimension
vTabPlacement :: VerticalTabPlacement
showIfSingleWindow :: SingleTabMode
vTabHeight :: forall a. TabbedGeometry a -> Dimension
vTabWidth :: forall a. TabbedGeometry a -> Dimension
vTabPlacement :: forall a. TabbedGeometry a -> VerticalTabPlacement
showIfSingleWindow :: forall a. TabbedGeometry a -> SingleTabMode
..} ->
case VerticalTabPlacement
vTabPlacement of
VerticalTabPlacement
TabsAtLeft -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle (Position
x forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fi Dimension
dw) Position
y (Dimension
w forall a. Num a => a -> a -> a
- Dimension
dw) Dimension
h
VerticalTabPlacement
TabsAtRight -> Position -> Position -> Dimension -> Dimension -> Rectangle
Rectangle Position
x Position
y (Dimension
w forall a. Num a => a -> a -> a
- Dimension
dw) Dimension
h
textTabbed :: (Shrinker shrinker)
=> shrinker
-> ThemeEx StandardWidget
-> l Window
-> ModifiedLayout (DecorationEx TextDecoration StandardWidget TabbedGeometry shrinker) l Window
textTabbed :: forall shrinker (l :: * -> *).
Shrinker shrinker =>
shrinker
-> ThemeEx StandardWidget
-> l Window
-> ModifiedLayout
(DecorationEx
TextDecoration StandardWidget TabbedGeometry shrinker)
l
Window
textTabbed shrinker
shrinker ThemeEx StandardWidget
theme = forall (engine :: * -> * -> *) widget a (geom :: * -> *) shrinker
(l :: * -> *).
(DecorationEngine engine widget a, DecorationGeometry geom a,
Shrinker shrinker) =>
shrinker
-> Theme engine widget
-> engine widget a
-> geom a
-> l a
-> ModifiedLayout (DecorationEx engine widget geom shrinker) l a
decorationEx shrinker
shrinker ThemeEx StandardWidget
theme forall widget a. TextDecoration widget a
TextDecoration forall a. Default a => a
def