Update example

This commit is contained in:
lyxia 2017-08-21 21:23:41 +02:00
parent 41616e98ec
commit bab2c3b499

View File

@ -1,25 +1,34 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Proxy
import GHC.Generics ( Generic, Rep )
import GHC.Generics (Generic)
import Test.QuickCheck
import Generic.Random.Generic
data Tree a = Leaf | Node (Tree a) a (Tree a)
deriving (Show, Generic)
type instance Found (Tree a) z = GFound (Tree a) z
instance GBaseCaseSearch (Tree a) z e => BaseCaseSearch (Tree a) z e
instance Arbitrary a => Arbitrary (Tree a) where
arbitrary = genericArbitrary' Z uniform
arbitrary = genericArbitrary' uniform
data Bush a = Tip a | Fork (Bush a) (Bush a)
deriving (Show, Generic)
instance (Arbitrary a, BaseCases' Z a) => Arbitrary (Bush a) where
arbitrary = genericArbitrary' (S Z) (weights (1 % (2 % ())))
type instance Found (Bush a) z = GFound (Bush a) z
instance GBaseCaseSearch (Bush a) z e => BaseCaseSearch (Bush a) z e
instance (Arbitrary a, BaseCase (Bush a)) => Arbitrary (Bush a) where
arbitrary = genericArbitrary' (weights (1 % (2 % ())))
main :: IO ()
main = do
sample (arbitrary :: Gen (Tree ()))
putStrLn ""