[Haskell-beginners] Lifting Numbers
David McBride
toad3k at gmail.com
Tue Oct 3 14:01:52 UTC 2017
You can get some intuition for how this works by replacing "Moving v" with
its definition "Time -> v". Let's look at the + operation.
class Number a where
(+) :: a -> a -> a
instance Number v => Number (Moving v)
instance Number v => Number (Time -> v)
(+) :: Number v => (Time -> v) -> (Time -> v) -> (Time -> v)
So each argument of + must take a Time, the end result must also take a
Time, and whatever each argument returns must be a Number (and thus has +
defined for it). So you can sort of see how it works. + for a Moving v
takes a time, then passes that time to each of its arguments, then adds the
result.
(+) a b = \t -> (a t) Prelude.+ (b t)
data Time = Time Double -- For example.
Then you can make formulas that are rooted in time. For example
(contrived) if you are throwing a ball, the distance of the ball from you
at time f could be something like the following:
balldistance :: Moving Double
balldistance (Time f) = f * 1.2
ball1 :: Moving Double
ball1 = balldistance
ball2 :: Moving Double
ball2 = balldistance
-- the combined distance of both balls at time f
bothballs :: Moving Double
bothballs = ball1 + ball2
Then you can get the combined distance of both balls after 12 seconds, for
example.
test :: Double
test = bothballs (Time 12.0)
On Tue, Oct 3, 2017 at 9:07 AM, PATRICK BROWNE <patrick.browne at dit.ie>
wrote:
> Hi,
> I am trying to compile, run, and understand the following code from [1].
>
> type Moving v = Time -> v
>
> class Number a where
> (+), (-), (*) :: a -> a -> a
> sqr, sqrt :: a -> a
> sqr a = a * a
>
> instance Number v => Number (Moving v) where
> (+) a b = \t -> (a t) + (b t)
> (-) a b = \t -> (a t) - (b t)
> (*) a b = \t -> (a t) * (b t)
> sqrt a = \t -> sqrt (a t)
>
> I followed the compiler advice to produce the following version which
> compiles:
>
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE TypeSynonymInstances #-}
> module MovingPoint where
> type Time = Float -- Type synonym assumed, could it be data type??
> type Moving v = Time -> v
>
> class Number a where
> (+), (-), (*) :: a -> a -> a
> sqr :: a -> a
> sqrt :: a -> a
>
> instance (Floating v) => Number (Moving v) where
> (+) a b = \t -> (a t) Prelude.+ (b t)
> (-) a b = \t -> (a t) Prelude.- (b t)
> (*) a b = \t -> (a t) Prelude.* (b t)
> sqr a = \t -> (a t) Prelude.* (a t)
> sqrt a = \t -> Prelude.sqrt (a t)
>
> I do not know how to invoke any of the operations. In general I do know
> how to execute lambdas.
> I do not understand the bracketed pairs e.g. (a t).
> Any help on understanding and running the program would be appreciated.
> Thanks,
> Pat
>
>
> [1] Ontology for Spatio-temporal Databases
> http://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.
> 113.9804&rep=rep1&type=pdf
>
> This email originated from DIT. If you received this email in error,
> please delete it from your system. Please note that if you are not the
> named addressee, disclosing, copying, distributing or taking any action
> based on the contents of this email or attachments is prohibited.
> www.dit.ie
>
> Is ó ITBÁC a tháinig an ríomhphost seo. Má fuair tú an ríomhphost seo trí
> earráid, scrios de do chóras é le do thoil. Tabhair ar aird, mura tú an
> seolaí ainmnithe, go bhfuil dianchosc ar aon nochtadh, aon chóipeáil, aon
> dáileadh nó ar aon ghníomh a dhéanfar bunaithe ar an ábhar atá sa
> ríomhphost nó sna hiatáin seo. www.dit.ie
>
> Tá ITBÁC ag aistriú go Gráinseach Ghormáin – DIT is on the move to
> Grangegorman <http://www.dit.ie/grangegorman>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20171003/84aaff73/attachment.html>
More information about the Beginners
mailing list