[Haskell-cafe] Problem with overlapping class instances

Graham Klyne gk at ninebynine.org
Tue Nov 23 09:01:05 EST 2004


>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 at haskell.org
>>http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>------------
>Graham Klyne
>For email:
>http://www.ninebynine.org/#Contact



More information about the Haskell-Cafe mailing list