mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
depend on data-default, and deprecate the monomorphic name defaultConfig
This commit is contained in:
parent
8f039ec434
commit
ec1a20c727
2
Main.hs
2
Main.hs
@ -37,7 +37,7 @@ main :: IO ()
|
||||
main = do
|
||||
installSignalHandlers -- important to ignore SIGCHLD to avoid zombies
|
||||
args <- getArgs
|
||||
let launch = catchIO buildLaunch >> xmonad defaultConfig
|
||||
let launch = catchIO buildLaunch >> xmonad def
|
||||
case args of
|
||||
[] -> launch
|
||||
("--resume":_) -> launch
|
||||
|
@ -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:",
|
||||
|
@ -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)
|
||||
|
@ -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
|
||||
|
@ -258,7 +258,7 @@ main = xmonad defaults
|
||||
--
|
||||
-- No need to modify this.
|
||||
--
|
||||
defaults = defaultConfig {
|
||||
defaults = def {
|
||||
-- simple stuff
|
||||
terminal = myTerminal,
|
||||
focusFollowsMouse = myFocusFollowsMouse,
|
||||
|
@ -58,7 +58,8 @@ library
|
||||
else
|
||||
build-depends: base < 3
|
||||
build-depends: X11>=1.5 && < 1.7, mtl, unix,
|
||||
utf8-string >= 0.3 && < 0.4
|
||||
utf8-string >= 0.3 && < 0.4,
|
||||
data-default
|
||||
|
||||
if true
|
||||
ghc-options: -funbox-strict-fields -Wall
|
||||
|
Loading…
x
Reference in New Issue
Block a user