[Haskell-cafe] HList error with hFoldr

Denis Bueno dbueno at gmail.com
Fri Jan 25 17:12:46 EST 2008


Hello all,

I'm doing some machine learning in Haskell and have run into a
problem.  I have a generic distance function (declare in the
MetricSpace) typeclass that returns the distance between two things as
a number.  I frequently will be working with heterogeneous collections
of data, and if possible I'd like to write the distance function
(overloaded) once for all.  At the moment, I'm using HList to
represent the collections of data uniformly.

I wrote the following as a sanity check but I can't even get it to
compile.  The effect I'd like is that I can call `dist` on any two
HLists which have the correct, corresponding element types in the
correct positions, and `dist` will be recursively invoked to calculate
the typical euclidean distance (squared sum of individual element
distances, and at the and taking the square root).

My attempt at doing this follows.  For the moment my HLists only
contain Ints.  I'm using GHC 6.8.2 and HList 0.1.


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)

data ApplyDistSum = ApplyDistSum
instance (MetricSpace e r) => Apply ApplyDistSum ((e, e), r) r where
    apply _ (p, v) = v + uncurry dist p

-- Why should the following generate an error?
testApplyDistSum = hFoldr ApplyDistSum 0 ((4,4) .*. hNil)
{- The error:

/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:53:19:
    No instance for (Apply ApplyDistSum ((t, t1), r1) r)
      arising from a use of `hFoldr'
                   at
/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:53:19-56
    Possible fix:
      add an instance declaration for
      (Apply ApplyDistSum ((t, t1), r1) r)
    In the expression: hFoldr ApplyDistSum 0 ((4, 4) .*. hNil)
    In the definition of `testApplyDistSum':
        testApplyDistSum = hFoldr ApplyDistSum 0 ((4, 4) .*. hNil)

-}

Thanks in advance.

-- 
                              Denis


More information about the Haskell-Cafe mailing list