Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Lifting Numbers (PATRICK BROWNE)
   2. Re:  Lifting Numbers (David McBride)
   3. Re:  Lifting Numbers (PATRICK BROWNE)


----------------------------------------------------------------------

Message: 1
Date: Tue, 3 Oct 2017 14:07:01 +0100
From: PATRICK BROWNE <patrick.bro...@dit.ie>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] Lifting Numbers
Message-ID:
        <CAGFLrKe=le0s3bq_xuguutxbwcwlcs0ca5hjl0f+6p5q0mv...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20171003/546eb846/attachment-0001.html>

------------------------------

Message: 2
Date: Tue, 3 Oct 2017 10:01:52 -0400
From: David McBride <toa...@gmail.com>
To: Patrick Browne <patrick.bro...@dit.ie>,  The Haskell-Beginners
        Mailing List - Discussion of primarily beginner-level topics related
        to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Lifting Numbers
Message-ID:
        <can+tr42o6rofkokkytb4yukngqhiz0lfuwrzd9gspni5p2v...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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.bro...@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@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-0001.html>

------------------------------

Message: 3
Date: Tue, 3 Oct 2017 20:15:37 +0100
From: PATRICK BROWNE <patrick.bro...@dit.ie>
To: David McBride <toa...@gmail.com>
Cc: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Lifting Numbers
Message-ID:
        <CAGFLrKf8-U9=ktjEyvR=1jXK6ps0wGW=VyuwqiL_D3Q=u-m...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

David,
Thank you for you informative and helpful reply.
I think that are two issues impeding my understanding of the original code.
1. The use of lambda
2. The structure of the class and instance

1. The use of lambda
Is seems that the arguments to (+!) , below ,must be functions. I was
trying to use values
data Time  = Time Double

type Moving v  = Time -> v

(+!) a b = \t -> (a t)  Prelude.+ (b t)

b ::  Moving Double

b (Time x) = x * 1.5

test = (b +! b) (Time 10.0)

Is my take on this correct?


2. The structure of the class and instance.
Recall the original code:

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 believe that this would have to be changed to avoid a clash with the
Prelude definitions.
Is the following structuring reasonable?

module MovingPoint where
data  Time  = Time Double
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)

b ::  Moving Double
b (Time x) = x Prelude.* 1.5
test = (b MovingPoint.+ b) (Time 10.0)

Thanks,
Pat






On 3 October 2017 at 15:01, David McBride <toa...@gmail.com> wrote:

> 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.bro...@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@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>

-- 


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>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20171003/b7599b76/attachment.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 112, Issue 4
*****************************************

Reply via email to