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:  Re: Is Haskell for me? (Nathan M. Holden)
   2. Re:  Re: Is Haskell for me? (Jon Harrop)
   3. Re:  Type classes and synonyms (Philip Scott)
   4. Re:  Type classes and synonyms (Chadda? Fouch?)
   5. Re:  Type classes and synonyms (Daniel Fischer)
   6. Re:  Type classes and synonyms (Philip Scott)
   7. Re:  Type classes and synonyms (Felipe Lessa)


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

Message: 1
Date: Sat, 21 Nov 2009 13:57:21 -0500
From: "Nathan M. Holden" <nathanmhol...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Is Haskell for me?
To: j...@ffconsultancy.com
Cc: beginners@haskell.org
Message-ID: <200911211357.21870.nathanmhol...@gmail.com>
Content-Type: Text/Plain;  charset="iso-8859-1"

I'm not a Haskell expert-- in fact, I'm a beginner, and that's why I'm here, 
but I read your blog post on the subject of this hash table program, and it 
seems to me from reading the comments in reply that you're just here trolling, 
because you're using an algorithm that is fundamentally not purely functional, 
and of course that's going to be slower, just like asking Joel Zumaya to pitch 
left handed.

If you were being honest about your complaint, you'd make an apples-to-apples 
comparison, and a number of commenters on your blog have proposed 
implementations that perform much better than your example.

Sorry if I'm just being a jerk,
Nathan M. Holden,
Haskell Beginner

On Saturday 21 November 2009 12:55:03 pm beginners-requ...@haskell.org wrote:
> Message: 4
> Date: Sat, 21 Nov 2009 18:02:33 +0000
> From: Jon Harrop <j...@ffconsultancy.com>
> Subject: Re: [Haskell-beginners] Re: Is Haskell for me?
> To: Ben Lippmeier <ben.lippme...@anu.edu.au>
> Cc: beginners <beginners@haskell.org>
> Message-ID: <200911211802.33494....@ffconsultancy.com>
> Content-Type: text/plain;  charset="iso-8859-1"
> 
> On Saturday 21 November 2009 11:56:09 Ben Lippmeier wrote:
> > Hmm. I'd be careful about conflating algorithmic complexity with memory
> > management issues.
> 
> No need. Just look at how badly the performance scales for Haskell vs other
> languages. For example, inserting 1-16 million floating point key/values
>  into a hash table:
> 
>           Haskell         OCaml         F#
>  1M:   3.198s   1.0x   1.129s  1.0x  0.080s  1.0x
>  2M:   8.498s   2.7x   2.313s  2.0x  0.138s  1.7x
>  4M:  25.697s   8.0x   4.567s  4.0x  0.281s  3.5x
>  8M:  97.994s  30.6x  10.450s  9.3x  0.637s  8.0x
> 16M: 388.080s 121.4x  23.261s 20.6x  1.338s 16.7x
> 
> Note that Haskell is 290x slower than F# on that last test.
> 
> In practice, you would turn to a purely functional dictionary in Haskell
>  based upon balanced binary trees in order to work around this
>  long-standing bug in the GC but those trees incur O(log n) indirections
>  and typically run orders of magnitude slower than a decent hash table.
> 
> Suffice to say, Haskell is nowhere near being in the ballpark of C++'s
> performance for basic functionality like dictionaries and sorting.
> 
> > By the above reasoning, if I were to run any program
> > using arrays on a system with a two space garbage collector (which copies
> > all live objects during each GC) I could say the worst case algorithmic
> > complexity was O(n). That doesn't sound right.
> 
> Can you write a program that demonstrates this effect as I did?
> 
> > I could take this further and say that in a virtual memory system, there
> > is a chance that the whole heap gets copied to the disk and back between
> > each array update.
> 
> Can you write a program that demonstrates this effect as I did?


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

Message: 2
Date: Sat, 21 Nov 2009 20:52:30 +0000
From: Jon Harrop <j...@ffconsultancy.com>
Subject: Re: [Haskell-beginners] Re: Is Haskell for me?
To: "Nathan M. Holden" <nathanmhol...@gmail.com>,
        beginners@haskell.org
Message-ID: <200911212052.30615....@ffconsultancy.com>
Content-Type: text/plain;  charset="iso-8859-1"

On Saturday 21 November 2009 18:57:21 you wrote:
> I'm not a Haskell expert-- in fact, I'm a beginner, and that's why I'm
> here, but I read your blog post on the subject of this hash table program,
> and it seems to me from reading the comments in reply that you're just here
> trolling, because you're using an algorithm that is fundamentally not
> purely functional, and of course that's going to be slower, just like
> asking Joel Zumaya to pitch left handed.
>
> If you were being honest about your complaint, you'd make an
> apples-to-apples comparison, and a number of commenters on your blog have
> proposed implementations that perform much better than your example.
>
> Sorry if I'm just being a jerk,

Not at all, that is a perfectly reasonable concern but I did already try to 
address it in my previous post:

> > In practice, you would turn to a purely functional dictionary in Haskell
> > based upon balanced binary trees in order to work around this
> > long-standing bug in the GC but those trees incur O(log n) indirections
> > and typically run orders of magnitude slower than a decent hash table.

For example, the following Haskell program builds a purely functional 
Data.Map:

module Main where

import Prelude hiding (lookup)
import Data.Map (empty, insert, lookup, size)

n = 1000000

build m 0 = m
build m n = build (insert x (1.0 / x) m) (n-1)
  where x = fromIntegral n :: Double

main = do
  let 
      m = build empty n
      (Just v) = lookup 100 m

  print $ size m
  print v

Running this program with different "n" gives:

        Data.Map
 1M:  2.797s  1.0x
 2M:  6.090s  2.2x
 4M: 14.226s  5.1x
 8M: 28.449s 10.2x
16M: 83.171s 29.7x

This is several times faster than Haskell's Data.Hashtable (because of the 
long-standing bug in their GC that I described) and is scaling better. 
However, if you compare with the timings I gave before:

      Data.Hashtable       OCaml          F#
 1M:   3.198s   1.0x   1.129s  1.0x  0.080s  1.0x
 2M:   8.498s   2.7x   2.313s  2.0x  0.138s  1.7x
 4M:  25.697s   8.0x   4.567s  4.0x  0.281s  3.5x
 8M:  97.994s  30.6x  10.450s  9.3x  0.637s  8.0x
16M: 388.080s 121.4x  23.261s 20.6x  1.338s 16.7x

you'll see that the absolute performance of this idiomatic Haskell solution is 
still absolutely awful: consistently about 50x slower than the F#.

This is also true in the context of sorting: Haskell's standard library 
routines for sorting are orders of magnitude slower than those found in most 
other compiled languages.

Suffice to say, idiomatic Haskell is also nowhere near being in the same 
ballpark as C++ with respect to performance. Realistically, with enough 
expertise you should be able to optimize most of your Haskell programs to 
beat Python's performance but there are some important cases where you will 
not even be able to do that.

-- 
Dr Jon Harrop, Flying Frog Consultancy Ltd.
http://www.ffconsultancy.com/?e


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

Message: 3
Date: Sat, 21 Nov 2009 20:33:28 +0000
From: Philip Scott <haskell-beginn...@foo.me.uk>
Subject: Re: [Haskell-beginners] Type classes and synonyms
To: beginners@haskell.org
Message-ID: <200911212033.29004.haskell-beginn...@foo.me.uk>
Content-Type: Text/Plain;  charset="iso-8859-1"

Hi ho,

> In general, however, you just need practice.  Go code! =)

Righto, I am getting stuck in with that. One last question; I've been trying 
to read up on Arrows and my mind is being boggled. Via experiment, I have 
worked out what 'second' was doing (the documentation is useless unless you 
already understand a lot of stuff I clearly don't)

For the other newbies, 'second' takes a function and a tuple, it applies the 
function to the second thing in your tuple and returns a tuple with the first 
value unchanged, and the result of applying 'f' to the second:

>  second (\x -> "fish") (10,20)
(10,"fish")

What I am struggling to understand is what on earth the type signature means:

:t second
second :: (Arrow a) => a b c -> a (d, b) (d, c)

How can (\x -> "fish") be an 'a b c' when it really looks like this:

:t (\x->"fish")
(\x->"fish") :: t -> [Char]

And I am pretty sure I never made any Arrpws...

I feel I am on the verge of understanding something deep and fundamentally 
philosophical about the typesystem but I can't quite bend my mind around to it 
:)

All the best,

Philip


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

Message: 4
Date: Sat, 21 Nov 2009 21:51:06 +0100
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Type classes and synonyms
To: Philip Scott <haskell-beginn...@foo.me.uk>
Cc: beginners@haskell.org
Message-ID:
        <e9350eaf0911211251x67b99a1bnb2ee00a9434e4...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sat, Nov 21, 2009 at 9:33 PM, Philip Scott
<haskell-beginn...@foo.me.uk> wrote:
> For the other newbies, 'second' takes a function and a tuple, it applies the
> function to the second thing in your tuple and returns a tuple with the first
> value unchanged, and the result of applying 'f' to the second:

That's what it does on a specific arrow, though generally that's the idea.

> What I am struggling to understand is what on earth the type signature means:
>
> :t second
> second :: (Arrow a) => a b c -> a (d, b) (d, c)
>
> How can (\x -> "fish") be an 'a b c' when it really looks like this:
>
> :t (\x->"fish")
> (\x->"fish") :: t -> [Char]

Right, but you must understand that (->) is a type constructor, just
like Maybe or Either or your Ts. It takes two types parameter and
return a function type. So "a -> b" is the infix syntax, but you could
write that "(->) a b" just like you can write "3 + 5" as "(+) 3 5".
Once you've done that on your function you get "(->) t Char" which
looks a bit more like "a b c"...
The final piece is that (->) is an Arrow, the most basic one but still
an Arrow, so if you replace a by (->) in the type of second, you get :
second :: (->) b c -> (->) (d, b) (d, c)
which is just
second :: (b -> c) -> (d, b) -> (d, c)
which corresponds exactly to the action of second you described
(that's the only function that could have this type, except bottom of
course).

-- 
Jedaï


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

Message: 5
Date: Sat, 21 Nov 2009 21:51:42 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Type classes and synonyms
To: beginners@haskell.org
Message-ID: <200911212151.43482.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Samstag 21 November 2009 21:33:28 schrieb Philip Scott:
> Hi ho,
>
> > In general, however, you just need practice.  Go code! =)
>
> Righto, I am getting stuck in with that. One last question; I've been
> trying to read up on Arrows and my mind is being boggled. Via experiment, I
> have worked out what 'second' was doing (the documentation is useless
> unless you already understand a lot of stuff I clearly don't)
>
> For the other newbies, 'second' takes a function and a tuple, it applies
> the function to the second thing in your tuple and returns a tuple with the
> first
>
> value unchanged, and the result of applying 'f' to the second:
> >  second (\x -> "fish") (10,20)
>
> (10,"fish")
>
> What I am struggling to understand is what on earth the type signature means:
> :t second
>
> second :: (Arrow a) => a b c -> a (d, b) (d, c)
>
> How can (\x -> "fish") be an 'a b c' when it really looks like this:
> :t (\x->"fish")
> (\x->"fish") :: t -> [Char]

a is a type variable (restricted to be a member of the Arrow class).
Now the type ghci reports for (\x -> "fish") is printed in infix form, in 
prefix form, it 
reads

:t (\x -> "fish")
(\x -> "fish") :: (->) t [Char]

so we find

a = (->)
b = t
c = [Char]

and you're using the most widespread instance of Arrow, (->).

Arrows are a generalisation of functions.

Until you're more familiar with Arrows, I suggest replacing any
(Arrow a) with (->) in the type signatures to understand what things mean in 
the familiar 
case.

Next in line would probably be Kleisli arrows (Monad m => a -> m b; it's 
wrapped in a 
newtype for Control.Arrow), break at any level of abstraction you want and 
return later.

>
> And I am pretty sure I never made any Arrpws...

There are a few others have made for you to use :)

>
> I feel I am on the verge of understanding something deep and fundamentally
> philosophical about the typesystem but I can't quite bend my mind around to
> it
>
> :)
>
> All the best,
>
> Philip



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

Message: 6
Date: Sat, 21 Nov 2009 21:07:38 +0000
From: Philip Scott <haskell-beginn...@foo.me.uk>
Subject: Re: [Haskell-beginners] Type classes and synonyms
To: beginners@haskell.org
Message-ID: <200911212107.38396.haskell-beginn...@foo.me.uk>
Content-Type: Text/Plain;  charset="utf-8"

> The final piece is that (->) is an Arrow, the most basic one but still
> an Arrow, so if you replace a by (->) in the type of second, you get :
> second :: (->) b c -> (->) (d, b) (d, c)
> which is just
> second :: (b -> c) -> (d, b) -> (d, c)

Ahh I see, very clever! There is method to the madness after all; I should 
never have doubted you Haskell. Thank you for taking the time to explain that 
:)

Do you know of any good discussions/tutorials on Arrows? I've only managed to 
find little snippets here and there

http://www.haskell.org/arrows/

Doesn't have a lot of detail and

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html

..would probably be useful once I actually understand what is going on but 
right now I think a slap in the face with a big wet fish might help me more ;)

- Philip


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

Message: 7
Date: Sat, 21 Nov 2009 19:08:33 -0200
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Type classes and synonyms
To: beginners@haskell.org
Message-ID: <20091121210833.ga...@kira.casa>
Content-Type: text/plain; charset=us-ascii

On Sat, Nov 21, 2009 at 08:33:28PM +0000, Philip Scott wrote:
> Righto, I am getting stuck in with that. One last question; I've been trying
> to read up on Arrows and my mind is being boggled. Via experiment, I have
> worked out what 'second' was doing (the documentation is useless unless you
> already understand a lot of stuff I clearly don't)
>
> For the other newbies, 'second' takes a function and a tuple, it applies the
> function to the second thing in your tuple and returns a tuple with the first
> value unchanged, and the result of applying 'f' to the second:
>
> >  second (\x -> "fish") (10,20)
> (10,"fish")
>
> What I am struggling to understand is what on earth the type signature means:
>
> :t second
> second :: (Arrow a) => a b c -> a (d, b) (d, c)
>
> How can (\x -> "fish") be an 'a b c' when it really looks like this:
>
> :t (\x->"fish")
> (\x->"fish") :: t -> [Char]
>
> And I am pretty sure I never made any Arrpws...
>
> I feel I am on the verge of understanding something deep and fundamentally
> philosophical about the typesystem but I can't quite bend my mind around to it
> :)

The problem you're facing is that you have to think of the arrow
operator (->) as a type constructor.  IOW, to unify :

    a b c     with    t -> [Char]

you have the following "assignments":

    a ~ (->)
    b ~ t
    c ~ [Char]

In another other words,

    t -> [Char]    is the same as    (->) t [Char]

Now it's easy to see whats happening.  Note that (->) is an
instance to Arrow, in GHCi:

    Prelude Control.Arrow> :i Arrow
    class (Control.Category.Category a) => Arrow a where
      arr    :: (b -> c) -> a b c
      first  :: a b c -> a (b, d) (c, d)
      second :: a b c -> a (d, b) (d, c)
      (***)  :: a b c -> a b' c' -> a (b, b') (c, c')
      (&&&)  :: a b c -> a b c' -> a b (c, c')
        -- Defined in Control.Arrow
    instance Arrow (->) -- Defined in Control.Arrow   <<< HERE <<<
    instance (Monad m) => Arrow (Kleisli m) -- Defined in Control.Arrow

Specializing those types to Arrow (->) and using the common infix
notation we have that:

      arr    :: (b -> c) -> (b -> c)
      first  :: (b -> c) -> ((b, d) -> (c, d))
      second :: (b -> c) -> ((d, b) -> (d, c))
      (***)  :: (b -> c) -> (b' -> c') -> ((b, b') -> (c, c'))
      (&&&)  :: (b -> c) -> (b' -> c') -> (b -> (c, c'))

Note that 'arr = id'. That's why we may use all Arrow functions
on, err, plain functions without having wrap everything with
'arr' (as you would with any other arrow).

It's a good exercise to try to reproduce the definition of the
Arrow (->) instance by defining the functions above.  Most
definitions, if not all, are just the corresponding free theorems
(meaning roughly that the definition follows from the type
because that's the only definition that doesn't have
undefined's).

HTH!

--
Felipe.


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

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


End of Beginners Digest, Vol 17, Issue 21
*****************************************

Reply via email to