Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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. Re:  Sub-second precision (Alex Rozenshteyn)
   2.  Re: proper way to read fold types (Ertugrul Soeylemez)
   3.  use of First or Last (Johann Bach)
   4. Re:  use of First or Last (Johan Tibell)
   5. Re:  Re: proper way to read fold types (dan portin)


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

Message: 1
Date: Sun, 25 Jul 2010 21:27:31 +0300
From: Alex Rozenshteyn <rpglove...@gmail.com>
Subject: Re: [Haskell-beginners] Sub-second precision
To: Henk-Jan van Tuyl <hjgt...@chello.nl>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <aanlktiks_c36q7wkg8v9bzyf57mpxrjv0xeui09t=...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I'm using gtk2hs (although I might try and see how wxHaskell compares when
I've got more working).

As for the repainting, I don't think I was clear enough in my initial post:
 my problem isn't how to change the value every 1/100 of a second but how to
ensure that the value I write doesn't get hugely inaccurate.  I was thinking
that I'd use the system time as the data and just draw when appropriate, but
I hadn't found something that was precise enough.

I ended up finding System.Posix.Clock, which does what I need, but I don't
know if there's something more standard.

On Sun, Jul 25, 2010 at 7:30 PM, Henk-Jan van Tuyl <hjgt...@chello.nl>wrote:

> On Sat, 24 Jul 2010 22:09:15 +0200, Alex Rozenshteyn <rpglove...@gmail.com>
> wrote:
>
>  I'm trying to write a simple timer application (mostly to learn gui
>> programming), and I'd like it to display 1/100ths of a second.  I know I
>> can
>> fake this with threadDelay, but I was wondering if there's a way to get
>> current time to more precision than one second.
>>
>>
> That depends on the type of GUI you are using, of course. If you use
> wxHaskell, you can do it like this:
>
>   t <- timer f [ interval   := 10
>>               , on command := repaint
>>               ]
>>
>
> where f is the frame handle; you don't need to use t anywhere. The interval
> is defined in milliseconds.
>
> Regards,
> Henk-Jan van Tuyl
>
>
> --
> http://Van.Tuyl.eu/
> http://members.chello.nl/hjgtuyl/tourdemonad.html
> --
>



-- 
          Alex R
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100725/69932f03/attachment-0001.html

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

Message: 2
Date: Mon, 26 Jul 2010 09:30:41 +0200
From: Ertugrul Soeylemez <e...@ertes.de>
Subject: [Haskell-beginners] Re: proper way to read fold types
To: beginners@haskell.org
Message-ID: <20100726093041.0fe70...@tritium.streitmacht.eu>
Content-Type: text/plain; charset=US-ASCII

prad <p...@towardsfreedom.com> wrote:

> i'm trying to make sense of the a vs b in foldr, so here goes:
>
> foldr takes 3 arguments:
>       1. some function f, illustrated within () of type b
>       2. some value of type b
>       3. some list with elements of type a
>
> foldr applies f to each element of [a], computing a new function (f a)
> which is then applied to the item of type b, computing a result of
> type b, which is then combined with #2 (this would be the accumulator)
>
> finally, the net computation of foldr results in some item of type b.

You think too complicated.  It's really very simple.  Look at how foldr
is defined:

  foldr f z []     = z
  foldr f z (x:xs) = x `f` foldr f z xs

In the recursive case the folding function gets its two arguments:  The
first argument is the head element of the list.  The second argument is
the result of folding the rest of the list.  You can read from this
function immediately that it really replaces each (:) by 'f' and the []
by 'z' in a right-associative manner.

  foldr (+) 0 [a,b,c] = a + (b + (c + 0))


> foldr1 takes 2 arguments:
>       1. some function g, illustrated within () of type a
>       2. some list with elements of type a
>
> foldr1 applies g to each element of [a], computing a new function (g
> a) which is then applied to a non-explicitly defined item of type a,
> computing a result also of type a.
>
> the net computation of foldr1 results in some item of type a.

Simple:

  foldr1 f [x]    = x
  foldr1 f (x:xs) = x `f` foldr1 f xs

This is just a simplified version of foldr.  The base element is passed
explicitly in foldr as 'z'.  Here the base element is just the last
element of the list to be folded.  For some folds, having an extra base
element wouldn't make much sense, for example for the 'maximum'
function:

  myMaximum = foldr1 max

This is why there is the foldr1 variant of foldr.  But of course, you
would write 'maximum' as a left fold (foldl1), not a right fold.

  foldr1 max [a,b,c] = a `max` (b `max` c)


> i know how i can use the folds in some situations, but explaining
> their type definitions to reveal how they work, is coming out pretty
> convoluted when i make the attempt. :(

Just read the type of the function and its definition.  For most
functions in Haskell, you will even find that reading the type signature
and the name of the function suffices to understand, what it does.
Trying to interpret combinators (or even to find metaphors, as many
people do) is not always the right thing to do.

However, in this case there is an easy interpretation:  It takes the
list elements and puts a binary operator between each of them.  It also
appends a base element (usually some kind of neutral element or initial
value) to the list, so that the empty list is allowed.  That's it.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/




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

Message: 3
Date: Mon, 26 Jul 2010 01:20:56 -0700
From: Johann Bach <johann.bach1...@gmail.com>
Subject: [Haskell-beginners] use of First or Last
To: beginners@haskell.org
Message-ID:
        <aanlkti=e0nm_snrdvfoavbdbusdk05p1hodd=ywf1...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I am reading "typeclassopedia" and got curious about how the monoid
instances First or Last could be applied to a real problem. Any
suggestions for improvement would be welcome.

So I imagined this problem:

We have a list of executives in a company, and their rank. Some
executives have assistants, some don't.

import Data.List
import Data.Monoid
import Data.Function

data Executive = Executive
               { name :: String
               , rank :: Int
               , assistant :: Maybe String
               }
               deriving (Show)

We want to bring an urgent matter to an executive. We'd like to
contact the highest ranking executive, but we also don't want to
disturb any executive directly, so we want to contact the highest
ranking executive with an assistant. This function finds the name of
that assistant:



findContact :: [Executive] -> Maybe String
findContact = getLast . mconcat . map (Last . assistant) . sortBy
(compare `on` rank)

data1 =
 [ Executive "Mary Poppins"   1  Nothing
 , Executive "Fred Flinstone" 2  (Just "John Deere")
 , Executive "Ann Curry"      3  (Just "Terry Crews")
 ]

> findContact data1
Just "Terry Crews"


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

Message: 4
Date: Mon, 26 Jul 2010 10:33:27 +0200
From: Johan Tibell <johan.tib...@gmail.com>
Subject: Re: [Haskell-beginners] use of First or Last
To: Johann Bach <johann.bach1...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktik_gr2+f_auky24kmddvsui3jzztqu_rnkfu...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Johann,

On Mon, Jul 26, 2010 at 10:20 AM, Johann Bach <johann.bach1...@gmail.com>wrote:

> I am reading "typeclassopedia" and got curious about how the monoid
> instances First or Last could be applied to a real problem. Any
> suggestions for improvement would be welcome.
>

The code looks fine to me.

The Last monoid is useful when parsing command line flags and you want the
last mention of a flag to have precedence. You can further extend this to
allow for default values of flags and flag definitions in config files. See
Duncan's explanation of how this is used in Cabal:

    http://www.mail-archive.com/cabal-de...@haskell.org/msg01492.html

Cheers,
Johan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100726/0e3cbfab/attachment-0001.html

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

Message: 5
Date: Mon, 26 Jul 2010 04:30:16 -0700
From: dan portin <danpor...@gmail.com>
Subject: Re: [Haskell-beginners] Re: proper way to read fold types
To: Ertugrul Soeylemez <e...@ertes.de>, p...@towardsfreedom.com,
        beginners@haskell.org
Message-ID:
        <aanlktimey3r0-qcu+n3lqg1_vwvc5z4zs7y75hwwt...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I'm still a Haskell newbie, so take this with a grain of salt: the type
signature of *foldr* and *foldr1* confuses me also. While I understand how
each operates, I've never found a description of the type signatures of
either functions which explains why the function argument of *foldr1* is of
type (a -> a -> a) instead of (a -> b -> b). This is the conclusion I came
to. Hopefully it helps; if it's wrong, then hopefully it can be corrected.

Suppose we have a list M = [x1, x2, ..., x(n-1), xn], and we evaluate the
function:

foldr1 *f* M = *f* x1 (*f* x2 ... (*f* x(n-1) xn) ...)

We know that for all xi <- M, xi has type *a*. Suppose that the
function *f*has type (
*a* -> *b* -> *c*) and consider the expression *f* x(i-1) xi, where x(i-1),
xi <- M. Since x(i-1) and xi have type *a*, the expression is well-typed
only if the type *b* is the same as *a*. Because each such expression
resulting from folding *f* into M becomes the second argument to *f*, the
result of evaluating *f* must be a value of type *a*. That is, *c* must be
the same type as *a*.

With *foldr*, however, this isn't necessarily the case. Suppose we have a
list N = [x1, x2, ..., xn], and we evaluate the function:

foldr *f* **v N = *f* x1 (*f* x2 ... (*f* xn v) ...)

There is no reason that *v* must have the same type as each xi <- N, since *
v* is not derived from N. You can see that as *foldr* is evaluated, starting
from the most nested *f*, the value bound to the second argument of each
occurrence of *f* has the same type as the value which is the result of
evaluating *f*. If this is the case, however, then the type of the value
which results from evaluating *foldr*, where *v* has type *b*, must be a
value of type *b*.

You might, however, define a function using *foldr* and *foldr1* which
produce the same result. For instance,

mySum list = foldr (+) 0 list
mySum' list = foldr1 (+) list

In this case, (+) :: (a -> a -> a). So *b* is the same type as *a* and all
is well.




On Mon, Jul 26, 2010 at 12:30 AM, Ertugrul Soeylemez <e...@ertes.de> wrote:

> prad <p...@towardsfreedom.com> wrote:
>
> > i'm trying to make sense of the a vs b in foldr, so here goes:
> >
> > foldr takes 3 arguments:
> >       1. some function f, illustrated within () of type b
> >       2. some value of type b
> >       3. some list with elements of type a
> >
> > foldr applies f to each element of [a], computing a new function (f a)
> > which is then applied to the item of type b, computing a result of
> > type b, which is then combined with #2 (this would be the accumulator)
> >
> > finally, the net computation of foldr results in some item of type b.
>
> You think too complicated.  It's really very simple.  Look at how foldr
> is defined:
>
>  foldr f z []     = z
>  foldr f z (x:xs) = x `f` foldr f z xs
>
> In the recursive case the folding function gets its two arguments:  The
> first argument is the head element of the list.  The second argument is
> the result of folding the rest of the list.  You can read from this
> function immediately that it really replaces each (:) by 'f' and the []
> by 'z' in a right-associative manner.
>
>  foldr (+) 0 [a,b,c] = a + (b + (c + 0))
>
>
> > foldr1 takes 2 arguments:
> >       1. some function g, illustrated within () of type a
> >       2. some list with elements of type a
> >
> > foldr1 applies g to each element of [a], computing a new function (g
> > a) which is then applied to a non-explicitly defined item of type a,
> > computing a result also of type a.
> >
> > the net computation of foldr1 results in some item of type a.
>
> Simple:
>
>  foldr1 f [x]    = x
>  foldr1 f (x:xs) = x `f` foldr1 f xs
>
> This is just a simplified version of foldr.  The base element is passed
> explicitly in foldr as 'z'.  Here the base element is just the last
> element of the list to be folded.  For some folds, having an extra base
> element wouldn't make much sense, for example for the 'maximum'
> function:
>
>  myMaximum = foldr1 max
>
> This is why there is the foldr1 variant of foldr.  But of course, you
> would write 'maximum' as a left fold (foldl1), not a right fold.
>
>  foldr1 max [a,b,c] = a `max` (b `max` c)
>
>
> > i know how i can use the folds in some situations, but explaining
> > their type definitions to reveal how they work, is coming out pretty
> > convoluted when i make the attempt. :(
>
> Just read the type of the function and its definition.  For most
> functions in Haskell, you will even find that reading the type signature
> and the name of the function suffices to understand, what it does.
> Trying to interpret combinators (or even to find metaphors, as many
> people do) is not always the right thing to do.
>
> However, in this case there is an easy interpretation:  It takes the
> list elements and puts a binary operator between each of them.  It also
> appends a base element (usually some kind of neutral element or initial
> value) to the list, so that the empty list is allowed.  That's it.
>
>
> Greets,
> Ertugrul
>
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100726/11afba04/attachment.html

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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 25, Issue 51
*****************************************

Reply via email to