
Denis Bueno wrote:
For the moment my HLists only contain Ints. ... -- Why should the following generate an error? testApplyDistSum = hFoldr ApplyDistSum 0 ((4,4) .*. hNil)
Here is the problem: in Haskell, 4 is not an Int. (4::Int) is an Int, but just 4 is a _polymorphic_ constant of the type Num a => a. Because it is polymorphic and so does not have any defined type, the type checker cannot chose an appropriate instance for ApplyDistSum. The error message says this directly:
No instance for (Apply ApplyDistSum ((t, t1), r1) r)
Note the appearance of lower-case identifiers t, t1, r1, and r in the error message. They stand for the types that the type checker cannot figure out. When you use hFoldr in a larger expression, the types often become constrained by other components of the expression and so type variables become instantiated. In the simple cases as above, there is no information available to instantiate the type variables, hence the error. You have to give the type-checker hints in the form of type annotations: testApplyDistSum = hFoldr ApplyDistSum (0::Int) ((4::Int,4::Int) .*. hNil) In general, it is possible to avoid the type annotation on the accumulator (in this case, 0). The type checker could figure out the type of the result. But that requires specifying functional dependencies. The type annotations might be easier to start with. Incidentally, it is generally a good idea in Haskell to write Int constants as (1::Int), explicitly specifying their type. Here's a bit elaborated example: {-# OPTIONS -fglasgow-exts #-} module B where import HList class (Num i) => MetricSpace e i where dist :: e -> e -> i instance Num i => MetricSpace Int i where x `dist` y = fromIntegral $ abs (y - x) instance Floating i => MetricSpace Float i where x `dist` y = realToFrac $ abs (y - x) data ApplyDistSum = ApplyDistSum instance (MetricSpace e r) => Apply ApplyDistSum ((e, e), r) r where apply _ (p, v) = v + uncurry dist p testApplyDistSum = hFoldr ApplyDistSum (0::Double) ((4::Int,5::Int) .*. hNil) testApplyDistSum1 = hFoldr ApplyDistSum (0::Double) ( (4::Float,5.1::Float) .*. (4::Int,5::Int) .*. hNil)