assert-failure-0.1.1.0: Syntactic sugar improving 'assert' and 'error'

Safe HaskellNone
LanguageHaskell2010

Control.Exception.Assert.Sugar

Description

Syntactic sugar that improves the usability of assert and error.

This is actually a bunch of hacks wrapping the original assert function, which is, as of GHC 7.8, the only simple way of obtaining source positions. The original assert function is here re-exported for convenience.

Make sure to enable assertions for your cabal package, e.g., by setting

ghc-options: -fno-ignore-asserts

in your .cabal file. Otherwise, some of the functions will have no effect at all.

Synopsis

Documentation

assert :: Bool -> a -> a

If the first argument evaluates to True, then the result is the second argument. Otherwise an AssertionFailed exception is raised, containing a String with the source file and line number of the call to assert.

Assertions can normally be turned on or off with a compiler flag (for GHC, assertions are normally on unless optimisation is turned on with -O or the -fignore-asserts option is given). When assertions are turned off, the first argument to assert is ignored, and the second argument is returned as the result.

blame :: Show a => Bool -> a -> Bool infix 1 Source

If the condition fails, display the value blamed for the failure. Used as in

assert (age < 120 `blame` age) $ savings / (120 - age)

failure :: Show a => (forall x. Bool -> x -> x) -> a -> b infix 1 Source

Like error, but shows the source position and also the value to blame for the failure. To be used as in

case xs of
  0 : _ -> assert `failure` (xs, "has an insignificant zero")

twith :: Text -> b -> (Text, b) infix 2 Source

Syntactic sugar for the pair operation, to be used in blame and failure as in

assert (age < 120 `blame` "age too high" `twith` age) $ savings / (120 - age)

or

case xs of
  0 : _ -> assert `failure` "insignificant zero" `twith` xs

Fixing the first component of the pair to Text prevents warnings about defaulting.

swith :: String -> b -> (String, b) infix 2 Source

The same as twith, but for String, not Text.

Syntactic sugar for the pair operation, to be used in blame and failure as in

assert (age < 120 `blame` "age too high" `swith` age) $ savings / (120 - age)

or

case xs of
  0 : _ -> assert `failure` "insignificant zero" `swith` xs

Fixing the first component of the pair to String prevents warnings about defaulting.

allB :: Show a => (a -> Bool) -> [a] -> Bool Source

Like all, but if the predicate fails, blame all the list elements and especially those for which it fails. To be used as in

assert (allB (<= height) [yf, y1, y2])

skip :: Monad m => m () Source

To be used in place of the verbose (return ()), as in

do k <- getK7 r
   assert (k <= maxK `blame` "K7 too large" `twith` r) skip
   return $ k >= averageK

forceEither :: Show a => (forall x. Bool -> x -> x) -> Either a b -> b infix 1 Source

Assuming that Left signifies an error condition, check the Either value and, if Left is encountered, fail outright and show the error message. Used as in

assert `forceEither` parseOrFailWithMessage code