Hspec + QuickCheck passing type

Hi, I'm writing the following Hspec + QuickCheck test for some type: context "Type1" $ it "decode inverses encode" $ property $ \x -> (decode . encode) x == Right (x::Type1) However, I have a number of these types, and I could write the same test for every type, but that isn't very DRY. Therefore I would like to put the test in a function and call that function for every type. Something like the following: typeTest name = do context name $ it "decode inverses encode" $ property $ \x -> (decode . encode) x == Right x 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? Kind regards, Martijn Rijkeboer

I would recommend using http://hackage.haskell.org/package/base-4.8.2.0/docs/Prelude.html#v:asTypeOf And passing a dummy variable of the correct type. -Will
On Mar 28, 2016, at 12:53, Martijn Rijkeboer
wrote: Hi,
I'm writing the following Hspec + QuickCheck test for some type:
context "Type1" $ it "decode inverses encode" $ property $ \x -> (decode . encode) x == Right (x::Type1)
However, I have a number of these types, and I could write the same test for every type, but that isn't very DRY. Therefore I would like to put the test in a function and call that function for every type. Something like the following:
typeTest name = do context name $ it "decode inverses encode" $ property $ \x -> (decode . encode) x == Right x
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?
Kind regards,
Martijn Rijkeboer
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

I would recommend using http://hackage.haskell.org/package/base-4.8.2.0/docs/Prelude.html#v:asTypeOf
And passing a dummy variable of the correct type.
Thanks, this is exactly what I was looking for. Kind regards, Martijn Rijkeboer

Martijn Rijkeboer
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
participants (3)
-
John Wiegley
-
Martijn Rijkeboer
-
Will Yager