clean up some weird formatting/overboard strictness annotations

This commit is contained in:
Don Stewart 2007-11-05 01:14:00 +00:00
parent d1c29a40cf
commit 934fb2c368

View File

@ -62,19 +62,21 @@ data XConf = XConf
} }
-- todo, better name -- todo, better name
data XConfig = XConfig { normalBorderColor :: !String data XConfig = XConfig
, focusedBorderColor :: !String { normalBorderColor :: !String
, terminal :: !String , focusedBorderColor :: !String
, layoutHook :: !(Layout Window) , terminal :: !String
, manageHook :: !(Window -> String -> String -> String -> X (WindowSet -> WindowSet)) , layoutHook :: !(Layout Window)
, workspaces :: ![String] , manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet)
, defaultGaps :: ![(Int,Int,Int,Int)] , workspaces :: [String]
, numlockMask :: !KeyMask , defaultGaps :: [(Int,Int,Int,Int)]
, modMask :: !KeyMask , numlockMask :: !KeyMask
, keys :: !(XConfig -> M.Map (ButtonMask,KeySym) (X ())) , modMask :: !KeyMask
, mouseBindings :: !(XConfig -> M.Map (ButtonMask, Button) (Window -> X ())) , keys :: XConfig -> M.Map (ButtonMask,KeySym) (X ())
, borderWidth :: !Dimension , mouseBindings :: XConfig -> M.Map (ButtonMask, Button) (Window -> X ())
, logHook :: !(X ()) } , borderWidth :: !Dimension
, logHook :: X ()
}
type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail type WindowSet = StackSet WorkspaceId (Layout Window) Window ScreenId ScreenDetail
type WindowSpace = Workspace WorkspaceId (Layout Window) Window type WindowSpace = Workspace WorkspaceId (Layout Window) Window
@ -113,8 +115,7 @@ catchX :: X a -> X a -> X a
catchX job errcase = do catchX job errcase = do
st <- get st <- get
c <- ask c <- ask
(a, s') <- io $ runX c st job `catch` (a, s') <- io $ runX c st job `catch` \e -> case e of
\e -> case e of
ExitException {} -> throw e ExitException {} -> throw e
_ -> do hPrint stderr e; runX c st errcase _ -> do hPrint stderr e; runX c st errcase
put s' put s'