[Haskell-beginners] Re: [Haskell-cafe] running and understanding a
lifting program
Bastian Erdnüß
earthnut at web.de
Mon Oct 25 09:05:54 EDT 2010
On Oct 24, 2010, at 15:12, Patrick Browne wrote:
> hi,
> I am trying to run and understand a lifting program from [1].
> The program lifts points to moving points that vary their position over
> time.
> I made some effort to run the progrm but I do not know how to overide
> the +,-,*,sqr, and sqrt from the Num class. Below is my current attempt.
>
> I do not wish to change or imporve the code, rather I wish to understand
> it as it stands and find out what needs to be added to get the outputs
> shown below i.e. distance between points p1 and p2 --> 1.55 and the
> distance between moving points mp1 and mp2 for time 2 ----> 5.83.
I got pretty close with
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
import Prelude hiding ((+), (-), (*), sqrt)
import qualified Prelude
data Point a = Point a a
type Time = Float
type Changing v = Time -> v
lift0 a = \t -> a
lift1 op a = \t -> op (a t)
lift2 op a b = \t -> op (a t) (b t)
class PlusMinus a where
(+), (-) :: a -> a -> a
instance PlusMinus Float where
(+) = (Prelude.+)
(-) = (Prelude.-)
instance PlusMinus s => PlusMinus (Point s) where
(+) (Point x y) (Point x' y') = Point (x+x') (y+y')
(-) (Point x y) (Point x' y') = Point (x-x') (y-y')
class PlusMinus a => Number a where
(*) :: a -> a -> a
sqr, sqrt :: a -> a
sqr a = a * a
instance Number Float where
(*) = (Prelude.*)
sqrt = Prelude.sqrt
class Number s => Points s where
x, y :: Point s -> s
x (Point x' y') = x'
y (Point x' y') = y'
dist :: Point s -> Point s -> s
dist (Point x y) (Point x' y') = sqrt $ sqr (x-x') + sqr (y-y')
instance Points Float
instance PlusMinus v => PlusMinus (Changing v) where
(+) = lift2 (+)
(-) = lift2 (-)
instance Number v => Number (Changing v) where
(*) = lift2 (*)
sqrt = lift1 sqrt
instance Points (Changing Float)
> [1] A Mathematical Tool to Extend 2D Spatial Operations
> to Higher Dimensions: by Farid Karimipour1,2, Mahmoud R. Delavar1, and
> Andrew U. Frank2
>
> http://books.google.ie/books?id=JUGpGN_jwf0C&pg=PA153&lpg=PA153&dq=Karimipour+%22A+Mathematical+Tool+to+Extend+2D+Spatial+Operations+to+Higher+Dimensions%22&source=bl&ots=fu-lSkPMr3&sig=ztkcRV3Cv6hn9T6iwQCJ9sB75IM&hl=en&ei=QS7ETJHPGoiA5Ab0zZW6Aw&sa=X&oi=book_result&ct=result&resnum=4&ved=0CCMQ6AEwAw#v=onepage&q=Karimipour%20%22A%20Mathematical%20Tool%20to%20Extend%202D%20Spatial%20Operations%20to%20Higher%20Dimensions%22&f=false
Cheers,
Bastian
More information about the Beginners
mailing list