module XMonad.Layout.ImageButtonDecoration
    ( 
      
      imageButtonDeco
    , defaultThemeWithImageButtons
    , imageTitleBarButtonHandler
    , ImageButtonDecoration
    ) where
import XMonad
import XMonad.Layout.Decoration
import XMonad.Layout.DecorationAddons
import XMonad.Util.Image
import XMonad.Actions.WindowMenu
import XMonad.Layout.Minimize
import XMonad.Layout.Maximize
buttonSize :: Int
buttonSize = 10
menuButtonOffset :: Int
menuButtonOffset = 4
minimizeButtonOffset :: Int
minimizeButtonOffset = 32
maximizeButtonOffset :: Int
maximizeButtonOffset = 18
closeButtonOffset :: Int
closeButtonOffset = 4
convertToBool' :: [Int] -> [Bool]
convertToBool' = map (\x -> x == 1)
convertToBool :: [[Int]] -> [[Bool]]
convertToBool = map convertToBool'
menuButton' :: [[Int]]
menuButton' = [[1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1]]
menuButton :: [[Bool]]
menuButton = convertToBool menuButton'
miniButton' :: [[Int]]
miniButton' = [[0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [0,0,0,0,0,0,0,0,0,0],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1]]
miniButton :: [[Bool]]
miniButton = convertToBool miniButton'
maxiButton' :: [[Int]]
maxiButton' = [[1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,0,0,0,0,0,0,1,1],
               [1,1,1,1,1,1,1,1,1,1],
               [1,1,1,1,1,1,1,1,1,1]]
maxiButton :: [[Bool]]
maxiButton = convertToBool maxiButton'
closeButton' :: [[Int]]
closeButton' = [[1,1,0,0,0,0,0,0,1,1],
                [1,1,1,0,0,0,0,1,1,1],
                [0,1,1,1,0,0,1,1,1,0],
                [0,0,1,1,1,1,1,1,0,0],
                [0,0,0,1,1,1,1,0,0,0],
                [0,0,0,1,1,1,1,0,0,0],
                [0,0,1,1,1,1,1,1,0,0],
                [0,1,1,1,0,0,1,1,1,0],
                [1,1,1,0,0,0,0,1,1,1],
                [1,1,0,0,0,0,0,0,1,1]]
closeButton :: [[Bool]]
closeButton = convertToBool closeButton'
imageTitleBarButtonHandler :: Window -> Int -> Int -> X Bool
imageTitleBarButtonHandler mainw distFromLeft distFromRight = do
    let action = if (fi distFromLeft >= menuButtonOffset &&
                      fi distFromLeft <= menuButtonOffset + buttonSize)
                        then focus mainw >> windowMenu >> return True
                  else if (fi distFromRight >= closeButtonOffset &&
                           fi distFromRight <= closeButtonOffset + buttonSize)
                              then focus mainw >> kill >> return True
                  else if (fi distFromRight >= maximizeButtonOffset &&
                           fi distFromRight <= maximizeButtonOffset + buttonSize)
                             then focus mainw >> sendMessage (maximizeRestore mainw) >> return True
                  else if (fi distFromRight >= minimizeButtonOffset &&
                           fi distFromRight <= minimizeButtonOffset + buttonSize)
                             then focus mainw >> minimizeWindow mainw >> return True
                  else return False
    action
defaultThemeWithImageButtons :: Theme
defaultThemeWithImageButtons = def {
                                windowTitleIcons = [ (menuButton, CenterLeft 3),
                                                     (closeButton, CenterRight 3),
                                                     (maxiButton, CenterRight 18),
                                                     (miniButton, CenterRight 33) ]
                               }
imageButtonDeco :: (Eq a, Shrinker s) => s -> Theme
                   -> l a -> ModifiedLayout (Decoration ImageButtonDecoration s) l a
imageButtonDeco s c = decoration s c $ NFD True
data ImageButtonDecoration a = NFD Bool deriving (Show, Read)
instance Eq a => DecorationStyle ImageButtonDecoration a where
    describeDeco _ = "ImageButtonDeco"
    decorationCatchClicksHook _ mainw dFL dFR = imageTitleBarButtonHandler mainw dFL dFR
    decorationAfterDraggingHook _ (mainw, _) decoWin = focus mainw >> handleScreenCrossing mainw decoWin >> return ()