[Haskell-cafe] Using quickcheck to check for errors
Niklas Hambüchen
mail at nh2.me
Sat Jun 7 20:11:21 UTC 2014
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
More information about the Haskell-Cafe
mailing list