ghc overlapping instances

Hello, I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance instance Arbitrary [Stmt] (mainly to restrict the size of the list). In quickcheck an instance Arbitrary of lists is already defined. Which parameters do I have to give ghc such that it accepts such an instance? In hugs -98 +o is enough. I have tried -XOverlappingInstances, -XFlexibleInstances and also -XIncoherentInstances, however I still got an overlapping instances error for this declaration. Regards, Steffen

Steffen Mazanek wrote:
Hello,
I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance
instance Arbitrary [Stmt]
(mainly to restrict the size of the list).
you don't always need to use instances. for example, I have (where Predicate is a type I defined which I gave a separate normal Arbitrary instance) arbpredicate :: Gen Predicate arbpredicate = do ... prop_assocUnify :: Property prop_assocUnify = forAll arbpredicate $ \a -> forAll arbpredicate $ \b -> forAll arbpredicate $ \c -> ...boolean result Isaac

On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote:
Hello,
I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance
instance Arbitrary [Stmt]
(mainly to restrict the size of the list).
In quickcheck an instance Arbitrary of lists is already defined. Which parameters do I have to give ghc such that it accepts such an instance? In hugs -98 +o is enough. I have tried -XOverlappingInstances, -XFlexibleInstances and also -XIncoherentInstances, however I still got an overlapping instances error for this declaration.
You shouldn't use lists if you need to have special instance behavior - lists are for perfectly ordinary sequences of things. If a program is just a bunch of unrelated statements, then use [], otherwise use a custom (new)type. Stefan

Hi,
Stefan and Isaac, thx for providing quick advice.
@Stefan: Unfortunately I have to use a list.
@Isaac: I do not get it. Could you please provide a short example of your
approach?
The question still remains. Which arguments do I have ghc to start with to
get the same behavior than hugs with -98 +o (here it works).
I provide my example for testing purposes:
module Test where
import Test.QuickCheck
import Monad(liftM,liftM2)
type Program = [Stmt]
data Stmt = Text | IfElse Program Program | While Program deriving (Eq,
Show)
instance Arbitrary [Stmt] where
arbitrary = sized genProg
instance Arbitrary Stmt where
arbitrary = sized genStmt
genStmt::Int->Gen Stmt
genStmt 0 = return Text
genStmt 1 = return Text
genStmt 2 = oneof [return Text, return (While [Text])]
genStmt n | n>2 = oneof ([return Text,
liftM While (genProg (n-1))]++
[liftM2 IfElse (genProg k) (genProg
(n-k-1))|k<-[1..n-2]])
genProg::Int->Gen Program
genProg 0 = return []
genProg 1 = return [Text]
genProg n | n>1 = oneof ((liftM (\x->[x]) (genStmt n)):[liftM2 (:) (genStmt
k) (genProg (n-k))|k<-[1..n-1]])
prop_ConstructParse progr = True
where types = progr::Program
main = mapM_ (\(s,a) -> putStrLn s >> a) [("flowchart construct and parse",
test prop_ConstructParse)]
2007/12/4, Stefan O'Rear
On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote:
Hello,
I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance
instance Arbitrary [Stmt]
(mainly to restrict the size of the list).
In quickcheck an instance Arbitrary of lists is already defined. Which parameters do I have to give ghc such that it accepts such an instance? In hugs -98 +o is enough. I have tried -XOverlappingInstances, -XFlexibleInstances and also -XIncoherentInstances, however I still got an overlapping instances error for this declaration.
You shouldn't use lists if you need to have special instance behavior - lists are for perfectly ordinary sequences of things. If a program is just a bunch of unrelated statements, then use [], otherwise use a custom (new)type.
Stefan
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux)
iD8DBQFHVcxTFBz7OZ2P+dIRAmtMAJ9xcL0xhG9u+QaIFXwhEEq177ePEgCfUfOf dlDMHAN8ldq2qZ7ctOFkNb4= =hxkS -----END PGP SIGNATURE-----
-- Dipl.-Inform. Steffen Mazanek Institut für Softwaretechnologie Fakultät Informatik Universität der Bundeswehr München 85577 Neubiberg Tel: +49 (0)89 6004-2505 Fax: +49 (0)89 6004-4447 E-Mail: steffen.mazanek@unibw.de

Steffen Mazanek wrote:
Hi,
Stefan and Isaac, thx for providing quick advice.
@Stefan: Unfortunately I have to use a list. @Isaac: I do not get it. Could you please provide a short example of your approach?
The question still remains. Which arguments do I have ghc to start with to get the same behavior than hugs with -98 +o (here it works).
I provide my example for testing purposes:
module Test where import Test.QuickCheck import Monad(liftM,liftM2)
type Program = [Stmt] data Stmt = Text | IfElse Program Program | While Program deriving (Eq, Show)
instance Arbitrary [Stmt] where arbitrary = sized genProg instance Arbitrary Stmt where arbitrary = sized genStmt
genStmt::Int->Gen Stmt genStmt 0 = return Text genStmt 1 = return Text genStmt 2 = oneof [return Text, return (While [Text])] genStmt n | n>2 = oneof ([return Text, liftM While (genProg (n-1))]++ [liftM2 IfElse (genProg k) (genProg (n-k-1))|k<-[1..n-2]])
genProg::Int->Gen Program genProg 0 = return [] genProg 1 = return [Text] genProg n | n>1 = oneof ((liftM (\x->[x]) (genStmt n)):[liftM2 (:) (genStmt k) (genProg (n-k))|k<-[1..n-1]])
prop_ConstructParse progr = True where types = progr::Program
main = mapM_ (\(s,a) -> putStrLn s >> a) [("flowchart construct and parse", test prop_ConstructParse)]
is prop_ConstructParse the only thing that breaks when you remove the instance Arbitrary [Stmt] where arbitrary = sized genProg, or have I missed something? If that's all, try this (untested) : prop_ConstructParse = forAll (sized genProg) (\progr -> True) and similarly for other properties. Or, you _can_ use a newtype for quickcheck-only, something like this: newtype P = P { unP :: Program } instance Show P where show = show . unP instance Arbitrary P where arbitrary = sized genProg . unP prop_ConstructParse (P progr) = True Isaac
participants (3)
-
Isaac Dupree
-
Stefan O'Rear
-
Steffen Mazanek