[Haskell-cafe] Quickcheck generator help
Ivan Lazar Miljenovic
ivan.miljenovic at gmail.com
Mon Nov 11 22:59:53 UTC 2013
On 12 November 2013 09:31, Graham Berks <graham at fatlazycat.com> wrote:
> Hi, have the following type
>
> data BinomialHeap a = EmptyHeap | Node a Int (BinomialHeap a)
>
> and wanted to create a test generator with type ‘a’ as an Int for example
>
> hence had
>
> newtype BinominalHeapInt = BinominalHeap Int deriving (Eq, Show)
Methinks this line is an error: what you've said is that
BinominalHeapInt is an Int wrapped in a BinominalHeap constructor; you
probably want:
newtype BinomialHeapInt = BHI (BinomialHeap Int)
Notice also your type of "Binominal" instead of "Binomial".
(You can't derive anything as Eq and Show aren't derived/defined for
BinomialHeap)
>
> But struggling to get the generator correct, currently have
>
> instance Arbitrary BinominalHeapInt where
> arbitrary = sized heap' where
> heap' 0 = return EmptyHeap
> heap' n | n>0 = oneof [return EmptyHeap, liftM3 Node arbitrary arbitrary
> subnode]
> where subnode = heap' (n `div` 2)
What you'd probably want is to have "instance (Arbitrary a) =>
Arbitrary (BinomialHeap a) where ..." with this definition, and then:
instance Arbitrary BinomialHeapInt where
arbitrary = fmap BHI arbitrary
>
> But it complains
>
> Expected type: Int -> Gen BinominalHeapInt
> Actual type: Int -> Gen (BinomialHeap a1)
>
> in sized heap’
>
> Any pointers ?
>
> Thanks
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
--
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com
More information about the Haskell-Cafe
mailing list