[Haskell-cafe] Re: HList error with hFoldr
Denis Bueno
dbueno at gmail.com
Sat Jan 26 11:03:33 EST 2008
On Sat, Jan 26, 2008 at 1:59 AM, <oleg at okmij.org> wrote:
[snip useful explanation of error}
> Here's a
> bit elaborated example:
[...]
Thanks! this works, and I understand why it didn't before.
The example I posted was a stepping stone toward a definition of
distance using hFoldr and hZip. I've updated "testApplyDistSum" so
that it mirrors the structure of what I want, and it compiles, but the
general case does not. (As an aside: I'm not quite sure whether the
constraints in the MetricSpace (HCons e l) f instance are correct, but
they seem so.)
Have I made some sort of simple error, or am I going about this the
wrong way altogether?
{- CODE -}
import HList
instance (Floating f, MetricSpace e f, HList l, HZip l l l
,HFoldr ApplyDistSum Float l f)
=> MetricSpace (HCons e l) f where
c `dist` c' = hFoldr ApplyDistSum (0::Float) (hZip c c')
-- The following works:
testApplyDistSum = hFoldr ApplyDistSum 0
(hZip ("2 " .*. (2.0::Float) .*. (4::Int) .*. hNil)
("1" .*. (1.5::Float) .*. (5::Int) .*. hNil))
-- The following issues a compile error, with no useful source location:
testDistInst =
let a = (1::Int) .*. (2::Int) .*. (4::Int) .*. hNil
b = (1::Int) .*. (2::Int) .*. (3::Int) .*. hNil
in a `dist` b
{-
Line 1 of Knn.hs is a comment.
/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:1:0:
Couldn't match expected type `Int'
against inferred type `(Int, Int)'
Expected type: HCons Int (HCons Int HNil)
Inferred type: HCons (Int, Int) l
When using functional dependencies to combine
HZip (HCons hx tx) (HCons hy ty) (HCons (hx, hy) l),
arising from the instance declaration at <no location info>
HZip
(HCons Int (HCons Int HNil))
(HCons Int (HCons Int HNil))
(HCons Int (HCons Int HNil)),
arising from a use of `dist'
at
/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:67:7-16
-}
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 Num i => MetricSpace Integer i where
x `dist` y = fromIntegral $ abs (y - x)
instance (Floating o) => MetricSpace Float o where
x `dist` y = realToFrac $ abs (y - x)
instance (Num o) => MetricSpace String o where
x `dist` y = fromIntegral $ abs (length y - length x)
data ApplyDistSum = ApplyDistSum
instance (MetricSpace e r) => Apply ApplyDistSum ((e, e), r) r where
apply _ (p, v) = v + (uncurry dist p)^2
--
Denis
More information about the Haskell-Cafe
mailing list