Problem with overlapping class instances

Once again, the Haskell class system is proving rather subtle for me. On this occasion, I'm getting an overlapping class instance error which I think should be fully disambiguated by the supplied class context. The code below (end of message) is a .lhs file that reproduces the problem in Hugs, with external dependencies from my working codebase stripped out. It should be possible to simply load it (or this whole email) to get the same error: [[ Reading file "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs": ERROR "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs":30 - Overlapping inst ances for class "ConceptExpr" *** This instance : ConceptExpr (a b) *** Overlaps with : ConceptExpr AtomicConcept *** Common instance : ConceptExpr [Char] ]] The line referred to as "this instance" is: instance (ConceptWrapper cw c, ConceptExpr c) => ConceptExpr (cw c) where The reported overlapping instance is [Char], which I take to be derived from the type constructor [] applied to type Char, this yielding a form that matches (cw c). But the instance ConceptExpr (cw c) is declared to be dependent on the context ConceptWrapper cw c, which has *not* been declared for the type constructor []. GHCi with -fglasgow-exts is no more informative. What am I missing here? #g -- [Source code follows] spike-overlap-ConceptExpr.lhs -----------------------------
type AtomicConcepts a = [(AtomicConcept,[a] )] type AtomicRoles a = [(AtomicRole ,[(a,a)])]
type TInterpretation a = ([a],AtomicConcepts a,AtomicRoles a)
class (Eq c, Show c) => ConceptExpr c where iConcept :: Ord a => TInterpretation a -> c -> [a]
...
type AtomicConcept = String -- named atomic concept
Declare AtomicConcept and AtomicRole as instances of ConceptExpr and RoleExpr (AtomicRole is used by AL, and including AtomicConcept here for completeness).
instance ConceptExpr AtomicConcept where iConcept = undefined
... To allow a common expression to support multiple description logics, we first define a wrapper class for DLConcept and DLRole:
class ConceptExpr c => ConceptWrapper cw c | cw -> c where wrapConcept :: c -> cw c -> cw c getConcept :: cw c -> c
Using this, a ConceptWrapper can be defined to be an instance of ConceptExpr: This is line 30:
instance (ConceptWrapper cw c, ConceptExpr c) => ConceptExpr (cw c) where iConcept = iConcept . getConcept
Error message: Reading file "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs": ERROR "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs":30 - Overlapping inst ances for class "ConceptExpr" *** This instance : ConceptExpr (a b) *** Overlaps with : ConceptExpr AtomicConcept *** Common instance : ConceptExpr [Char] ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

Instance selection and thereby overlapping resolution is *independent* of constraints. It is defined to be purely syntactical in terms of instance heads. See the HList paper for some weird examples. Ralf Graham Klyne wrote:
The reported overlapping instance is [Char], which I take to be derived from the type constructor [] applied to type Char, this yielding a form that matches (cw c). But the instance ConceptExpr (cw c) is declared to be dependent on the context ConceptWrapper cw c, which has *not* been declared for the type constructor [].
GHCi with -fglasgow-exts is no more informative.
What am I missing here?

The trick here is to use a type to represent the constraint rather than a class, if possible. Keean Ralf Laemmel wrote:
Instance selection and thereby overlapping resolution is *independent* of constraints. It is defined to be purely syntactical in terms of instance heads. See the HList paper for some weird examples.
Ralf
Graham Klyne wrote:
The reported overlapping instance is [Char], which I take to be derived from the type constructor [] applied to type Char, this yielding a form that matches (cw c). But the instance ConceptExpr (cw c) is declared to be dependent on the context ConceptWrapper cw c, which has *not* been declared for the type constructor [].
GHCi with -fglasgow-exts is no more informative.
What am I missing here?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

At 22:05 22/11/04 +0000, Keean Schupke wrote: The trick here is to use a type to represent the constraint rather than a class, if possible.
Keean
Hmmm, I'm not sure that I understand what you mean. Considering my example (repeated below), is it that 'AtomicConcept' should be an algebraic datatype rather than just a type synonym? Or is there more? Or... I just found John Hughes 1999 paper on Restricted Data Types in Haskell [1], which talks about representing class constraints by the type of its associated dictionary. Is this is what you mean? #g -- [1] http://www.cs.chalmers.se/~rjmh/Papers/restricted-datatypes.ps spike-overlap-ConceptExpr.lhs -----------------------------
type AtomicConcepts a = [(AtomicConcept,[a] )] type AtomicRoles a = [(AtomicRole ,[(a,a)])]
type TInterpretation a = ([a],AtomicConcepts a,AtomicRoles a)
class (Eq c, Show c) => ConceptExpr c where iConcept :: Ord a => TInterpretation a -> c -> [a]
...
type AtomicConcept = String -- named atomic concept
Declare AtomicConcept and AtomicRole as instances of ConceptExpr and RoleExpr (AtomicRole is used by AL, and including AtomicConcept here for completeness).
instance ConceptExpr AtomicConcept where iConcept = undefined
... To allow a common expression to support multiple description logics, we first define a wrapper class for DLConcept and DLRole:
class ConceptExpr c => ConceptWrapper cw c | cw -> c where wrapConcept :: c -> cw c -> cw c getConcept :: cw c -> c
Using this, a ConceptWrapper can be defined to be an instance of ConceptExpr: This is line 30:
instance (ConceptWrapper cw c, ConceptExpr c) => ConceptExpr (cw c) where iConcept = iConcept . getConcept
Error message: Reading file "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs": ERROR "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs":30 - Overlapping inst ances for class "ConceptExpr" *** This instance : ConceptExpr (a b) *** Overlaps with : ConceptExpr AtomicConcept *** Common instance : ConceptExpr [Char]
Ralf Laemmel wrote:
Instance selection and thereby overlapping resolution is *independent* of constraints. It is defined to be purely syntactical in terms of instance heads. See the HList paper for some weird examples.
Ralf
Graham Klyne wrote:
The reported overlapping instance is [Char], which I take to be derived from the type constructor [] applied to type Char, this yielding a form that matches (cw c). But the instance ConceptExpr (cw c) is declared to be dependent on the context ConceptWrapper cw c, which has *not* been declared for the type constructor [].
GHCi with -fglasgow-exts is no more informative.
What am I missing here?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

The problem is that (cw c) overlaps with String. It will still ovarlap if you use data decl. it is the CW that needs to be a datatype. See Below: Keean. Graham Klyne wrote:
Hmmm, I'm not sure that I understand what you mean.
Considering my example (repeated below), is it that 'AtomicConcept' should be an algebraic datatype rather than just a type synonym? Or is there more?
Or... I just found John Hughes 1999 paper on Restricted Data Types in Haskell [1], which talks about representing class constraints by the type of its associated dictionary. Is this is what you mean?
#g --
[1] http://www.cs.chalmers.se/~rjmh/Papers/restricted-datatypes.ps
spike-overlap-ConceptExpr.lhs -----------------------------
type AtomicConcepts a = [(AtomicConcept,[a] )] type AtomicRoles a = [(AtomicRole ,[(a,a)])]
type TInterpretation a = ([a],AtomicConcepts a,AtomicRoles a)
class (Eq c, Show c) => ConceptExpr c where iConcept :: Ord a => TInterpretation a -> c -> [a]
...
type AtomicConcept = String -- named atomic concept
Declare AtomicConcept and AtomicRole as instances of ConceptExpr and RoleExpr (AtomicRole is used by AL, and including AtomicConcept here for completeness).
instance ConceptExpr AtomicConcept where iConcept = undefined
...
To allow a common expression to support multiple description logics, we first define a wrapper class for DLConcept and DLRole:
class ConceptExpr c => ConceptWrapper cw c | cw -> c where wrapConcept :: c -> cw c -> cw c getConcept :: cw c -> c
Do this: data CW cw = CW cw class ConceptWrapper cw c | cw -> c wrapConcept :: c -> (CW cw) c -> (CW cw) c getConcept :: (CW cw) c -> c
Using this, a ConceptWrapper can be defined to be an instance of ConceptExpr:
This is line 30:
instance (ConceptWrapper cw c, ConceptExpr c) => ConceptExpr (cw c) where iConcept = iConcept . getConcept
instance ConceptWrapper (CW cw) c,ConceptExpr c) => ConceptExpr ((CW cw) c) where
Error message: Reading file "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs": ERROR "D:\Cvs\DEV\HaskellDL\spike-overlap-conceptexpr.lhs":30 - Overlapping inst ances for class "ConceptExpr" *** This instance : ConceptExpr (a b) *** Overlaps with : ConceptExpr AtomicConcept *** Common instance : ConceptExpr [Char]

At 16:16 23/11/04 +0000, Keean Schupke wrote:
The problem is that (cw c) overlaps with String. It will still ovarlap if you use data decl. it is the CW that needs to be a datatype. See Below:
Thanks. I've massaged that into something that compiles (copy below). I think I see why this works, but I still can't say that I find the revised structure entirely intuitive. I think the key feature is that wrapped instances of ConceptExpr are distinguished from "native" instances by the type constructor CW. That is, each instance type is distinguished by different known type constructor -- in this case, [] and CW. I need to noodle on the a while to see if the pattern fits my application, but I think I get the general idea. Of all the combinations I thought about making the type constructor part of the class method signatures was not one I'd tried. Also, I think declaring CW as a 'newtype' rather than 'data' captures the intent more directly. #g -- spike-overlap-ConceptExpr-datatyped.lhs --------------------------------------- Some given type and class declarations:
type AtomicConcepts a = [(AtomicConcept,[a] )] type AtomicRoles a = [(AtomicRole ,[(a,a)])]
type TInterpretation a = ([a],AtomicConcepts a,AtomicRoles a)
class (Eq c, Show c) => ConceptExpr c where iConcept :: Ord a => TInterpretation a -> c -> [a]
type AtomicConcept = String -- named atomic concept type AtomicRole = String -- named atomic role
Declare AtomicConcept as "base" instance of ConceptExpr.
instance ConceptExpr AtomicConcept where iConcept = undefined
To allow a common expression to support multiple description logics, define a wrapper type and class for DLConcept and DLRole:
newtype CW cw c = CW cw deriving (Eq,Show) class ConceptWrapper cw c | cw -> c where wrapConcept :: c -> (CW cw c) -> (CW cw c) getConcept :: (CW cw c) -> c
Using this, a ConceptWrapper can be defined to be an instance of ConceptExpr:
instance (Eq cw, Show cw, ConceptWrapper cw c,ConceptExpr c) => ConceptExpr (CW cw c) where iConcept i = iConcept i . getConcept
Now declare a pair containing a ConceptExpr to be an instance of ConceptWrapper:
type Wrap d c = (c,d)
instance ConceptWrapper (Wrap d c) c where wrapConcept c (CW (_,d)) = CW (c,d) getConcept (CW (c,_)) = c
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

At 21:40 22/11/04 +0100, Ralf Laemmel wrote:
Instance selection and thereby overlapping resolution is *independent* of constraints. It is defined to be purely syntactical in terms of instance heads. See the HList paper for some weird examples.
That explains it. Thanks! #g --
Ralf
Graham Klyne wrote:
The reported overlapping instance is [Char], which I take to be derived from the type constructor [] applied to type Char, this yielding a form that matches (cw c). But the instance ConceptExpr (cw c) is declared to be dependent on the context ConceptWrapper cw c, which has *not* been declared for the type constructor [].
GHCi with -fglasgow-exts is no more informative.
What am I missing here?
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact
participants (3)
-
Graham Klyne
-
Keean Schupke
-
Ralf Laemmel