
On Apr 29, 7:47 am, John Creighton
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. {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, ScopedTypeVariables, FunctionalDependencies, FlexibleInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} --10 {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} data Noun = Noun deriving (Show) --15 data Verb = Verb deriving (Show) -- data Adjactive = Adjactive deriving (Show) data Animal=Animal deriving (Show) data Feline=Feline deriving (Show) --20 data Cat = Cat deriving (Show) data Taby_Cat=Taby_Cat deriving (Show) data T=T deriving (Show) data F=F deriving (Show) --25 --data Z=Z --data S i = S i --type One = S Z --type Zero = Z class Isa a b c | a b->c where isa::a->b->c --30 instance Isa Animal Noun T where isa a b = T -- class Parrent a b| a->b where -- Specific Cases parrent :: a->b -- instance Parrent Cat Feline where -- parrent a = Feline --40 instance Parrent Feline Animal where -- parrent a= Animal -- class TypeOr a b c|a b->c where typeOr :: a->b->c instance TypeOr T T T where typeOr a b = T --50 instance TypeOr T F T where typeOr a b = T instance TypeOr F T T where typeOr a b = T instance TypeOr F F T where typeOr a b = T class TypeEq' () x y b => TypeEq x y b | x y -> b instance TypeEq' () x y b => TypeEq x y b class TypeEq' q x y b | q x y -> b --60 class TypeEq'' q x y b | q x y -> b instance TypeCast b T => TypeEq' () x x b instance TypeEq'' q x y b => TypeEq' q x y b instance TypeEq'' () x y F -- see http://okmij.org/ftp/Haskell/typecast.html class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a-
b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a- b --70
instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x -- overlapping instances are used only for ShowPred class EqPred a flag | a->flag where {} -- Used only if the other -- instances don't apply -- 80 class IsSuperSet a b c | a b->c where -- General Definition isSuperSet :: a->b->c --instance (TypeEq b Animal T,TypeEq c F T)=>IsSuperSet a b c where --85 -- isSuperSet a b = F -- u=undefined instance ( TypeEq a b iseq, --90 TypeEq Animal b isaninmal, IsSuperSet' isaninmal iseq a b c3 -- ) => IsSuperSet a b c3 where -- isSuperSet a b=(isSuperSet' (u::isaninmal) (u::iseq) (a::a) (b::b))::c3 class IsSuperSet' isanimal iseq a b c| isanimal iseq a b->c where isSuperSet' :: a->b->c instance IsSuperSet' isanimal T a b T where isSuperSet' a b = T instance (Parrent b d, IsSuperSet a b c)=>IsSuperSet' F F a b c where isSuperSet' a b = (isSuperSet a ((parrent (b::b)::d)))::c instance IsSuperSet' T F a b F where isSuperSet' a b = F 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