[Haskell-cafe] collection monads

2006-10-08 Thread tpledger
Matthias Fischmann wrote:
> > Do you expect the contained type x to change during a
> > sequence of monadic actions?  e.g. would you ever use
(>>=)
> > at the type 'Permutation Int -> (Int -> Permutation
Bool) ->
> > Permutation Bool'?
>
> no, i don't need that.  but aside from
> the fact that
>
> > data Permutation k v =
> > Permutation [(k, v)]
> > instance (Ix k) =>
> > Monad (Permutation k)
>
> is redundant (i think of the permutation
> as a function applicable to arbitrary
> lists): how would that change anything?
> my definition of return still doesn't
> work.  or how would you redefine
> 'return'?

Ah.  Yes, my approach falls over because it lacks two
things.  #1: a distinguished value of the Ix-constrained
type k, to pair off with return's argument.  #2: a purpose. 
I don't have a clear idea of what a do-block in a
permutation monad ought to mean.  Whoops!  :-]

Regards,
Tom (crawling back under his rock)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell speaking Spanish

2006-10-08 Thread Bulat Ziganshin
Hello Luis,

Friday, October 6, 2006, 6:52:04 AM, you wrote:

> I have recently started editing a page on the Haskell.org wiki site
> dedicated to our spanish-speaker community.[0]

i had the same idea about Russian page although still not implemented it

> I also expect we could get some of the main Haskell wiki pages translated,
> at least the most popular pages.[1]

great idea!

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trying to understand HList / hSequence now (it works, but why?! :-0)

2006-10-08 Thread Matthias Fischmann


Hi,

here is how you do sequencing for HList, and a question why the type
signatures are valid.  Here is the code:


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module Foo where
import Char
import HListPrelude

class (Monad m, HList l) => HSequence m l l' | l -> m l'
where hSequence :: l -> m l'

instance (Monad m, HSequence m HNil HNil) => HSequence m HNil HNil 
where hSequence _ = return HNil

instance (Monad m, HSequence m l l') => HSequence m (HCons (m a) l) (HCons a l')
where hSequence (HCons ma ml) = do
a <- ma
l <- hSequence ml
return (HCons a l)

hlist = HCons (Just 1) (HCons (Just 'c') HNil)
testHSequence = hSequence hlist

*Foo> testHSequence
Just (HCons 1 (HCons 'c' HNil)) :: Maybe (HCons Integer (HCons Char HNil))


what staggers me is the instance declaration of "HSequence m HNil
HNil": how can i use the goal of the declaration as one of the
conditions without causing some sort of black hole in the type
inference algorithm?

also i wanted to show off with the code :-).  should i submit it
somewhere?

cheers,
matthias


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] collection monads

2006-10-08 Thread Matthias Fischmann

On Sun, Oct 08, 2006 at 10:57:46PM +1300, [EMAIL PROTECTED] wrote:
> To: haskell-cafe@haskell.org
> From: [EMAIL PROTECTED]
> Date: Sun, 08 Oct 2006 22:57:46 +1300
> Subject: [Haskell-cafe] collection monads
> 
> Matthias Fischmann wrote:
> > > Do you expect the contained type x to change during a
> > > sequence of monadic actions?  e.g. would you ever use
> (>>=)
> > > at the type 'Permutation Int -> (Int -> Permutation
> Bool) ->
> > > Permutation Bool'?
> >
> > no, i don't need that.  but aside from
> > the fact that
> >
> > > data Permutation k v =
> > > Permutation [(k, v)]
> > > instance (Ix k) =>
> > > Monad (Permutation k)
> >
> > is redundant (i think of the permutation
> > as a function applicable to arbitrary
> > lists): how would that change anything?
> > my definition of return still doesn't
> > work.  or how would you redefine
> > 'return'?
> 
> Ah.  Yes, my approach falls over because it lacks two
> things.  #1: a distinguished value of the Ix-constrained
> type k, to pair off with return's argument.  #2: a purpose. 
> I don't have a clear idea of what a do-block in a
> permutation monad ought to mean.  Whoops!   color=red>:-]

yes, me neither.  i thought of something like sequencial execution of
permutations, and was hoping it was similar enough to strings and
concat / join.  but it seems it's something else...

ok, permutations are not that monadic, really.  i'll try to live with
it.  (-:


matthias


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Yang

This email actually turned out much longer than I expected, but I hope
it sparks interesting (and hopefully, thorough!) discussion on points
that weren't touched on by previous threads on this topic. What
follows describes my journey thus far exploring what I see (as a
newcomer to Haskell) as a major problem with Haskell - the ease with
which users can write inefficient code, and have no idea that they
did. Some of this has to do with laziness, some of it with the
functional programming in general. My goal is to achieve (as a link
further down says) *good* performance, not blazing performance. I.e.,
I want to avoid what should really be no-brainers such as
little-omega(1) space utilization for simple folds.

The first version of a simple program I wrote was reasonably "clean."
(Throughout this email, "clean" is supposed to mean some combination
of: clear, compact, modular, elegant, etc.) It's a polynomial adder,
which takes in lists of (coefficient, degree) tuples, combining terms
of the same degree and maintaining a sorted order of least-to-greatest
degree:

type Poly = [(Int,Int)]

addPoly1 :: Poly -> Poly -> Poly
addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t)
   | p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t
   | p1d < p2d = p1h : addPoly1 p1t p2
   | p1d > p2d = p2h : addPoly1 p1 p2t
addPoly1 p1 [] = p1
addPoly1 [] p2 = p2
addPoly1 [] [] = []

But this doesn't use tail recursion/accumulation (which seems to me
like a complete hack that is a mandatory price to pay for using FP),
so I rewrote it:

addPoly :: Poly -> Poly -> Poly
addPoly p1 p2 =
   let addPoly' p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t) result
   | p1d == p2d = addPoly' p1t p2t ((p1c + p2c, p1d):result)
   | p1d > p2d = addPoly' p1 p2t (p2h:result)
   | p1d < p2d = addPoly' p1t p2 (p1h:result)
   addPoly' (p1:p1s) [] result = addPoly' p1s [] (p1:result)
   addPoly' [] (p2:p2s) result = addPoly' [] p2s (p2:result)
   addPoly' [] [] result = reverse result
   in addPoly' p1 p2 []

But laziness will cause this to occupy Theta(n)-space of cons-ing
thunks. (See appendix for a simpler example.) My third iteration will
become even uglier because I will have to incorporate strictness and
things like $! or seq. And there's probably a whole host of other
issues that I haven't even thought of or don't know about (boxing,
space leaks, etc.).


From #haskell, I got a general piece of advice:


Oct 07 22:37:20 Actually, a lot of the time, code gets messy
when people optimise because they take the wrong road to optimisation
Oct 07 22:37:31 There are two ways to optimise a piece of Haskell code
Oct 07 22:37:43 You can make it stricter, forcing evaluation to
occur sooner
Oct 07 22:38:01 Or you can make it lazier, ensuring that things
are not demanded until actually needed
Oct 07 22:38:09@wiki performance
Oct 07 22:38:09http://www.haskell.org/haskellwiki/performance
Oct 07 22:38:13 the latter route actually tends to result in cleaner 
code

Of course, to want to learn route 2 was a no-brainer. I read through
that wiki page on laziness and various other resources, but was
disappointed in what I found:

http://www.haskell.org/haskellwiki/Performance/Laziness only discusses
the aspect of laziness where you only evaluate what you need, which by
now has been repeatedly beaten into my head and sounds obvious. Aren't
there other advantages to laziness? Or at least, am I not fully
appreciating the "obvious" work-avoiding part of laziness? For
instance, the example seems to allude to sharing (between the even and
odd functions), which I think ties in strongly with laziness. I was
hoping for more in-depth insights on how to take advantage of laziness
to write cleaner AND more efficient code. (A loose analogy exists in
computer architecture - the smaller the chip, the less power it can
consume/the faster it can clock.)

http://en.wikibooks.org/wiki/Haskell/Laziness_revisited does slightly
better but still just scratches the surface - it gives an example of a
clean (compact and modular) yet efficient piece of code
(isSubstringOf), then completely neglects explaining it (e.g., exactly
why/how does it run more efficiently?).

http://users.aber.ac.uk/afc/stricthaskell.html seems to suggest that
strictness is the way to go. Please say it ain't so!

http://www.algorithm.com.au/mt/haskell/haskells_performance.html says
that between code optimized for performance in Haskell and in another
language (like O'Caml), "which is more declarative, high-level, and
most importantly, which one doesn't require an expert in the language
to write" is an unfortunate (for Haskell fans) no-brainer:

"The problem then is you have to know why something is slow, and
there's where Haskell can get complex. Is there a space leak? (Do you
even know what a space leak is?) Is your array strict instead of lazy?
If it's strict, is it boxed instead of unboxed? (Do you even know what
unboxing is?) Can you use unsafeRe

[Haskell-cafe] Trying to serialize HList

2006-10-08 Thread Matthias Fischmann


... and here is the code I am giving up on for today: Serialization of
HLists.  Questions below.


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}

module Foo where
import Char
import List
import Monad
import Permutation
import HListPrelude  -- [1] http://web.engr.oregonstate.edu/~erwig/pfp/


-- Serializable is like Show, but
--   (a) it carries explicit type information, and
--   (b) it allows for serializing IORefs etc.

class Serializable s
where
serialize :: s -> IO String
deSerialize :: String -> IO s

instance Serializable Int where
serialize = return . ("Int::" ++) . show
deSerialize s | isPrefixOf "Int::" s = return . (read :: String -> Int) . 
drop 5 $ s

instance Serializable Char where
serialize = return . ("Char::" ++) . show
deSerialize s | isPrefixOf "Char::" s = return . (read :: String -> Char) . 
drop 6 $ s


-- SList is a list of heterogenous serializable elements...
class HList l => SList l
instance SList HNil
instance (Serializable s, SList ss) => SList (HCons s ss)

-- ... so it should be possible to write instantiate Serializable, right?:
instance (SList s, HMapOut Serialize s (IO String)) => Serializable s
where
serialize = liftM show . (sequence :: [IO String] -> IO [String]) . hMapOut 
Serialize
deSerialize = error "Not yet.  (I am not even done with serialize yet.)"

-- Seems we need the trick from the paper that oleg pointed out to me earlier 
in this thread:
data Serialize = Serialize
instance (Serializable s) => Apply Serialize s (IO String) where apply _ = 
serialize


-- Example:
slist = HCons (1 :: Int) (HCons ('c' :: Char) HNil)

test1 = serialize slist
-- (This is where -fallow-overlapping-instances helps.  There is a
-- section in [1] on how to get rid of it, which I haven't read yet.)

test2 :: IO (HCons Int (HCons Char HNil))
test2 = test1 >>= deSerialize


Two questions:

 (1) Do you see any reasons why it should be impossible in principle
 to write deSerialize for the SList instance of Serializable?  (I
 think the answer is "it's possible to write it, but you need to
 add quite some type information by hand".)

 (2) The problem with test2 is that I need to know its precise
 object-level type, ie which types occur at which positions in the
 SList.  I am pretty sure this is a restriction I have to live
 with.  Please tell me I am wrong.  (-:  (I think my application
 will make it possible for ghc to infer the type, which is fixed
 at compile time anyways, so it's not a severe restriction.)

 (3) (bonus question :) Who wants to write deSerialize for SLists for
 me?

And another one: Why do I need to list the HMapOut instance in the
context of the instance declaration of Serializable for SLists?  (It's
not a big deal, but I can't see why it can't be inferred automatically
from the rest of the code.)

Possibly back with another issue of my HList diary tomorrow.  (Please
tell me if you find this interesting or if you would like me to stop
being so verbose.)

cheers,
Matthias


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell performance (again)!

2006-10-08 Thread apfelmus
Hello,

admittedly, there is a lack of material on lazy evaluation and
performance. IMHO, the current wiki(book) and other articles are
somewhat inadequate which stems from the fact that current rumor is
"strictness is fast" and "arrays must be unboxed" or so. I don't agree
with this, so I post some remarks about performance in general and with
laziness in particular.


My first remark about performance is unfair and amounts to discuss the
issue away:
* The programmers viewpoint about performance in Haskell should be a
lazy one, i.e. you think about the performance of your code only when
its forced by someone else. If no one complains, do not even waste a
second thinking about it.

So

> type Poly = [(Int,Int)]
>
> addPoly1 :: Poly -> Poly -> Poly
> addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t)
>| p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t
>| p1d < p2d = p1h : addPoly1 p1t p2
>| p1d > p2d = p2h : addPoly1 p1 p2t
> addPoly1 p1 [] = p1
> addPoly1 [] p2 = p2
> addPoly1 [] [] = []

is the right thing to do. Point. With that viewpoint, your sorrows will
fade away :) Mine do.

In my experience, clean code by far outweighs any performance issues as
it allows one to reduce the complexity of the programming task until it
actually becomes tractable. As example, Darcs' patch mechanism is almost
impossible to code in a non-functional language. And what about those
open source / freeware game web sites where one reads "at some point my
code base became absolutely unmaintainable and I had to abandon this
project" ?

Linked to that is the advent of scripting languages like perl, python,
tcl. Why do people use these interpreted languages as there are the
coffins of performance? IMHO, there also already is the trend to buy
medium abstraction (Java, Objective-C) by deliberately selling away
performance (Java programs are so lame, Objective-C can be speed up 10%
by optimizing the msg_send() assembly) and i think: Haskell has a much
better benefit-to-cost ratio then the others.


The second remark is:
* On machine level, Laziness is an overhead, but it's only a constant
factor. *Constant factor*!

There is a story about this in S. Skiena's "The Algorithm Design Manual"
where some guy eats all the CPU of a supercomputer for a stupid task
which he programmed using an asymptotically mediocre algorithm. Ouch.

This already applies to your polynomials: are you sure [(Int,Int)] is
the right data structure to fulfill your performance requirements on the
asymptotic running time of your intended operation? Or should you use
  Data.Map Int Int
which grants O(log n) random access (by index i) to every coefficient
a_i as opposed to the list case where you can only fetch a_i in O(n) time?
The answer is that your original representation is quite suitable as the
common operations +,*,diff,evaluation etc. for polynomials have no "a
priori" knowledge about which coefficients are 0 and which are not, they
have to discover it anyway. Only internally * needs a finite map to
collect common degrees. You can even write a function sum ::
[Polynomial] -> Polynomial which uses a finite map to collect degrees
and define + and * in terms of it.

By the way, I don't know any imperative hobby programmer for which
mutable arrays are not the one and for all collection data structure.
Haskell offers a much easier access to data structures like binary
search trees with appropriate polymorphism. IMHO, Haskell is even the
first language to have a binary search tree library which offers
satisfying generality and ease of use. This makes your program faster!


Only the third remark starts to be about performance in Haskell itself:
* Haskell is a lazy language. Why to make this your enemy, why to swim
against the currents by making your programs more strict?

As I remember, Cale once said on IRC how the relative strength of
strictness / laziness applies on functions which operate on the
different data sizes:
small -> smalldoesn't really matter
  (minor lazy overhead but we have
   strictness analysis)
large -> small
  every part of the large thing is needed in calculation
  strictness wins
large -> small
  only parts are needed
  lazyness wins
large -> largedepends on large input like above
  but roughly same otherwise
small -> largeroughly same

Only in the case where strictness wins, you have to insert a seq or two.
 As a rule of thumb, all recursive data structures like lists and trees
are large. Int's are small. The point is that when you are given an Int,
the first look at it will reveal all information about it. In case of a
list, a first look only reveals the first element.

What was the primary reason for laziness, anyway? The famous paper "Why
functional programming matters" by John Hughes gives the answer: you can
code programs in a more modular way (and this without biting performance
penalties). Laziness is what makes compositions like 

Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread ihope

On 10/8/06, Yang <[EMAIL PROTECTED]> wrote:

And do most (experienced) Haskell
users sacrifice cleanliness for speed, or speed for cleanliness?


Keep the internals of your code--that which will be looked at a
lot--fast and ugly, while the rest can be clean. If you have a
function that does something very simple, but the "pretty" way to do
it takes a second to run while the ugly way is much, much faster, use
the pretty one if it's only going to be needed once or twice. It's
certainly not the kind of thing you want to fold your lists with: use
the ugly version for that.

Also, if you want, you can write both a pretty version and an ugly
version, and put the pretty version in comments while the ugly version
does all the real work.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread ihope

On 10/8/06, ihope <[EMAIL PROTECTED]> wrote:

Keep the internals of your code--that which will be looked at a
lot--fast and ugly, while the rest can be clean.


Sorry. Meant "that which will be used a lot".
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Jason Dagit

On 10/8/06, ihope <[EMAIL PROTECTED]> wrote:

On 10/8/06, Yang <[EMAIL PROTECTED]> wrote:
> And do most (experienced) Haskell
> users sacrifice cleanliness for speed, or speed for cleanliness?

Keep the internals of your code--that which will be looked at a
lot--fast and ugly, while the rest can be clean. If you have a
function that does something very simple, but the "pretty" way to do
it takes a second to run while the ugly way is much, much faster, use
the pretty one if it's only going to be needed once or twice. It's
certainly not the kind of thing you want to fold your lists with: use
the ugly version for that.

Also, if you want, you can write both a pretty version and an ugly
version, and put the pretty version in comments while the ugly version
does all the real work.


Another good idea when you have a pretty version which is easy to
verify for correctness and an ugly version that is harder to verify is
to use QuickCheck or SmallCheck and define a property that says both
versions are equal for all inputs.  Ugly code is notorious for holding
bugs, but doing this would help test the ugly code.

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Duncan Coutts
On Sun, 2006-10-08 at 15:25 -0700, Jason Dagit wrote:

> Another good idea when you have a pretty version which is easy to
> verify for correctness and an ugly version that is harder to verify is
> to use QuickCheck or SmallCheck and define a property that says both
> versions are equal for all inputs.  Ugly code is notorious for holding
> bugs, but doing this would help test the ugly code.

This is exactly how we tested Data.ByteString and to great effect I
think. We uncovered loads of bugs during testing. The few bugs uncovered
by our users since it has been released have invariably been in things
we didn't have QC properties for.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Donald Bruce Stewart
duncan.coutts:
> On Sun, 2006-10-08 at 15:25 -0700, Jason Dagit wrote:
> 
> > Another good idea when you have a pretty version which is easy to
> > verify for correctness and an ugly version that is harder to verify is
> > to use QuickCheck or SmallCheck and define a property that says both
> > versions are equal for all inputs.  Ugly code is notorious for holding
> > bugs, but doing this would help test the ugly code.
> 
> This is exactly how we tested Data.ByteString and to great effect I
> think. We uncovered loads of bugs during testing. The few bugs uncovered
> by our users since it has been released have invariably been in things
> we didn't have QC properties for.

Yes, I agree with this. By checking fast-bug-ugly code against
slow-but-obvious code, we were able to catch bugs before Data.ByteString
was deployed in the outside world, and before the bugs could hurt
anyone. These days, Data.ByteString has some 2000 lines of QC
properties, which are run on ever darcs commit.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Udo Stenzel
Yang wrote:
> type Poly = [(Int,Int)]
> 
> addPoly1 :: Poly -> Poly -> Poly
> addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t)
>| p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t
>| p1d < p2d = p1h : addPoly1 p1t p2
>| p1d > p2d = p2h : addPoly1 p1 p2t
> addPoly1 p1 [] = p1
> addPoly1 [] p2 = p2
> addPoly1 [] [] = []
> 
> But this doesn't use tail recursion/accumulation

Indeed it doesn't.  Now remind me, why is that supposed to be a Bad
Thing?  The above code exhibits a maximum of lazyness and runs with no
useless space overhead.  Apart from the expression (p1c + p2c), which
you probably want to evaluate eagerly, it is close to perfect.

> so I rewrote it: [...]
> 
> But laziness will cause this to occupy Theta(n)-space of cons-ing
> thunks.

No, it doesn't.  Insisting on accumulator recursion does.  Actually,
using reverse does.  Think about it, a strict reverse cannot use less
than O(n) space, either.


> I was
> hoping for more in-depth insights on how to take advantage of laziness
> to write cleaner AND more efficient code.

Try to explain why your first iteration was bad.  You'll achieve
enlightenment at the point where your explanation fails.


Udo.
-- 
Hast du zum Leben kein Motiv --
steig mal vor, vielleicht geht's schief.
-- aus einem Gipfelbuch


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bizarre garbage collection behaviour

2006-10-08 Thread Guillaume Theoret

I'm using Hugs98 for .NET and I'm running into some bizarre garbage
collection issues. I hope I'm posting at the right spot. I didn't want
to post this in Hugs bugs since I'm pretty new to Haskell and it's
entirely possible I'm doing something a way I shouldn't.

Back to the problem at hand.

My script (link available at the bottom of this email) fetches a
webpage through the .NET Net library and processes it.

If I output the result of this processing (a list with the player's
name, goals, assists and points) to the screen with putStrLn I can
process about two dozen before I hit a .NET runtime exception (which
is a different issue entirely).

If I don't ouput the result to the screen (I delete 2 lines that only
do putStrLn, Ln 148 & Ln 161) I get "ERROR - Garbage collection fails
to reclaim sufficient space" after 2 players processed which seems
completely counter-intuitive to me.

Does someone have an idea as to what's going on here?

The script (and its dependencies) are available here:
http://smokinn.tengun.net/comp348/week6/

Thanks,
Guillaume Theoret
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Yang

On 10/8/06, Udo Stenzel u.stenzel-at-web.de |haskell-cafe|
<...> wrote:

Yang wrote:
> type Poly = [(Int,Int)]
>
> addPoly1 :: Poly -> Poly -> Poly
> addPoly1 p1@(p1h@(p1c,p1d):p1t) p2@(p2h@(p2c,p2d):p2t)
>| p1d == p2d = (p1c + p2c, p1d) : addPoly1 p1t p2t
>| p1d < p2d = p1h : addPoly1 p1t p2
>| p1d > p2d = p2h : addPoly1 p1 p2t
> addPoly1 p1 [] = p1
> addPoly1 [] p2 = p2
> addPoly1 [] [] = []
>
> But this doesn't use tail recursion/accumulation

Indeed it doesn't.  Now remind me, why is that supposed to be a Bad
Thing?  The above code exhibits a maximum of lazyness and runs with no
useless space overhead.  Apart from the expression (p1c + p2c), which
you probably want to evaluate eagerly, it is close to perfect.

> so I rewrote it: [...]
>
> But laziness will cause this to occupy Theta(n)-space of cons-ing
> thunks.

No, it doesn't.  Insisting on accumulator recursion does.  Actually,
using reverse does.  Think about it, a strict reverse cannot use less
than O(n) space, either.


Well, in general, the problem you run into is this, where we use
linear space for the thunks:

foldl (+) 0 [1,2,3]
= foldl (+) (0 + 1) [2,3]
= foldl (+) ((0 + 1) + 2) [3]
= foldl (+) (((0 + 1) + 2) + 3) []
= ((0 + 1) + 2) + 3
= (1 + 2) + 3
= 3 + 3
= 6

whereas with strictness, you use constant space:

foldl' f z [] = z
foldl' f z (x:xs) = let u = f z x in u `seq` foldl' f u xs
foldl' (+) 0 [1,2,3]
= let u = 0 + 1 in u `seq` foldl' (+) u [2,3]
= foldl' (+) 1 [2,3]
= let u = 1 + 2 in u `seq` foldl' (+) u [3]
= foldl' (+) 3 [3]
= let u = 3 + 3 in u `seq` foldl' (+) u []
= foldl' (+) 6 []
= 6



> I was
> hoping for more in-depth insights on how to take advantage of laziness
> to write cleaner AND more efficient code.

Try to explain why your first iteration was bad.  You'll achieve
enlightenment at the point where your explanation fails.


Udo.
--
Hast du zum Leben kein Motiv --
steig mal vor, vielleicht geht's schief.
-- aus einem Gipfelbuch


-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.1 (GNU/Linux)

iD8DBQFFKYwQc1ZCC9bsOpURAs4KAKCymnLiE5LfkCa01H0AJ2FddwJ6oQCfY6DY
sYRPT1fGr0mUozUcs+qGC8s=
=BRLQ
-END PGP SIGNATURE-




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe