Re: [Haskell-cafe] running and understanding a lifting program

2010-10-25 Thread Patrick Browne
Patrick,
Thanks for taking the time to get the program running.
It seems fine, but I cannot get the *md* to print out, probably missing
the Show class somewhere.

Thanks again,
Pat


Patrick LeBoutillier wrote:
 Patrick,
 
 I found this program interesting and decided to spend a bit of time on
 it, even though I'm still a newbie.
 I did a few things to simplify the code, here are some comments:
 
 1) I chose to rename the arithmetic functions in the Number class
 instead of trying to overload the real ones, I'm not that good at
 Haskell yet...
 
 2) The program had some errors, namely I think the definition of the
 Point type should be:
 
   data Point a = Point a a
 
  to allow for different types of Points.
 
 3) The Points class seemed useless in the end, I simply defined the
 dist function at the top level.
 
 4) If you import Control.Monad, it makes functions (and therefore
 Changing v) into a Monad (maybe my terminology is off here...) and
 allows you to use the general liftM and liftM2 lifting functions
 instead of defining your own.
 
 
 Here's the complete program:
 
 {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
 
 data Point a = Point { x ::a, y :: a }
 type Time = Float
 
 -- Functor Changing, which adds time parameter t to its input value.
 -- For example, Changing Float indicates a changing floating number
 -- (i.e. a function of time).
 type Changing v = Time - v
 
 -- Lifting functions
 lift1 op a = \t - op (a t)
 lift2 op a b = \t - op (a t) (b t)
 
 class Number a where
  add, sub, mul :: a - a - a
  square, squareRoot :: a - a
  square a = a `mul` a
 
 instance Number Float where
   add = (+)
   sub = (-)
   mul = (*)
   squareRoot = sqrt
 
 instance Number (Changing Float) where
   add = lift2 add
   sub = lift2 sub
   mul = lift2 mul
   squareRoot = lift1 squareRoot
 
 -- The distance operation is defined as follow
 dist :: Number a = Point a - Point a - a
 dist a b = squareRoot $ square((x a) `sub` (x b)) `add` square ((y a)
 `sub` (y b))
 
 -- Running the code
 -- If p1 and p2 are two 2D static points,
 -- their distance d is calculated as follows:
 p1, p2 :: Point Float
 p1 = Point 3.4 5.5
 p2 = Point 4.5 4.5
 
 -- distance between p1 and p2 -- 1.55
 d = dist p1 p2
 
 -- For 2D moving points mp1 and mp2, their distance md,
 -- which is a function of time, is calculated as follows:
 mp1, mp2 :: Point (Changing Float)
 mp1 = Point (\t - 4.0 + 0.5 * t) (\t - 4.0 - 0.5 * t)
 mp2 = Point (\t - 0.0 + 1.0 * t) (\t - 0.0 - 1.0 * t)
 --  distance between mp1 and mp2
 md = dist mp1 mp2
 -- distance md for time 2  5.83
 
 

 This message has been scanned for content and viruses by the DIT Information 
 Services E-Mail Scanning Service, and is believed to be clean. 
 http://www.dit.ie
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 
 Patrick
 


This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] running and understanding a lifting program

2010-10-25 Thread Patrick LeBoutillier
Patrick,

On Mon, Oct 25, 2010 at 6:12 PM, Patrick Browne patrick.bro...@dit.ie wrote:
 Patrick,
 Thanks for taking the time to get the program running.
 It seems fine, but I cannot get the *md* to print out, probably missing
 the Show class somewhere.

md is a function to which you have to give a Time value, basically
the Time at which you want to evaluate the Changing points' positions.

Try md 2 in ghci, it should give you the expected value.

Patrick



 Thanks again,
 Pat


 Patrick LeBoutillier wrote:
 Patrick,

 I found this program interesting and decided to spend a bit of time on
 it, even though I'm still a newbie.
 I did a few things to simplify the code, here are some comments:

 1) I chose to rename the arithmetic functions in the Number class
 instead of trying to overload the real ones, I'm not that good at
 Haskell yet...

 2) The program had some errors, namely I think the definition of the
 Point type should be:

       data Point a = Point a a

      to allow for different types of Points.

 3) The Points class seemed useless in the end, I simply defined the
 dist function at the top level.

 4) If you import Control.Monad, it makes functions (and therefore
 Changing v) into a Monad (maybe my terminology is off here...) and
 allows you to use the general liftM and liftM2 lifting functions
 instead of defining your own.


 Here's the complete program:

 {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}

 data Point a = Point { x ::a, y :: a }
 type Time = Float

 -- Functor Changing, which adds time parameter t to its input value.
 -- For example, Changing Float indicates a changing floating number
 -- (i.e. a function of time).
 type Changing v = Time - v

 -- Lifting functions
 lift1 op a = \t - op (a t)
 lift2 op a b = \t - op (a t) (b t)

 class Number a where
  add, sub, mul :: a - a - a
  square, squareRoot :: a - a
  square a = a `mul` a

 instance Number Float where
   add = (+)
   sub = (-)
   mul = (*)
   squareRoot = sqrt

 instance Number (Changing Float) where
   add = lift2 add
   sub = lift2 sub
   mul = lift2 mul
   squareRoot = lift1 squareRoot

 -- The distance operation is defined as follow
 dist :: Number a = Point a - Point a - a
 dist a b = squareRoot $ square((x a) `sub` (x b)) `add` square ((y a)
 `sub` (y b))

 -- Running the code
 -- If p1 and p2 are two 2D static points,
 -- their distance d is calculated as follows:
 p1, p2 :: Point Float
 p1 = Point 3.4 5.5
 p2 = Point 4.5 4.5

 -- distance between p1 and p2 -- 1.55
 d = dist p1 p2

 -- For 2D moving points mp1 and mp2, their distance md,
 -- which is a function of time, is calculated as follows:
 mp1, mp2 :: Point (Changing Float)
 mp1 = Point (\t - 4.0 + 0.5 * t) (\t - 4.0 - 0.5 * t)
 mp2 = Point (\t - 0.0 + 1.0 * t) (\t - 0.0 - 1.0 * t)
 --  distance between mp1 and mp2
 md = dist mp1 mp2
 -- distance md for time 2  5.83



 This message has been scanned for content and viruses by the DIT 
 Information Services E-Mail Scanning Service, and is believed to be clean. 
 http://www.dit.ie
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


 Patrick



 This message has been scanned for content and viruses by the DIT Information 
 Services E-Mail Scanning Service, and is believed to be clean. 
 http://www.dit.ie




-- 
=
Patrick LeBoutillier
Rosemère, Québec, Canada
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe