[Haskell-cafe] Re: HList error with hFoldr

2008-02-02 Thread Denis Bueno
On Jan 28, 2008 12:45 AM,  [EMAIL PROTECTED] wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HList error with hFoldr

2008-01-27 Thread oleg

 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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HList error with hFoldr

2008-01-26 Thread Denis Bueno
On Sat, Jan 26, 2008 at 1:59 AM,  [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: HList error with hFoldr

2008-01-26 Thread Denis Bueno
On Sat, Jan 26, 2008 at 11:03 AM, Denis Bueno [EMAIL PROTECTED] wrote:
  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe