Reputation: 253
I am trying to understand the code in Listing 1, which lifts the basic numeric operation to produces time varying numbers. The time varying numbers are then used to calculate distances between points at differing times. The calculation of moving distances "seems" to require the application of several lambda functions to one Time
argument. I am not sure of the exact evaluation mechanism that allows the one single argument to be applied to the distance calculation in:
(dist mp1 mp2) 2.0
(1)
I have a basic understanding of lambda expressions and lifting, but I do not understand their combination in this code. Any insight into the detailed evaluation of (1) would be appreciated.
Listing 1
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
module MovingPoint where
data Point a = Point { x ::a, y :: a } deriving Show
type Time = Double
type Moving 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
sqr, sqrt1 :: a -> a
sqr a = a `mul` a -- default def
-- define Number operations using builtin Num class
instance Number Double where
add = (+)
sub = (-)
mul = (*)
sqrt1 = sqrt
-- The calculation of the distance between two points
dist :: Number a => Point a -> Point a -> a
dist a b = sqrt1 (sqr((x a) `sub` (x b)) `add` sqr ((y a) `sub` (y b)))
-- Lift numbers. LHS ops are for (Moving Double), RHS ops are for Double
instance Number (Moving Double) where
add = lift2 add
sub = lift2 sub
mul = lift2 mul
sqrt1 = lift1 sqrt1
sqr = lift1 sqr
mp1, mp2 :: Point (Moving Double)
mp1 = Point (\t -> (4.0 `add` (0.5 `mul` t))) (\t -> (4.0 `sub` (0.5 `mul` t)))
mp2 = Point (\t -> (0.0 `add` (1.0 `mul` t))) (\t -> (0.0 `sub` (1.0 `mul` t)))
-- distance between mp1 and mp2 at times 2.0 and 10.0
md1 = (dist mp1 mp2) 2.0 -- > 5.8
md2 = (dist mp1 mp2) 10.0 -- > 9.05
Comment on Answer
I could not format the comment properly, so I have added it here. Focusing on the sub
in sqr
,
sqrt1 (sqr((\t -> (4.0 + 0.5 * t)) sub (\t -> (0.0 + 1.0 * t))) ...)
= Both arguments of this sub
are (Moving Double)
so use def (lift2 (op) a b = \t -> (a t) op (b t))
using infix notation.
sqrt1 (sqr(\t -> (4.0 + 0.5 * t) - (0.0 + 1.0 * t)) ...)
I am unsure how the two \t
s became one \t
. Obviously I am missing something.
Upvotes: 2
Views: 127
Reputation: 116174
To evaluate (dist mp1 mp2) 2.0
let's start with the function, dist mp1 mp2
:
dist mp1 mp2
= -- def dist
sqrt1 (sqr((x mp1) `sub` (x mp2)) `add` sqr ((y mp1) `sub` (y mp2)))
= -- replace the cooridanates of the two points
sqrt1 (sqr((\t -> (4.0 `add` (0.5 `mul` t)))
`sub`
(\t -> (0.0 `add` (1.0 `mul` t))))
`add` ...) -- omitting the similar part
= -- the inner `add`, `mul` are the Double ones
sqrt1 (sqr((\t -> (4.0 + 0.5 * t)))
`sub`
(\t -> (0.0 + 1.0 * t))))
`add` ...)
= -- `sub` instead is the lifted subtraction since it's applied to `Moving Double`s
sqrt1 (sqr(\t -> (4.0 + 0.5 * t) - (0.0 + 1.0 * t))
`add` ...)
= -- `sqr` is lifted for the same reason
sqrt1 ((\t -> sqr((4.0 + 0.5 * t) - (0.0 + 1.0 * t)))
`add` ...)
= -- `add` is lifted, let the ... above be (\t -> ...2)
sqrt1 (\t -> sqr((4.0 + 0.5 * t) - (0.0 + 1.0 * t)) + ...2)
= -- `sqrt1` is lifted
\t -> sqrt (sqr((4.0 + 0.5 * t) - (0.0 + 1.0 * t)) + ...2)
Finally, we can apply the last lambda to 2.0
as wanted, and get the Double
result.
Note that, to understand the above computation, it is crucial to keep in mind which expressions evaluate to Double
s and which ones evaluate to Moving Double
s, so that we can lift as needed.
Upvotes: 3