[Haskell-cafe] Using quickcheck to check for errors

Bob Ippolito bob at redivi.com
Sat Jun 7 20:16:57 UTC 2014


There's a slightly cleaner way to do it. Of course it also uses
`unsafePerformIO` under the hood, but you can let Test.QuickCheck.Monadic
worry about that :)

Something like this: https://gist.github.com/etrepum/d450420a7fd8c2e73aec

import Data.Either (isLeft)
import Control.Exception (try, evaluate, SomeException)
import Test.QuickCheck (Property, quickCheck)
import Test.QuickCheck.Monadic (monadicIO, run, assert)

isFailure :: a -> IO Bool
isFailure = fmap isLeft . tryEval
  where
    tryEval :: a -> IO (Either SomeException a)
    tryEval = try . evaluate

prop_empty_list :: Int -> Property
prop_empty_list idx = monadicIO (run (isFailure ([] !! idx)) >>= assert)

prop_unexpected_success :: Int -> Property
prop_unexpected_success idx = monadicIO (run (isFailure ([()] !! idx)) >>=
assert)

main :: IO ()
main = mapM_ quickCheck [ prop_empty_list, prop_unexpected_success ]




On Sat, Jun 7, 2014 at 1:11 PM, Niklas Hambüchen <mail at nh2.me> wrote:

> On 07/06/14 19:56, Rafael Almeida wrote:
> > Let's say we want to quickcheck the function !!. Passing a negative
> > index to it is an error. However, how can you make a check that it
> > indeed errors in such situation?
>
> Hello!
>
> You can do so with the divine unsafePerformIO-try-evaluate-force combo.
>
> -- Code also at https://gist.github.com/nh2/1ce734759b196c3483fa
> {-# LANGUAGE ScopedTypeVariables #-}
>
> import Control.Exception
> import Control.DeepSeq
> import Data.List (isPrefixOf)
> import System.IO.Unsafe (unsafePerformIO)
> import Test.QuickCheck
>
> main :: IO ()
> main = quickCheck $ property $ \(list :: [Char], n :: Int) ->
>   n >= length list ==> throwsIndexError (list !! n)
>
>
> throwsIndexError :: (NFData a) => a -> Bool
> throwsIndexError expr = unsafePerformIO $ do
>   res <- try $ evaluate (force expr)
>   case res of
>     Left (ErrorCall msg) -> return $ "Prelude.(!!): index too large"
> `isPrefixOf` msg
>     Right _              -> return False -- no exception
>
>
> -- End of code
>
> `force` makes sure that the expression is evaluated all the way to the
> bottom, and nothing is left lazily unevaluated. If you don't desire
> that, you can leave `force` out.
>
> We use `isPrefixOf` because for some reason, the exception contains a
> newline.
>
> In case you are not familiar with deepseq, the `NFData a` requirement
> makes sure that the expression can be evaluated all the way down. If you
> don't want/need to use `force`, you can drop that one.
>
> The use of `unsafePerformIO` is OK here because it is referentially
> transparent: We use it only to wrap a pure function, and perform no
> further IO in it.
>
> Hope that helps!
> Niklas
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140607/bc936341/attachment.html>


More information about the Haskell-Cafe mailing list