mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 20:51:55 -07:00
Lift initColor exceptions into Maybe
We should audit all X11 Haskell lib calls we make for whether they throw undocumented exceptions, and then banish that.
This commit is contained in:
@@ -28,6 +28,7 @@ import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
|
||||
import Graphics.X11.Xlib.Extras
|
||||
|
||||
import XMonad.Core
|
||||
import qualified XMonad.Config as Default
|
||||
import XMonad.StackSet (new, floating, member)
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Operations
|
||||
@@ -46,8 +47,14 @@ xmonad initxmc = do
|
||||
|
||||
rootw <- rootWindow dpy dflt
|
||||
xinesc <- getCleanedScreenInfo dpy
|
||||
nbc <- initColor dpy $ normalBorderColor xmc
|
||||
fbc <- initColor dpy $ focusedBorderColor xmc
|
||||
nbc <- do v <- initColor dpy $ normalBorderColor xmc
|
||||
~(Just nbc_) <- initColor dpy $ normalBorderColor Default.defaultConfig
|
||||
return (fromMaybe nbc_ v)
|
||||
|
||||
fbc <- do v <- initColor dpy $ focusedBorderColor xmc
|
||||
~(Just fbc_) <- initColor dpy $ focusedBorderColor Default.defaultConfig
|
||||
return (fromMaybe fbc_ v)
|
||||
|
||||
hSetBuffering stdout NoBuffering
|
||||
args <- getArgs
|
||||
|
||||
|
@@ -31,8 +31,9 @@ import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
|
||||
import Control.Applicative
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import qualified Control.Exception as C
|
||||
|
||||
import System.IO
|
||||
import Graphics.X11.Xlib
|
||||
@@ -381,8 +382,9 @@ cleanMask km = do
|
||||
return (complement (nlm .|. lockMask) .&. km)
|
||||
|
||||
-- | Get the Pixel value for a named color
|
||||
initColor :: Display -> String -> IO Pixel
|
||||
initColor dpy c = (color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
initColor :: Display -> String -> IO (Maybe Pixel)
|
||||
initColor dpy c = C.handle (\_ -> return Nothing) $
|
||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||
where colormap = defaultColormap dpy (defaultScreen dpy)
|
||||
|
||||
------------------------------------------------------------------------
|
||||
|
Reference in New Issue
Block a user