{-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.MultiToggle.TabBarDecoration
-- Copyright   :  (c) 2018  Lucian Poston
-- License     :  BSD-style (see LICENSE)
--
-- Maintainer  :  <lucianposton@pm.me>
-- Stability   :  unstable
-- Portability :  unportable
--
-- Provides a simple transformer for use with "XMonad.Layout.MultiToggle" to
-- dynamically toggle "XMonad.Layout.TabBarDecoration".
-----------------------------------------------------------------------------

module XMonad.Layout.MultiToggle.TabBarDecoration (
    SimpleTabBar(..)
) where

import XMonad.Layout.MultiToggle

import XMonad
import XMonad.Layout.LayoutModifier
import XMonad.Layout.TabBarDecoration

-- $usage
-- To use this module with "XMonad.Layout.MultiToggle", add the @SIMPLETABBAR@
-- to your layout For example, from a basic layout like
--
-- > layout = tiled ||| Full
--
-- Add @SIMPLETABBAR@ by changing it this to
--
-- > layout = mkToggle (single SIMPLETABBAR) (tiled ||| Full)
--
-- You can now dynamically toggle the 'XMonad.Layout.TabBarDecoration'
-- transformation by adding a key binding such as @mod-x@ as follows.
--
-- > ...
-- >   , ((modm,               xK_x     ), sendMessage $ Toggle SIMPLETABBAR)
-- > ...

-- | Transformer for "XMonad.Layout.TabBarDecoration".
data SimpleTabBar = SIMPLETABBAR deriving (ReadPrec [SimpleTabBar]
ReadPrec SimpleTabBar
Int -> ReadS SimpleTabBar
ReadS [SimpleTabBar]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleTabBar]
$creadListPrec :: ReadPrec [SimpleTabBar]
readPrec :: ReadPrec SimpleTabBar
$creadPrec :: ReadPrec SimpleTabBar
readList :: ReadS [SimpleTabBar]
$creadList :: ReadS [SimpleTabBar]
readsPrec :: Int -> ReadS SimpleTabBar
$creadsPrec :: Int -> ReadS SimpleTabBar
Read, Int -> SimpleTabBar -> ShowS
[SimpleTabBar] -> ShowS
SimpleTabBar -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleTabBar] -> ShowS
$cshowList :: [SimpleTabBar] -> ShowS
show :: SimpleTabBar -> String
$cshow :: SimpleTabBar -> String
showsPrec :: Int -> SimpleTabBar -> ShowS
$cshowsPrec :: Int -> SimpleTabBar -> ShowS
Show, SimpleTabBar -> SimpleTabBar -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleTabBar -> SimpleTabBar -> Bool
$c/= :: SimpleTabBar -> SimpleTabBar -> Bool
== :: SimpleTabBar -> SimpleTabBar -> Bool
$c== :: SimpleTabBar -> SimpleTabBar -> Bool
Eq)
instance Transformer SimpleTabBar Window where
    transform :: forall (l :: * -> *) b.
LayoutClass l Window =>
SimpleTabBar
-> l Window
-> (forall (l' :: * -> *).
    LayoutClass l' Window =>
    l' Window -> (l' Window -> l Window) -> b)
-> b
transform SimpleTabBar
_ l Window
x forall (l' :: * -> *).
LayoutClass l' Window =>
l' Window -> (l' Window -> l Window) -> b
k = forall (l' :: * -> *).
LayoutClass l' Window =>
l' Window -> (l' Window -> l Window) -> b
k (forall a (l :: * -> *).
Eq a =>
l a
-> ModifiedLayout
     (Decoration TabBarDecoration DefaultShrinker)
     (ModifiedLayout ResizeScreen l)
     a
simpleTabBar l Window
x) (\(ModifiedLayout Decoration TabBarDecoration DefaultShrinker Window
_ (ModifiedLayout ResizeScreen Window
_ l Window
x')) -> l Window
x')