[Haskell-cafe] Problem with overlapping class instances

Keean Schupke k.schupke at imperial.ac.uk
Tue Nov 23 11:16:24 EST 2004


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]
>


More information about the Haskell-Cafe mailing list