mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
According to its documentation[1], this module simply re-exports Control.Exception on recent GHC versions. As we only support recent versions, this import is unnecessary. [1] http://hackage.haskell.org/package/extensible-exceptions-0.1.1.4/docs/Control-Exception-Extensible.html
31 lines
1001 B
Haskell
31 lines
1001 B
Haskell
module Properties.Failure where
|
|
|
|
import XMonad.StackSet hiding (filter)
|
|
|
|
import qualified Control.Exception as C
|
|
import System.IO.Unsafe
|
|
import Data.List (isPrefixOf)
|
|
|
|
-- ---------------------------------------------------------------------
|
|
-- testing for failure and help out hpc
|
|
--
|
|
-- Since base 4.9.0.0 `error` appends a stack trace. The tests below
|
|
-- use `isPrefixOf` to only test equality on the error message.
|
|
--
|
|
prop_abort :: Int -> Bool
|
|
prop_abort _ = unsafePerformIO $ C.catch (abort "fail") check
|
|
where
|
|
check (C.SomeException e) =
|
|
return $ "xmonad: StackSet: fail" `isPrefixOf` show e
|
|
|
|
-- new should fail with an abort
|
|
prop_new_abort :: Int -> Bool
|
|
prop_new_abort _ = unsafePerformIO $ C.catch f check
|
|
where
|
|
f = new undefined{-layout-} [] [] `seq` return False
|
|
check (C.SomeException e) =
|
|
return $ "xmonad: StackSet: non-positive argument to StackSet.new" `isPrefixOf` show e
|
|
|
|
-- TODO: Fix this?
|
|
-- prop_view_should_fail = view {- with some bogus data -}
|