
The errors in the older code were due to not supplying enough input
arguments to all my class instance declarations. My final code works
and is pasted bellow:
{-# LANGUAGE EmptyDataDecls,
MultiParamTypeClasses,
ScopedTypeVariables,
FunctionalDependencies,
OverlappingInstances,
FlexibleInstances,
UndecidableInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
data Noun = Noun deriving (Show) --10
data Verb = Verb deriving (Show) --
data Adjactive = Adjactive deriving (Show)
data Animal=Animal deriving (Show)
data Feline=Feline deriving (Show)
data Cat = Cat deriving (Show)
data Taby_Cat=Taby_Cat deriving (Show)
data T=T deriving (Show)
data F=F deriving (Show) --20
class Isa a b c | a b->c where isa::a->b->c
instance Isa Animal Noun T where isa a b = T --25
class IsSuperSet a b c | a b->c where -- General Definition
isSuperSet :: a->b->c
class IsSuperSet' a b c | a b->c where -- Specific Cases
isSuperSet :: a->b->c
instance IsSuperSet' Feline Cat T where --30
isSuperSet a b=T
instance IsSuperSet' Animal Feline T where
isSuperSet a b=T
instance IsSuperSet' a Animal F where
isSuperSet a b=F --35
instance (IsSuperSet' d b c, --40
IsSuperSet a d c,
)=>
IsSuperSet a b c where
isSuperSet a b=undefined::c
class ToBool a where
toBool :: a->Bool
instance ToBool T where
toBool a = True
instance ToBool F where
toBool a = False
myCat=Cat
bla=isSuperSet Animal Cat
bla2=isSuperSet Cat Animal
On May 1, 10:16 am, John Creighton
On Apr 30, 6:18 pm, John Creighton
wrote: On Apr 29, 7:47 am, John Creighton
wrote: I've been trying to apply some stuff I learned about functional dependencies, but I run into one of two problems. I either end up with inconsistent dependencies (OverlappingInstances doesn't seem to apply) or I end up with infinite recursion. I want to be able to do simple things like if a is a subset of b and b is a subset of c then a is a subset of c. If a is a is a subset of b and b is a c then a is a c.
Before I added the equality functions I had infinite recursion. Once I put them them in then I have trouble with overlapping instances.
I've been doing some reading and I think the following is an improvement but I end up hanging the compiler so I can't tell what the errors are. I'll see if their are any trace options that might be helpfully for GHC.
So bellow I'll post the latest version of my code but first the errors which seem very strange to me:
--------------------------------------------------------------------
could not deduce (IsSuperSet' isanimal iseq isanimal iseq1 (a -> b -> c3) ) from the context (IsSuperSet a b c2, Typeeq a b iseq1, TypeEq Animal b isaninmal, IsSuperSet' isanimal iseq1 a b c3) arising from a use of 'isSuperSet'' at logicp2.hs:92:25-74 Possible fix: add (IsSuperSet' isanimal iseq isanimal iseq1 (a -> b -> c3)) to context of the declaration or add an instance delaration for (IsSuperSet' isanimal iseq isanimal iseq1 (a -> b -> c3)) In the expression: (isSuperSet' (u :: isanimal) (u :: iseq) (a :: a) (b ::b)) :: c3 In the definition of 'isSuperset': isSuperset a b = (isSuperSet' (u :: isanimal) (u :: iseq) (a :: a) (b :: b)) in the instance delaration for 'IsSuperSet a b c3'