diff options
Diffstat (limited to 'XMonad')
-rw-r--r-- | XMonad/Config.hs | 17 | ||||
-rw-r--r-- | XMonad/Core.hs | 7 | ||||
-rw-r--r-- | XMonad/Main.hsc | 4 |
3 files changed, 21 insertions, 7 deletions
diff --git a/XMonad/Config.hs b/XMonad/Config.hs index cbfb06e..9aaab8f 100644 --- a/XMonad/Config.hs +++ b/XMonad/Config.hs @@ -1,4 +1,5 @@ -{-# OPTIONS -fno-warn-missing-signatures #-} +{-# OPTIONS -fno-warn-missing-signatures -fno-warn-orphans #-} +{-# LANGUAGE TypeFamilies #-} ----------------------------------------------------------------------------- -- | -- Module : XMonad.Config @@ -13,13 +14,13 @@ -- -- DO NOT MODIFY THIS FILE! It won't work. You may configure xmonad -- by providing your own @~\/.xmonad\/xmonad.hs@ that overrides --- specific fields in 'defaultConfig'. For a starting point, you can +-- specific fields in the default config, 'def'. For a starting point, you can -- copy the @xmonad.hs@ found in the @man@ directory, or look at -- examples on the xmonad wiki. -- ------------------------------------------------------------------------ -module XMonad.Config (defaultConfig) where +module XMonad.Config (defaultConfig, Default(..)) where -- -- Useful imports @@ -38,6 +39,7 @@ import XMonad.Operations import XMonad.ManageHook import qualified XMonad.StackSet as W import Data.Bits ((.|.)) +import Data.Default import Data.Monoid import qualified Data.Map as M import System.Exit @@ -250,8 +252,8 @@ mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList -- you may also bind events to the mouse scroll wheel (button4 and button5) ] --- | The default set of configuration values itself -defaultConfig = XConfig +instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) where + def = XConfig { XMonad.borderWidth = borderWidth , XMonad.workspaces = workspaces , XMonad.layoutHook = layout @@ -271,6 +273,11 @@ defaultConfig = XConfig , XMonad.rootMask = rootMask } +-- | The default set of configuration values itself +{-# DEPRECATED defaultConfig "Use def (from Data.Default, and re-exported by XMonad and XMonad.Config) instead." #-} +defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full)) +defaultConfig = def + -- | Finally, a copy of the default bindings in simple textual tabular format. help :: String help = unlines ["The default modifier key is 'alt'. Default keybindings:", diff --git a/XMonad/Core.hs b/XMonad/Core.hs index 569f9f9..112d1e4 100644 --- a/XMonad/Core.hs +++ b/XMonad/Core.hs @@ -37,6 +37,7 @@ import Control.Exception.Extensible (catch, fromException, try, bracket, throw, import Control.Applicative import Control.Monad.State import Control.Monad.Reader +import Data.Default import System.FilePath import System.IO import System.Info @@ -149,6 +150,9 @@ instance (Monoid a) => Monoid (X a) where mempty = return mempty mappend = liftM2 mappend +instance Default a => Default (X a) where + def = return def + type ManageHook = Query (Endo WindowSet) newtype Query a = Query (ReaderT Window X a) deriving (Functor, Monad, MonadReader Window, MonadIO) @@ -160,6 +164,9 @@ instance Monoid a => Monoid (Query a) where mempty = return mempty mappend = liftM2 mappend +instance Default a => Default (Query a) where + def = return def + -- | Run the 'X' monad, given a chunk of 'X' monad code, and an initial state -- Return the result, and final state runX :: XConf -> XState -> X a -> IO (a, XState) diff --git a/XMonad/Main.hsc b/XMonad/Main.hsc index 8410a0c..5d59042 100644 --- a/XMonad/Main.hsc +++ b/XMonad/Main.hsc @@ -85,11 +85,11 @@ xmonad initxmc = do xinesc <- getCleanedScreenInfo dpy nbc <- do v <- initColor dpy $ normalBorderColor xmc - ~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig + ~(Just nbc_) <- initColor dpy $ normalBorderColor Default.def return (fromMaybe nbc_ v) fbc <- do v <- initColor dpy $ focusedBorderColor xmc - ~(Just fbc_) <- initColor dpy $ focusedBorderColor Default.defaultConfig + ~(Just fbc_) <- initColor dpy $ focusedBorderColor Default.def return (fromMaybe fbc_ v) hSetBuffering stdout NoBuffering |