[Haskell-cafe] Instance match surprise
Wojtek Narczyński
wojtek at power.com.pl
Mon Feb 1 18:53:32 UTC 2016
Dear List,
Why does the first instance match? ANY is neither Eq nor Typeable. I
thought I had some basic understanding of type classes, and now this...
wojtek at biuro:~/src/he$ cat minimatch.hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module MiniMatch where
import Data.Typeable
data A130 = A130 deriving (Eq)
data ANY = ANY
class AtmAcct a
class Against q
class (AtmAcct a, Against q) => Match a q where match :: a -> q -> Bool
instance AtmAcct A130
instance Against ANY
instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a, Against q) =>
Match a q where match _ _ = False
instance (AtmAcct a) => Match a ANY where match _ _ = True
m1 = match A130 ANY -- offending line
wojtek at biuro:~/src/he$ ghc minimatch.hs
[1 of 1] Compiling MiniMatch ( minimatch.hs, minimatch.o )
minimatch.hs:21:6: error:
• Overlapping instances for Match A130 ANY
arising from a use of ‘match’
Matching instances:
instance (Eq a, Eq q, Typeable a, Typeable q, AtmAcct a,
Against q) =>
Match a q
-- Defined at minimatch.hs:18:10
instance AtmAcct a => Match a ANY -- Defined at minimatch.hs:19:10
• In the expression: match A130 ANY
In an equation for ‘m1’: m1 = match A130 ANY
--
Thanks,
Wojtek Narczyński
More information about the Haskell-Cafe
mailing list