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:
Don Stewart
2008-02-06 19:48:58 +00:00
parent 261f742404
commit 695860f1fd
2 changed files with 14 additions and 5 deletions

View File

@@ -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)
------------------------------------------------------------------------