{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.ButtonDecoration
-- Description :  Decoration that includes buttons, executing actions when clicked on.
-- Copyright   :  (c) Jan Vornberger 2009
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  jan.vornberger@informatik.uni-oldenburg.de
-- Stability   :  unstable
-- Portability :  not portable
--
-- A decoration that includes small buttons on both ends which invoke
-- various actions when clicked on: Show a window menu (see
-- "XMonad.Actions.WindowMenu"), minimize, maximize or close the window.
--
-- Note: For maximizing and minimizing to actually work, you will need
-- to integrate "XMonad.Layout.Maximize" and "XMonad.Layout.Minimize" into your
-- setup.  See the documentation of those modules for more information.
--
-----------------------------------------------------------------------------

module XMonad.Layout.ButtonDecoration
    ( -- * Usage:
      -- $usage
      buttonDeco,
      ButtonDecoration,
    ) where

import XMonad
import XMonad.Layout.Decoration
import XMonad.Layout.DecorationAddons

-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.DecorationAddons
-- > import XMonad.Layout.ButtonDecoration
--
-- Then edit your @layoutHook@ by adding the ButtonDecoration to
-- your layout:
--
-- > myL = buttonDeco shrinkText defaultThemeWithButtons (layoutHook def)
-- > main = xmonad def { layoutHook = myL }
--

buttonDeco :: (Eq a, Shrinker s) => s -> Theme
           -> l a -> ModifiedLayout (Decoration ButtonDecoration s) l a
buttonDeco :: forall a s (l :: * -> *).
(Eq a, Shrinker s) =>
s
-> Theme
-> l a
-> ModifiedLayout (Decoration ButtonDecoration s) l a
buttonDeco s
s Theme
c = s
-> Theme
-> ButtonDecoration a
-> l a
-> ModifiedLayout (Decoration ButtonDecoration 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
s Theme
c (ButtonDecoration a
 -> l a -> ModifiedLayout (Decoration ButtonDecoration s) l a)
-> ButtonDecoration a
-> l a
-> ModifiedLayout (Decoration ButtonDecoration s) l a
forall a b. (a -> b) -> a -> b
$ Bool -> ButtonDecoration a
forall a. Bool -> ButtonDecoration a
NFD Bool
True

newtype ButtonDecoration a = NFD Bool deriving (Int -> ButtonDecoration a -> ShowS
[ButtonDecoration a] -> ShowS
ButtonDecoration a -> String
(Int -> ButtonDecoration a -> ShowS)
-> (ButtonDecoration a -> String)
-> ([ButtonDecoration a] -> ShowS)
-> Show (ButtonDecoration a)
forall a. Int -> ButtonDecoration a -> ShowS
forall a. [ButtonDecoration a] -> ShowS
forall a. ButtonDecoration a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ButtonDecoration a] -> ShowS
$cshowList :: forall a. [ButtonDecoration a] -> ShowS
show :: ButtonDecoration a -> String
$cshow :: forall a. ButtonDecoration a -> String
showsPrec :: Int -> ButtonDecoration a -> ShowS
$cshowsPrec :: forall a. Int -> ButtonDecoration a -> ShowS
Show, ReadPrec [ButtonDecoration a]
ReadPrec (ButtonDecoration a)
Int -> ReadS (ButtonDecoration a)
ReadS [ButtonDecoration a]
(Int -> ReadS (ButtonDecoration a))
-> ReadS [ButtonDecoration a]
-> ReadPrec (ButtonDecoration a)
-> ReadPrec [ButtonDecoration a]
-> Read (ButtonDecoration a)
forall a. ReadPrec [ButtonDecoration a]
forall a. ReadPrec (ButtonDecoration a)
forall a. Int -> ReadS (ButtonDecoration a)
forall a. ReadS [ButtonDecoration a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ButtonDecoration a]
$creadListPrec :: forall a. ReadPrec [ButtonDecoration a]
readPrec :: ReadPrec (ButtonDecoration a)
$creadPrec :: forall a. ReadPrec (ButtonDecoration a)
readList :: ReadS [ButtonDecoration a]
$creadList :: forall a. ReadS [ButtonDecoration a]
readsPrec :: Int -> ReadS (ButtonDecoration a)
$creadsPrec :: forall a. Int -> ReadS (ButtonDecoration a)
Read)

instance Eq a => DecorationStyle ButtonDecoration a where
    describeDeco :: ButtonDecoration a -> String
describeDeco ButtonDecoration a
_ = String
"ButtonDeco"
    decorationCatchClicksHook :: ButtonDecoration a -> Window -> Int -> Int -> X Bool
decorationCatchClicksHook ButtonDecoration a
_ = Window -> Int -> Int -> X Bool
titleBarButtonHandler
    decorationAfterDraggingHook :: ButtonDecoration a -> (Window, Rectangle) -> Window -> X ()
decorationAfterDraggingHook ButtonDecoration a
_ (Window
mainw, Rectangle
_) Window
decoWin = Window -> X ()
focus Window
mainw X () -> X Bool -> X Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Window -> Window -> X Bool
handleScreenCrossing Window
mainw Window
decoWin X Bool -> X () -> X ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()