[Haskell-cafe] Fixing undeduceable instance ==> overlapping instance
Michael Orlitzky
michael at orlitzky.com
Sun Feb 24 07:28:10 CET 2013
I'm trying to write a determinant function that works on matrices
parameterized by their dimensions (Peano naturals). If I declare the
following,
-- Define a class so that we get a different determinant function
-- on the base/recursive cases.
class (Eq a, Ring.C a) => Determined m a where
determinant :: (m a) -> a
-- Base case, 1x1 matrices
instance (Eq a, Ring.C a) => Determined (Mat (S Z) (S Z)) a where
determinant m = m !!! (0,0)
-- Recursive case, (n+2) x (n+2) matrices.
instance (Eq a, Ring.C a, Arity n)
=> Determined (Mat (S (S n)) (S (S n))) a where
determinant m =
...
-- Recursive algorithm, the i,jth minor has dimension
-- (n+1) x (n+1).
foo bar (determinant (minor m i j))
I get an error stating that I'm missing an instance:
Could not deduce (Determined (Mat (S n) (S n)) a)
...
Clearly, I *have* an instance for that case: if n == Z, then it's the
base case. If not, it's the recursive case. But GHC can't figure that
out. So maybe if I define a dummy instance to make it happy, it won't
notice that they overlap?
instance (Eq a, Ring.C a) => Determined (Mat m m) a where
determinant _ = undefined
No such luck:
>>> let m = fromList [[1,2],[3,4]] :: Mat2 Int
>>> determinant m
Overlapping instances for Determined (Mat N2 N2) Int
arising from a use of `determinant'
Matching instances:
instance (Eq a, Ring.C a) => Determined (Mat m m) a
-- Defined at Linear/Matrix2.hs:353:10
instance (Eq a, Ring.C a, Arity n) =>
Determined (Mat (S (S n)) (S (S n))) a
...
I even tried generalizing the (Mat m m) instance definition so that
OverlappingInstances would pick the one I want, but I can't get that to
work either.
Is there some way to massage this?
More information about the Haskell-Cafe
mailing list