[Haskell-cafe] Hspec + QuickCheck passing type

John Wiegley johnw at newartisans.com
Mon Mar 28 19:46:55 UTC 2016


>>>>> Martijn Rijkeboer <haskell at bunix.org> writes:

> Unfortunately this doesn't work, since QuickCheck doesn't know which
> Arbitrary instance to use. How can I pass the type, e.g. x::Type1, to this
> function so QuickCheck knows what Arbitrary instance to use?

For example:

    {-# LANGUAGE ScopedTypeVariables #-}
    
    import Test.QuickCheck
    import Test.Hspec
    import Data.Serialize
    import Data.Proxy
    
    typeTest :: forall a. (Show a, Eq a, Arbitrary a, Serialize a)
             => String -> Proxy a -> SpecWith ()
    typeTest name _ =
      context name $
        it "decode inverses encode" $ property $
          \(x :: a) -> (decode . encode) x == Right x
    
    main :: IO ()
    main = hspec $ typeTest "foo" (Proxy :: Proxy Int)

The use of Proxy conveys the needed type information, as Will had also
suggested.

-- 
John Wiegley                  GPG fingerprint = 4710 CF98 AF9B 327B B80F
http://newartisans.com                          60E1 46C4 BD1A 7AC1 4BA2


More information about the Haskell-Cafe mailing list