4
votes

I'm trying to understand a compiler error message which refers to a type variable p0. In most situations, the error message would tell me what the compiler is calling p0, with something along the lines of "p0 is a rigid type variable bound by...", but not in this case.

In general, if a compiler error message refers to a type variable that it has assigned (rather than a type variable I reference in the type signature), and it doesn't tell me where the type variable is bound, how can I figure it out?

{-# LANGUAGE TypeFamilies, FlexibleContexts, MultiParamTypeClasses #-}
import Data.List (minimumBy)
import Data.Ord (comparing)
import qualified Math.Geometry.Grid as G (Grid(..))
import qualified Math.Geometry.GridMap as GM (GridMap(..))
import Prelude hiding (lookup)

class Pattern p where
  type Metric p
  difference ∷ p → p → Metric p
  makeSimilar ∷ p → Metric p → p → p

data SOM gm k p = SOM
  {
    sGridMap :: gm p,
    sLearningFunction :: Int -> Int -> Metric p,
    sCounter :: Int
  }

foo 
  :: (Pattern p, Ord v, v ~ Metric p, GM.GridMap gm p, GM.GridMap gm v, 
      k ~ G.Index (GM.BaseGrid gm p), k ~ G.Index (GM.BaseGrid gm v)) => 
    SOM gm k p -> p -> [(k, v)]
foo s p = GM.toList . GM.map (p `difference`) . sGridMap $ s

bar :: (Pattern p, Ord v, v ~ Metric p) => [(k, v)] -> k
bar ds = fst . minimumBy (comparing snd) $ ds

wombat
  :: (Pattern p, Ord v, v ~ Metric p, GM.GridMap gm p, GM.GridMap gm v,
      k ~ G.Index (GM.BaseGrid gm p), k ~ G.Index (GM.BaseGrid gm v)) => 
    SOM gm k p -> p -> (k, [(k, v)])
wombat s p = (bar diffs, diffs)
  where diffs = foo s p

Here's the error:

λ> :l ../amy.hs
[1 of 1] Compiling Main             ( ../amy.hs, interpreted )

../amy.hs:33:19:
    Could not deduce (v ~ Metric p0)
    from the context (Pattern p,
                      Ord v,
                      v ~ Metric p,
                      GM.GridMap gm p,
                      GM.GridMap gm v,
                      k ~ G.Index (GM.BaseGrid gm p),
                      k ~ G.Index (GM.BaseGrid gm v))
      bound by the type signature for
                 wombat :: (Pattern p, Ord v, v ~ Metric p, GM.GridMap gm p,
                            GM.GridMap gm v, k ~ G.Index (GM.BaseGrid gm p),
                            k ~ G.Index (GM.BaseGrid gm v)) =>
                           SOM gm k p -> p -> (k, [(k, v)])
      at ../amy.hs:(30,10)-(32,40)
      `v' is a rigid type variable bound by
          the type signature for
            wombat :: (Pattern p, Ord v, v ~ Metric p, GM.GridMap gm p,
                       GM.GridMap gm v, k ~ G.Index (GM.BaseGrid gm p),
                       k ~ G.Index (GM.BaseGrid gm v)) =>
                      SOM gm k p -> p -> (k, [(k, v)])
          at ../amy.hs:30:10
    In the expression: bar diffs
    In the expression: (bar diffs, diffs)
    In an equation for `wombat':
        wombat s p
          = (bar diffs, diffs)
          where
              diffs = foo s p
Failed, modules loaded: none.
1

1 Answers

6
votes

This is a bit of a guess, but here goes:

p0 is renamed from p in bar's type signature.

bar :: (Pattern p, Ord v, v ~ Metric p) => [(k, v)] -> k

Here p occurs only to the left of the =>. Only k and v can be deduced from the call site. There could be many types p that give the same result when given to Metric, and the compiler can't make the assumption that p in bar is the same as the p in wombat, even though Metric p is the same in both cases.

In this case I would change the type signature to

bar :: Ord v => [(k, v)] -> k

as bar does not use any of the other constraints.

If in your Real Code bar does use the other constraints, I would add a proxy argument (that could be of type p if I had a value of the appropriate type lying around, as wombat does, or of a -> p or p -> a, etc) to help the type checker.