----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Hooks.CustomRestart
-- Copyright   :  (c) Jan Vornberger 2009
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  jan.vornberger@informatik.uni-oldenburg.de
-- Stability   :  unstable
-- Portability :  not portable
--
-----------------------------------------------------------------------------

module XMonad.Hooks.CustomRestart
    ( CustomRestart (..)
    , customRestartEventHook
    ) where

import Control.Monad (when)
import Data.Monoid

import XMonad

data CustomRestart = CustomRestart deriving ( Show, Read )

customRestartEventHook :: String -> Event -> X All
customRestartEventHook prog (ClientMessageEvent {ev_message_type = mt}) = do
        d <- asks display
        a <- io $ internAtom d "XMONAD_CUSTOM_RESTART" False
        when (mt == a) $ do
            restart prog True
        return (All True)
customRestartEventHook _ _ = return (All True)