
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)

On Sat, Jan 26, 2008 at 1:59 AM,
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

On Sat, Jan 26, 2008 at 11:03 AM, Denis Bueno
Have I made some sort of simple error, or am I going about this the wrong way altogether?
After some fooling around, I came up with something I think makes sense. Let me know if this is the right/wrong thing. It seems to work for the examples I've tried so far. instance (Floating f, MetricSpace e f ,MetricSpace e' f, HZip l l (HCons (e', e') l') ,HFoldr ApplyDistSum Float l' f) => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c') Thanks again for your help, oleg. -- Denis

After some fooling around, I came up with something I think makes sense. Let me know if this is the right/wrong thing. It seems to work for the examples I've tried so far.
instance (Floating f, MetricSpace e f ,MetricSpace e' f, HZip l l (HCons (e', e') l') ,HFoldr ApplyDistSum Float l' f) => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c')
It seems strange that you need the types e and e' (perhaps this is a quirk or a bug of GHC 6.8). With GHC 6.6, I have derived the following instance (Floating f, MetricSpace e f, HFoldr ApplyDistSum Float l1 f, HZip (HCons e l) (HCons e l) (HCons (e,e) l1)) => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c') which matches my intuitive understanding, and also sufficient to run the given examples. When I wrote `I derived with GHC' I meant it literally. First I wrote the instance without any constraints: instance () => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c') GHC of course complained about many missing constraints. I started adding the constraints from the list of complaints, until GHC was satisfied. This is basically a cut-and-paste job from the Emacs buffer with GHC error messages to the buffer with the code.

On Jan 28, 2008 12:45 AM,
It seems strange that you need the types e and e' (perhaps this is a quirk or a bug of GHC 6.8). With GHC 6.6, I have derived the following
instance (Floating f, MetricSpace e f, HFoldr ApplyDistSum Float l1 f, HZip (HCons e l) (HCons e l) (HCons (e,e) l1)) => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c')
which matches my intuitive understanding, and also sufficient to run the given examples.
This also works in GHC 6.8. Thanks!
When I wrote `I derived with GHC' I meant it literally. First I wrote the instance without any constraints:
instance () => MetricSpace (HCons e l) f where c `dist` c' = sqrt $ hFoldr ApplyDistSum (0::Float) (hZip c c')
GHC of course complained about many missing constraints. I started adding the constraints from the list of complaints, until GHC was satisfied. This is basically a cut-and-paste job from the Emacs buffer with GHC error messages to the buffer with the code.
Wow. I will try this next time I post. Thanks very much. -- Denis
participants (2)
-
Denis Bueno
-
oleg@okmij.org