[Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-24 Thread Heinrich Apfelmus
Manlio Perillo wrote:
> Conal Elliott ha scritto:
>> Manlio,
>>
>> We live in the age of participation -- of co-education.  Don't worry
>> about text-books.  Contribute to some wiki pages & blogs today that
>> share these smart techniques with others.
>>
> 
> When I started learning Haskell (by my initiative), what I did was:
> 
> [steps 1) - 9), mostly internet tutorials ]

I think you'd have had a much easier time by starting with a proper book
right away, like Richard Bird's "Introduction to Functional Programming
in Haskell", accompanied by Real World Haskell. You see, the reason that
books cost money is (should be) high quality content. :)


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 23:13 -0700, Donn Cave wrote:
> Quoth Duncan Coutts :
> 
> > You must not do this. It breaks the semantics of the language.
> >
> > Other people have given practical reasons why you should not but a
> > theoretical reason is that you've defined a non-continuous function.
> > That is impossible in the normal semantics of pure functional languages.
> > So you're breaking a promise which we rely on.
> 
> Could you elaborate a little, in what sense are we (?) relying on it?
> 
> I actually can't find any responses that make a case against it on a
> really practical level - I mean, it seems to be taken for granted that
> it will work as intended,

It shouldn't be.

Consider:

loop = loop
blam = error "blam"
notReallyTry = unsafePerformIO . try . evaluate

Now, normally, we have, for all x, y,

  x `seq` y `seq` x
= y `seq` x

But we clearly do *not* have this for x = blam, y = loop, since the
equality isn't preserved by notReallyTry:

notReallyTry $ blam `seq` loop `seq` blam = Left (ErrorCall "blam")
notReallyTry $ loop `seq` blam= loop

Now, say a compiler sees the definition

foo x y = x `seq` y `seq` x

in one module, and then in a later one

expectToBeTotal = notReallyTry $ foo blam loop

?  What happens if the compiler, while compiling foo, notices that x is
going to be evaluated eventually anyway, and decides against forcing it
before y?

What if foo was written as

foo (!x) (!y) = x

?  Which order are the evaluations performed in?  In a purely functional
language, it doesn't matter; but all of a sudden with impure operations
like notReallyTry popping up, it does.

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-24 Thread Jake McArthur

Donn Cave wrote:

Could you elaborate a little, in what sense are we (?) relying on it?

I actually can't find any responses that make a case against it on a
really practical level - I mean, it seems to be taken for granted that
it will work as intended, and we're down to whether we ought to have
such intentions, as a matter of principle.  If you've identified a
problem here with semantics that would break normal evaluation, from
the perspective of the programmer's intention, then this would be
the first practical reason?


Off the top of my head, here is a possible case:

foo :: Int -> Int
foo x = ... -- something that might throw an exception

bar :: Int -> Blah
bar x = ... -- internally use foo and catch the exception

baz :: Int -> Blah
baz = bar . foo

In this case, if the foo in baz throws an exception, I think bar may 
catch it and attempt to handle it as if the foo in bar had thrown it, 
but we probably would have expected this exception to go all the way to 
the top level and halt the program since exceptions are usually due to 
programmer error.


But I didn't test this, and since this isn't something I've ever done 
before I can't be 100% sure of its behavior.


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-24 Thread Donn Cave
Quoth Duncan Coutts :

> You must not do this. It breaks the semantics of the language.
>
> Other people have given practical reasons why you should not but a
> theoretical reason is that you've defined a non-continuous function.
> That is impossible in the normal semantics of pure functional languages.
> So you're breaking a promise which we rely on.

Could you elaborate a little, in what sense are we (?) relying on it?

I actually can't find any responses that make a case against it on a
really practical level - I mean, it seems to be taken for granted that
it will work as intended, and we're down to whether we ought to have
such intentions, as a matter of principle.  If you've identified a
problem here with semantics that would break normal evaluation, from
the perspective of the programmer's intention, then this would be
the first practical reason?

Donn

> It is not "safe". It's almost as bad as a function isBottom, which is
> the canonical non-continuous function. It's defined by:
>
> isBottom _|_ = True
> isBottom _   = False
>
> Of course your tryArith only tests for certain kinds of _|_ value, but
> in principle the problem is the same.
>
> It is not safe because it distinguishes values that are not supposed to
> be distinguishable. This invalidates many properties and
> transformations.
>
> Duncan

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread wren ng thornton

Manlio Perillo wrote:

But this may be really a question of personal taste or experience.
What is more "natural"?

1) pattern matching
2) recursion
or
1) function composition
2) high level functions



Which is more "natural":
* C-style for-loops (aka assembly while-loops), or
* any modern language's foreach loops (aka iterators)?

Following directly from the Rule of Least Power, if you can get away 
with foreach then that's what you should use. Why? Because the less 
power the construct has, the fewer corner cases and generalizations a 
reader of the code needs to consider. Now, just because iterators exist 
does not mean that one should never use the more general tool. If you're 
fighting to break out of your chosen straitjacket, then chances are it's 
the wrong one to use in the first place; it'd be clearer to use more 
power and have less fighting.


Both of these conclusions seem quite natural to me, even from before 
learning Haskell. It seems, therefore, that "naturality" is not the 
proper metric to discuss. It's oft overlooked, but the fact is that 
expressivity comes not from more formal power, but from _less_.


* A human's (or any vertebrate's) range of motion is severely crippled 
when compared to that of an amoeba; and yet it is those limitations 
which provide the structure necessary to perform greater tasks such as 
grasping, lifting, jumping, etc.


* Natural language has a limited range of words and syntactic 
constructs, but gives the larger-enough building blocks to enable 
unconstrained communication; whereas a language with a unique word for 
every utterance (arguably simpler) is impossible to learn.


* Regular expressions (and other classes of automata) have severe 
limitations on formal power, and yet these constraints enable poly-time 
algorithms for intersection, union, etc.


* Haskell's type system (sans extensions) is not Turing complete, yet 
this enables us to infer types rather than requiring annotations or proofs.



The contemporary state of scientific research is focused heavily on the 
idea of reductionism (the idea of being able to reduce all biology to 
chemistry, all chemistry to physics, all computer science to 
mathematics, etc). But as any systems theorist will tell you, this 
approach is misguided if the goal is a Theory of Everything. As per the 
famous book: no matter how much you learn about quarks, that tells you 
nothing about jaguars.


At every step of reduction, there is an increase in formal power and a 
concomitant loss of information. Even perfect knowledge of quarks and 
perfect simulation software isn't enough, because you've lost the 
_abstraction_ that is "jaguar". You can simulate it, emulate it, model 
it, but you've lost the high-level perspective that says jaguars are 
different and more interesting than an arbitrary simulation of a 
collection of quarks. (And it's doubtful we'll ever have the omniscience 
to get even that far.)


While primitive recursion and case matching are _fundamental_ (that is, 
at the bottom of a reductionist tower), that does not entail that they 
are _central_ (that is, a ubiquitous pattern at every resolution of 
reduction). Church encoding, SKI combinators, Curry-Howard isomorphism, 
and the like are also fundamental topics to teach and understand; but 
they're rarely ones that should be central to a program or library.


Now, many Haskellers (like good scientists) bristle at this fundamental 
nature of things. And in response we're constantly coming up with new 
generalizations which have little-enough structure to be descriptive 
while having big-enough structure to be interesting. If there's too much 
structure, it's boilerplate and therefore unusable; if there's too 
little, it has no generality and is therefore unhelpful. But somewhere 
between those extremes someone has to make a judgment call and decide 
whether some particular pattern measures up to the metric of being 
helpful and usable. If it does, then everyone (whose domain it covers) 
should learn it and use it because it simplifies programming from a 
high-level of design.


Giants. Shoulders. Etc.

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Erik de Castro Lopo
Jake McArthur wrote:

> Richard O'Keefe wrote:
> > May I suggest that the most important thing missing from
> > all these versions of the function is a comment?
> > Most of the time I shouldn't *care* how the function works.
> > (And that, for me, is one of the key benefits of Haskell.)
> 
> Although in this case, a proper name and type signature is probably 
> enough. :)

I trust type signatures much more than comments because I
know the compiler actually verifies the type signature.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-24 Thread Duncan Coutts
On Mon, 2009-03-23 at 08:11 -0400, Xiao-Yong Jin wrote:
> Hi,
> 
> I just feel it is not comfortable to deal with exceptions
> only within IO monad, so I defined
> 
> > tryArith :: a -> Either ArithException a
> > tryArith = unsafePerformIO . try . evaluate

You must not do this. It breaks the semantics of the language.

Other people have given practical reasons why you should not but a
theoretical reason is that you've defined a non-continuous function.
That is impossible in the normal semantics of pure functional languages.
So you're breaking a promise which we rely on.

It is not "safe". It's almost as bad as a function isBottom, which is
the canonical non-continuous function. It's defined by:

isBottom _|_ = True
isBottom _   = False

Of course your tryArith only tests for certain kinds of _|_ value, but
in principle the problem is the same.

It is not safe because it distinguishes values that are not supposed to
be distinguishable. This invalidates many properties and
transformations.

Duncan

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Gwern Branwen
On Tue, Mar 24, 2009 at 2:42 PM, Manlio Perillo
 wrote:
> Tim Newsham ha scritto:
>>>
>>> These friends are very interested in Haskell, but it seems that the main
>>> reason why they don't start to seriously learning it, is that when they
>>> start reading some code, they feel the "Perl syndrome".
>>>
>>> That is, code written to be "too smart", and that end up being totally
>>> illegible by Haskell novice.
>>>
>>> I too have this feeling, from time to time.
>>>
>>> Since someone is starting to write the Haskell coding style, I really
>>> suggest him to take this "problem" into strong consideration.
>>
>> When you think about it, what you are saying is that Haskell programmers
>> shouldn't take advantage of the extra tools that Haskell provides.
>
> No, I'm not saying this.
>
> But, as an example, when you read a function like:
>
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
>
> that can be rewritten (argument reversed) as:
>
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _         =  []
> takeList _ []         =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>    where (head, tail) = splitAt n xs
...
>> [...]
>
>
> Manlio

Correct me if I'm wrong, but isn't this an example against your
thesis? Your two definitions apparently define different things.

{-# LANGUAGE NoMonomorphismRestriction #-}
import Test.QuickCheck

test = (\x y -> buildPartitions x y == takeList y x)

buildPartitions ::  [a] -> [Int] -> [[a]]
buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns

takeList :: [Int] -> [a] -> [[a]]
takeList [] _ =  []
takeList _ [] =  []
takeList (n : ns) xs  =  head : takeList ns tail
   where (head, tail) = splitAt n xs

{-
*Main Control.Monad Data.Char Data.List> quickCheck test
quickCheck test^J
:1:11:
Warning: Defaulting the following constraint(s) to type `()'
 `Eq a' arising from a use of `test' at :1:11-14
 `Arbitrary a'
   arising from a use of `quickCheck' at :1:0-14
 `Show a' arising from a use of `quickCheck' at :1:0-14
In the first argument of `quickCheck', namely `test'
In a stmt of a 'do' expression: it <- quickCheck test
*** Failed! Falsifiable (after 2 tests):
[]
[0]
-}

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

Richard O'Keefe wrote:

May I suggest that the most important thing missing from
all these versions of the function is a comment?
Most of the time I shouldn't *care* how the function works.
(And that, for me, is one of the key benefits of Haskell.)


Although in this case, a proper name and type signature is probably 
enough. :)


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Richard O'Keefe

May I suggest that the most important thing missing from
all these versions of the function is a comment?
Most of the time I shouldn't *care* how the function works.
(And that, for me, is one of the key benefits of Haskell.)

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


[Haskell-cafe] Re: Grouping - Map / Reduce

2009-03-24 Thread GüŸnther Schmidt

Hi Ketil,

Ketil Malde schrieb:

"Gü?nther Schmidt"  writes:


let say I got an unordered lazy list of key/value pairs like

[('a', 99), ('x', 42), ('a', 33) ... ]

and I need to sum up all the values with the same keys.

So far I wrote a naive implementation, using Data.Map, foldl and insertWith.


Data.Map.fromListWith (+)


The building of this map is of course a bottleneck, the successive
processing needs to wait until the entire list is eventually consumed
the Map is built and flattened again.


Sure this is not an artifact of the laziness of foldl?


well I can't really see how the map could be consumed *while* it's still 
being built, I just don't see it. (I'm using foldl' and insertWith', sry 
for not saying so initially).





Is there another way of doing this, something more "streaming
architecture" like?


I don't see how you can do this much better - for a small, fixed set
of keys, you could use an (STU) array for the sums, but it depends if
the added complexity is worth it.  You're already doing a single pass
over the data.

-k



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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread John Meacham
On Tue, Mar 24, 2009 at 10:29:55PM +0300, Miguel Mitrofanov wrote:
> Maybe it's just me, but I think that
>
> takeList ns xs = evalState (mapM (State . splitAt) ns) xs
>
> or even
>
> takeList = evalState . map (State . splitAt)
>
> would be much clearer than both versions.

I love it! It wouldn't occur to me to utilize State like this (too used
to thinking of it as a black box rather than whats inside of it). quite
a lot of useful information to learn can be expressed in a line of
haskell. sort of like a zen koan. :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Alberto G. Corona
Perhaps is much easier to create one line compositions of functions in
haskell rather than in C because the type system helps a lot in the process.
However, reusability of source code and maintainability has never been taken
seriously by haskell programmers, simply because there are no industrial
projects in Haskell with dozens of people with different skills that come
and go. Because that, probably the early C programers were far more
exhuberant than the current C++ and Java programmers now. To have a broad
base of users and/or to assure a cheap programmers for your industrial
application has the servitude to "the rule of least power". That is another
reason for the lemma: "Avoid success at all costs"

The rule of least power
(http://www.w3.org/2001/tag/doc/leastPower.html)
Originally
written by Tim Berners Lee;. For publishing (and, arguably, for code
reusability) "the best language is the least powerful".

This depressing conclusions can be overcomed if we consider that the rule of
least power  favours turing incomplete DSLs, so every industrial development
can be decomposed in two groups wich demands two different skills: 1)
 DSLs  creation  2) DSL programming


2009/3/24 Manlio Perillo 

> Zachary Turner ha scritto:
>
>> [...]
>>
> > but I do understand that one of the primary uses
>
>> cases and/or motivating factors for using Haskell is when you really just
>> NEED that extra abstraction and power you get from being able to do these
>> types of things.  Someone once said that "simple problems should be simple
>> and difficult problems should be possible".  That doesn't mean the difficult
>> problems become EASY.  One of the best uses for haskell is solving difficult
>> problems.  It's obviously still going to be difficult to solve, and as such
>> the writer (and hence by extension the reader) is going to have to be smart
>> as well.
>>
>
> I agree with you, and in fact I'm still learning Haskell.
> The reason I'm still learning Haskell is because I like its syntax.
> And yes, I also like the ability to write efficient function by composing
> other function.
>
> But there is a limit.
> In C you have the ability to write assembler code, but one usually think
> twice before doing so, since it will become unreadable to most of the
> people.
>
> If you think that writing low level assembler code is the best solution,
> you should at least document it well, instead of assuming that the reader is
> as smart as you.
>
>
> As I have written at the begin of the thread, there are people I know
> (*much* more smarter then me), that keep themselves away from Haskell
> because they start to read some code, and they feel something is wrong.
>
> They *think* "ah, the author wrote code in this way just to show how smart
> he is; how can I learn a language if most of the available code is written
> in this way"?
>
> Note the use of the verb "think".
> This is only a sensation, and it is wrong; but sensations are important.
>
>
>
> > [...]
>
>
> Manlio
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Grouping - Map / Reduce

2009-03-24 Thread Gü?nther Schmidt

Dear Luke,

I suspect Black Magic at work here.

This seems to work and I so don't have a clue why. But thank you very 
much nevertheless, I strongly suspect that, once I figured out why this 
works, I will have learned a very, very important trick indeed.


Had I read "purely functional data structures" from start to finish, 
would I have come across this?


Günther



Luke Palmer schrieb:
On Tue, Mar 24, 2009 at 3:51 PM, Luke Palmer > wrote:


On Tue, Mar 24, 2009 at 3:15 PM, Gü?nther Schmidt
mailto:gue.schm...@web.de>> wrote:

Hi,

let say I got an unordered lazy list of key/value pairs like

[('a', 99), ('x', 42), ('a', 33) ... ]

and I need to sum up all the values with the same keys.

So far I wrote a naive implementation, using Data.Map, foldl and
insertWith..

The result of this grouping operation, which is effectively
another list
of key/value pairs, just sums this time, needs to be further
processed.

The building of this map is of course a bottleneck, the successive
processing needs to wait until the entire list is eventually
consumed
the Map is built and flattened again.

Is there another way of doing this, something more "streaming
architecture" like?


Yeah, make a trie.  Here's a quick example.

import Data.Monoid

newtype IntTrie a = IntTrie [a]

singleton :: (Monoid a) => Int -> a -> IntTrie a
singleton ch x = IntTrie [ if fromIntegral ch == i then x else
mempty | i <- [0..] ]


This definition of singleton unnecessarily leaks memory in some cases.  
Here's a better one:


singleton ch x = IntTrie $ replicate ch mempty ++ [x] ++ repeat mempty

Luke



lookupTrie :: IntTrie a -> Int -> a
lookupTrie (IntTrie xs) n = xs !! n

instance (Monoid a) => Monoid (IntTrie a) where
mempty = IntTrie (repeat mempty)
mappend (IntTrie xs) (IntTrie ys) = IntTrie (infZipWith mappend
xs ys)

infZipWith f ~(x:xs) ~(y:ys) = f x y : infZipWith f xs ys

test = mconcat [ singleton (n `mod` 42) [n] | n <- [0..] ]
`lookupTrie` 10

This is an inefficient way to find the class of n such that n mod 42
= 10.  Note that it works on an infinite list of inputs.

Here the "trie" was a simple list, but you could replace it with a
more advanced data structure for better performace.

Luke





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



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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 16:43 -0700, Donn Cave wrote:
> If he really intended to promote some dumb code as a better
> alternative to some otherwise equivalent smart code,

`Smart' is Manlio's term --- or, rather, his characterization of his
friends' reaction upon seeing some inscrutable piece of (apparent)
Haskell golf or (seemingly) pointless code.  The code seems excessively
clever to them; when Manlio's example is merely clear, well-written,
concise, and declarative, rather than operational, in intention.

> ...

> Go ahead and write smart, clearly the benefits outweigh the cost,
> but tell us that there's no cost, no problem here if a reader who
> knows Haskell has a hard time following?

What reader who knows Haskell?  We have a programmer who is,
self-confessedly, just learning Haskell, not really proficient; we have
is friends, who, by his statement of the problem do not know Haskell at
all; and we have some un-specified group of other developers who, by
selection, barely know Haskell or do not know it at all --- that is,
developers who are still in the process of learning.  I think your
``reader who knows Haskel'' has no-where to here figured in the
discussion.

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Clive Brettingham-Moore
Code like that is why I love Haskell, while I haven't written a Haskell
program in years it is still a joy to read (much more so than the pretty
good zipWith version).
In reference to later comments: if you don't know Monads, you don't know
Haskell; that goes double for high order functions.
So really the only place where this code may be inappropriate is in a
beginner tutorial (unless you are trying to show why they need to learn
more!).
C

Miguel Mitrofanov wrote:

> takeList ns xs = evalState (mapM (State . splitAt) ns) xs
> 
> or even
> 
> takeList = evalState . map (State . splitAt)
> 

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Donn Cave
> Manlio -- You may be missing the point of my suggestion, which is to help
> people *find* code that suits them, rather than changing anyone's coding
> style.  Optimizing code for one segment of readers is pessimizing it for
> another.  Instead of dumbing down the smart code, I'd like to help your
> friends to help each other find dumber code, *and* to help others of us find
> smarter code.

If he really intended to promote some dumb code as a better
alternative to some otherwise equivalent smart code, then I must
have missed his point.

For me, when people defend a practice with notions like "programmer
needs be smarter/more responsible/better educated", that's like the
institutional equivalent of a "code smell".  You see it everywhere,
too.  C/C++ programmers will tell you its storage model is fine, just
"programmer needs to be more ..."

C's storage model does have its advantages, and smart code is
presumably a good thing too.  But for example, exercises like just
stripping a function of extraneous parameter identifiers doesn't make
it smart, while it may make it harder for someone to understand it
at a glance.  I do it myself, even though I claim to detest it,
which may tell us something about the appeal of exercises like that.

Go ahead and write smart, clearly the benefits outweigh the cost,
but tell us that there's no cost, no problem here if a reader who
knows Haskell has a hard time following?  >> "institution smell."

Donn

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


Re: [Haskell-cafe] Grouping - Map / Reduce

2009-03-24 Thread Ketil Malde
"Gü?nther Schmidt"  writes:

> let say I got an unordered lazy list of key/value pairs like
>
> [('a', 99), ('x', 42), ('a', 33) ... ]
>
> and I need to sum up all the values with the same keys.
>
> So far I wrote a naive implementation, using Data.Map, foldl and insertWith.

Data.Map.fromListWith (+)

> The building of this map is of course a bottleneck, the successive
> processing needs to wait until the entire list is eventually consumed
> the Map is built and flattened again.

Sure this is not an artifact of the laziness of foldl?

> Is there another way of doing this, something more "streaming
> architecture" like?

I don't see how you can do this much better - for a small, fixed set
of keys, you could use an (STU) array for the sums, but it depends if
the added complexity is worth it.  You're already doing a single pass
over the data.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Conal Elliott ha scritto:

And advices to experienced Haskell programmers about how to document
their code so that it may help less experienced programmers.


Manlio -- You may be missing the point of my suggestion, 


Ah, sorry.

which is to 
help people *find* code that suits them, rather than changing anyone's 
coding style.  Optimizing code for one segment of readers is pessimizing 
it for another.  Instead of dumbing down the smart code, I'd like to 
help your friends to help each other find dumber code, *and* to help 
others of us find smarter code.





This may be hard to do.

However I already suggested to start reading the Prelude code, from the 
Haskell Report.



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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Xiao-Yong Jin wrote:


Thanks for all the replies.  Now I understand more about
Exceptions and Errors.  I guess all I need is to compose a
larger monad, after all.  I need to learn how to make
two different stacks of monad transformers cooperate
seamlessly, though.


Until now it seems you only need Applicative functor. They can be combined 
in a more general way:

  
http://hackage.haskell.org/packages/archive/TypeCompose/0.6.4/doc/html/Control-Compose.html

See the instances:
  (Applicative g, Applicative f) => Applicative (g :. f)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Conal Elliott ha scritto:

Manlio,

We live in the age of participation -- of co-education.  Don't worry 
about text-books.  Contribute to some wiki pages & blogs today that 
share these smart techniques with others.




When I started learning Haskell (by my initiative), what I did was:

1) Quick reading of the first tutorial I found on the wiki.
   http://darcs.haskell.org/yaht/yaht.pdf, if i remember correctly

2) Quick reading the Haskell Report

3) Reading another tutorial:
   http://www.haskell.org/tutorial/

4) Reading again the Haskell Report

5) A lot of time spent finding good tutorials.
   Yet, I did not knew what monads were, I just
   felt that monads were some strange and advanced feature

... A period where I stop looking for Haskell

6) Found some good tutorial about what monads are, but yet I did not
   knew anything about state monads, monad transformers, and so.

... Another period were I stop looking for Haskell

7) The Real Word Haskell book.
   Finally in one book all "advanced" concepts.

   I read the book online.
   I found the book good, but i think it is too dispersive in some
   chapters.
   I already forgot some of the concepts I read, mostly because in some
   chapter I get annoyed, and started skipping things, or reading it
   quickly.

   I will buying a copy in May, at Pycon Italy
   (were there will be a stand by O'Really), so that I can read it
   again.

8) New impetus at learning Haskell.
   I read again the Haskell Report, and the
   "A Gentle Introduction to Haskell".

   I finally started to understand how things works

7) Start to write some "real" code.

   I now I'm able to understand much of the code I read.
   But for some kind of code I still have problems.


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Benja Fallenstein
2009/3/24 Peter Verswyvelen :
>> This strategy is doomed to failure, unfortunately.
>
> So it is the good strategy, because Haskell's slogan is "avoid success at
> all cost" :-)


IN THE YEAR 1987, WAR WAS BEGINNING

BIG, IMPERATIVE SOFTWARE BEHEMOTHS CLASHED IN A STATE OF IMPURITY

UNDER THE SHADOW OF FEAR AND DOUBT, COLONY BY COLONY FELL INTO TYPELESS ANARCHY

WHOLE PLANETS WERE SCROUNGED BY TERRIBLE SEGFAULTS

THE HUNGER FOR A NEW PARADIGM WAS GNAWING AT THE ROOTS OF THE CIVILIZED UNIVERSE


MEANWHILE, IN A GALAXY FAR, FAR AWAY, A SMALL GROUP OF LAZY FUNCTIONAL
PROGRAMMERS CREATED A LANGUAGE

IT WAS OUR LAST, BEST HOPE TO AVOID SUCCESS AT ALL COST...

IT FAILED


IT EVOLVED


THERE ARE 8,581 IMPLEMENTATIONS SUPPORTING 935,842,712 EXTENSIONS

THEY LOOK AND FEEL ... FUNCTIONAL

SOME ARE PROGRAMMED TO THINK THAT THEY AREN'T IMPERATIVE AT ALL

AT LEAST ONE IS ACTUALLY USED


ONCE, IT HAD BEEN OUR LAST, BEST HOPE TO AVOID SUCCESS

IN THE YEAR 2009, IT BECAME SOMETHING GREATER:

OUR LAST, BEST HOPE FOR BLASTING THE INFERIOR LANGUAGES OUT OF THE SKY
(WITH LAZY CLASS)


YOU HAVE NO CHANCE TO SURVIVE MAP YOUR BIND
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Xiao-Yong Jin
Jake McArthur  writes:

> Xiao-Yong Jin wrote:
> | Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
> | Why does it throws this /ugly/ /error/ when it is applied to
> | 0?  Why is it not using some beautiful
> | 'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
> | /ugly/ and doesn't make any sense?
>
> 'div' throws an error because dividing by zero is *programmer error*.
> *You* are supposed to make sure that you aren't dividing by zero.
>
> I differ from this decision in your case because, as you said, it is
> easier to check for the error condition in the function itself than to
> check it externally. This is fine, but because it's so hard to check
> externally, you have to tell the outside world whether there was an
> error or not. A functor/applicative/monad is the pure way to do this. An
> error is not.
>
> | Of course, 'scalarMult' is invulnerable and free of monad.
> | But take a look at the following functions,
> |
> |> f1 = scalarMult 2 . invMat
> |> f2 l r = l `multMat` invMat r
> |> ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
> |> ff x y = do let ff' = f1 x + f2 y
> |> put . (addMat ff') . f1 << get
> |> tell $ f2 ff'
> |> when (matrixWeDontLike (f1 ff') $
> |>  throwError MatrixWeDontLike
> |> return $ scalarMult (1/2) ff'
> |
> | Yes, I know, it's not really complicate to rewrite the above
> | code.  But, what do I really gain from this rewrite?
>
> Code that is fully documented by its type, no harder to compose, more
> pure, and does what the programmer expects it to do.

Thanks for all the replies.  Now I understand more about
Exceptions and Errors.  I guess all I need is to compose a
larger monad, after all.  I need to learn how to make
two different stacks of monad transformers cooperate
seamlessly, though.

Thanks,
Xiao-Yong
-- 
c/*__o/*
<\ * (__
*/\  <
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghci + hopengl

2009-03-24 Thread Peter Verswyvelen
On Tue, Mar 24, 2009 at 11:35 PM, Scott A. Waterman wrote:

> Duane -
>
> yes, please.  I've been wondering how to compile to a Mac .app structure.


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/mkbndl


> Also, anyone have any hints about distributing Haskell apps for mac, when
> you know the target will certianly *not* have a GHC environment on it?


GHC statically links everything, so you don't need the GHC environment to
run the app.


>
> Thanks
> --ts
>
> On Mar 21, 2009, at 2:18 PM, Duane Johnson wrote:
>
>  I've had issues with ghci and opengl... I usually have to compile my
>> programs before they will run.  I'm not sure why that's the case, but I too
>> get strange window behavior (sometimes it freezes, other times it doesn't
>> even show up).
>>
>> If you're on a Mac and would like help compiling to a .app folder, let me
>> know and I can post how I did that.
>>
>> Regards,
>> Duane Johnson
>> http://blog.inquirylabs.com/
>>
>>
>>  ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
>
> This question makes me wonder... why is explicit recursion taught first?
> [...]
>

Perhaps also because teachers, being older than their students, are often
mired in outdated thinking.

On Tue, Mar 24, 2009 at 3:35 PM, Jake McArthur  wrote:

> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> Jonathan Cast wrote:
> | You know, this might actually need to be looked into.
> |
> | You need to know recursion and pattern-matching to *write* re-usable
> | higher-order functions, but how appropriate is that as the first thing
> | taught?
>
> An excellent question!
>
> Coincidentally, I was just having a conversation with my girlfriend
> about programming with "building blocks." She described her main hurdle
> with programming at the moment, which is getting over the fact that she
> is used to working with tangible objects that you just put together in
> the appropriate way and her mind expects programming to work the same
> way, but it doesn't, at least in the languages she has looked at so far.
> I hypothesized that a language emphasizing combinators might be more
> intuitive to her than a language emphasizing loops and imperative steps
> for precisely this reason. I'm not entirely sure that she bought it, but
> she seemed to agree that it at least sounds nice in theory.
>
> Now I just have to convince her to become a willing subject in this
> experiment. ;)
>
> This question makes me wonder... why is explicit recursion taught first?
> I can't help but think now that it may be because those coming from
> imperative languages are used to writing loops, and recursion is the
> closest to loops that we have.
>
> - - Jake
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.9 (GNU/Linux)
> Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
>
> iEYEARECAAYFAknJYC4ACgkQye5hVyvIUKkExwCeLmejblGHyjdGsEkMykJ5bAJY
> pZ0AniaEpdgHCZzz2AALFYQ7X9WYEzws
> =R0qo
> -END PGP SIGNATURE-
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
Manlio,

We live in the age of participation -- of co-education.  Don't worry about
text-books.  Contribute to some wiki pages & blogs today that share these
smart techniques with others.

Learning/progress is mainly results when people respond to their
own incomprehension by moving into new & challenging ideas, not by banishing
them.  Puzzlement can be met by resistance or by embracing &
learning.


On Tue, Mar 24, 2009 at 3:15 PM, Manlio Perillo wrote:

> Dan Piponi ha scritto:
>
>> Miguel Mitrofanov wrote:
>>>
 takeList = evalState . mapM (State . splitAt)

>>>
>>  However, ironically, I stopped using them for pretty
>>> much the same reason that Manlio is saying.
>>>
>>
>> Are you saying there's a problem with this implementation? It's the
>> only one I could just read immediately.
>>
>
> Yes, you understand it immediately once you know what a state monad is.
> But how well is introduced, explained and emphasized the state monad in
> current textbooks?
>
> When I started learning Haskell, the first thing I learned was recursion
> and pattern matching.
>
> So, this may be the reason why I find more readable my takeList solution.
>
>
> > [...]
>
>
> Manlio
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghci + hopengl

2009-03-24 Thread Scott A. Waterman

Duane -

yes, please.  I've been wondering how to compile to a Mac .app  
structure.
Also, anyone have any hints about distributing Haskell apps for mac,  
when you know the target will certianly *not* have a GHC environment  
on it?

Thanks
--ts

On Mar 21, 2009, at 2:18 PM, Duane Johnson wrote:

I've had issues with ghci and opengl... I usually have to compile  
my programs before they will run.  I'm not sure why that's the  
case, but I too get strange window behavior (sometimes it freezes,  
other times it doesn't even show up).


If you're on a Mac and would like help compiling to a .app folder,  
let me know and I can post how I did that.


Regards,
Duane Johnson
http://blog.inquirylabs.com/



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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Jonathan Cast wrote:
| You know, this might actually need to be looked into.
|
| You need to know recursion and pattern-matching to *write* re-usable
| higher-order functions, but how appropriate is that as the first thing
| taught?

An excellent question!

Coincidentally, I was just having a conversation with my girlfriend
about programming with "building blocks." She described her main hurdle
with programming at the moment, which is getting over the fact that she
is used to working with tangible objects that you just put together in
the appropriate way and her mind expects programming to work the same
way, but it doesn't, at least in the languages she has looked at so far.
I hypothesized that a language emphasizing combinators might be more
intuitive to her than a language emphasizing loops and imperative steps
for precisely this reason. I'm not entirely sure that she bought it, but
she seemed to agree that it at least sounds nice in theory.

Now I just have to convince her to become a willing subject in this
experiment. ;)

This question makes me wonder... why is explicit recursion taught first?
I can't help but think now that it may be because those coming from
imperative languages are used to writing loops, and recursion is the
closest to loops that we have.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJYC4ACgkQye5hVyvIUKkExwCeLmejblGHyjdGsEkMykJ5bAJY
pZ0AniaEpdgHCZzz2AALFYQ7X9WYEzws
=R0qo
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
>
> And advices to experienced Haskell programmers about how to document their
> code so that it may help less experienced programmers.
>

Manlio -- You may be missing the point of my suggestion, which is to help
people *find* code that suits them, rather than changing anyone's coding
style.  Optimizing code for one segment of readers is pessimizing it for
another.  Instead of dumbing down the smart code, I'd like to help your
friends to help each other find dumber code, *and* to help others of us find
smarter code.

  - Conal

On Tue, Mar 24, 2009 at 3:03 PM, Manlio Perillo wrote:

> Conal Elliott ha scritto:
>
>> I'd love to help newbies get the hang of Haskell without having to jump in
>> the deep (and smart-infested) end first.  And I'd love for people to keep
>> writing smart code for non-newbies to enjoy.
>>
>> Perhaps a practical suggestion would be some wiki pages devoted to
>> pointing out code with various learning qualities, to help haskellers of all
>> levels of experience learn effectively.
>>
>>
> Yes, this is a good start.
>
> Advices to people learning Haskell about how to learn reading code.
> And advices to experienced Haskell programmers about how to document their
> code so that it may help less experienced programmers.
>
> IMHO, this should also go in the future Haskell coding style.
>
> > [...]
>
>
> Manlio
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Thomas Davie

*Launches missiles*

Bob

(that was my logo)

On 24 Mar 2009, at 21:46, Ross Mellgren wrote:

Doesn't matter how many times you seq the results, the thunk has  
been forced.


-Ross

On Mar 24, 2009, at 4:45 PM, FFT wrote:

I demand a recount! The one that launches the missile should have  
won!


2009/3/24 Eelco Lempsink :

The results of the Haskell logo competition are in!

You can view them at
http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl? 
num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath


Congratulations Jeff Wheeler!

I'll set up a page with the results visibile.

--
Regards,

Eelco Lempsink


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



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


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


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Xiao-Yong Jin wrote:
| Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
| Why does it throws this /ugly/ /error/ when it is applied to
| 0?  Why is it not using some beautiful
| 'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
| /ugly/ and doesn't make any sense?

'div' throws an error because dividing by zero is *programmer error*.
*You* are supposed to make sure that you aren't dividing by zero.

I differ from this decision in your case because, as you said, it is
easier to check for the error condition in the function itself than to
check it externally. This is fine, but because it's so hard to check
externally, you have to tell the outside world whether there was an
error or not. A functor/applicative/monad is the pure way to do this. An
error is not.

| Of course, 'scalarMult' is invulnerable and free of monad.
| But take a look at the following functions,
|
|> f1 = scalarMult 2 . invMat
|> f2 l r = l `multMat` invMat r
|> ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
|> ff x y = do let ff' = f1 x + f2 y
|> put . (addMat ff') . f1 << get
|> tell $ f2 ff'
|> when (matrixWeDontLike (f1 ff') $
|>  throwError MatrixWeDontLike
|> return $ scalarMult (1/2) ff'
|
| Yes, I know, it's not really complicate to rewrite the above
| code.  But, what do I really gain from this rewrite?

Code that is fully documented by its type, no harder to compose, more
pure, and does what the programmer expects it to do.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJXpcACgkQye5hVyvIUKnTOwCgzqRC4i7eLgbOQW1r+u2NPhAQ
7NkAnRsOFE8uMWrB/TRxTfdP/+x35EZ8
=kCtc
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 23:15 +0100, Manlio Perillo wrote:
> Dan Piponi ha scritto:
> >> Miguel Mitrofanov wrote:
> >>> takeList = evalState . mapM (State . splitAt)
> > 
> >> However, ironically, I stopped using them for pretty
> >> much the same reason that Manlio is saying.
> > 
> > Are you saying there's a problem with this implementation? It's the
> > only one I could just read immediately. 
> 
> Yes, you understand it immediately once you know what a state monad is.
> But how well is introduced, explained and emphasized the state monad in 
> current textbooks?
> 
> When I started learning Haskell, the first thing I learned was recursion 
> and pattern matching.

You know, this might actually need to be looked into.

You need to know recursion and pattern-matching to *write* re-usable
higher-order functions, but how appropriate is that as the first thing
taught?

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Manlio Perillo wrote:
| But this may be really a question of personal taste or experience.
| What is more "natural"?
|
| 1) pattern matching
| 2) recursion
| or
| 1) function composition
| 2) high level functions

Definitely the latter two. They are easier to comprehend (assuming each
of the smaller abstractions are already internalized) and more
efficient. Arguably, this building-block approach is the whole *point*
of Haskell.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJXDwACgkQye5hVyvIUKl/VQCgwspG1HDiGNwEQUFA/Wus6GYD
GkkAnRpiP50p17S8Pa9CEvxMFz4cDiZF
=/Gi/
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Dan Piponi ha scritto:

Miguel Mitrofanov wrote:

takeList = evalState . mapM (State . splitAt)



However, ironically, I stopped using them for pretty
much the same reason that Manlio is saying.


Are you saying there's a problem with this implementation? It's the
only one I could just read immediately. 


Yes, you understand it immediately once you know what a state monad is.
But how well is introduced, explained and emphasized the state monad in 
current textbooks?


When I started learning Haskell, the first thing I learned was recursion 
and pattern matching.


So, this may be the reason why I find more readable my takeList solution.


> [...]


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread John Melesky

On Mar 24, 2009, at 1:51 PM, Manlio Perillo wrote:

But this may be really a question of personal taste or experience.
What is more "natural"?

1) pattern matching
2) recursion
or
1) function composition
2) high level functions


I think, actually, that one of the fundamental intuitions of (modern)  
Haskell programming is that recursion should *rarely* be explicit,  
because the majority of places you'd use recursion all fall into a few  
different patterns (hence, the proliferation of maps and folds).


Once you get those recursive operations firmly embedded in your mind,  
then combining them becomes much simply, and you can reason about more  
complex transformations much more easily.


-johnn

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Peter Verswyvelen
On Tue, Mar 24, 2009 at 8:29 PM, Miguel Mitrofanov wrote:

> takeList ns xs = evalState (mapM (State . splitAt) ns) xs
>>
>
> or even
>
> takeList = evalState . map (State . splitAt)
>
> would be much clearer than both versions.


Brilliant. As a newbie, I knew all these functions, I have used them all.
When I saw both initial implementations, I tried to write what you did, but
failed, I didn't see the pattern, failed to pick the correct functions in my
head, failed to make the puzzle.

I guess that is the real power of Haskell. In imperative languages, the more
you practice, the better you get in avoiding the imperative pitfalls. In
functional languages, more practice really results in more and more
productivity because you recognize the patterns; the design patterns are not
just thoughts but real functions you can reuse.


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Conal Elliott ha scritto:
I'd love to help newbies get the hang of Haskell without having to jump 
in the deep (and smart-infested) end first.  And I'd love for people to 
keep writing smart code for non-newbies to enjoy.


Perhaps a practical suggestion would be some wiki pages devoted to 
pointing out code with various learning qualities, to help haskellers of 
all levels of experience learn effectively.




Yes, this is a good start.

Advices to people learning Haskell about how to learn reading code.
And advices to experienced Haskell programmers about how to document 
their code so that it may help less experienced programmers.


IMHO, this should also go in the future Haskell coding style.

> [...]


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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Jeff Wheeler
Yay, thanks everybody!

As Eelco pointed out, Darrin Thompson deserves much of the credit for
coming up with the design; I just made it pretty in Photoshop. :)

On Tue, 2009-03-24 at 08:29 -0400, John Van Enk wrote:

> Is this the part where all the pundits come out and talk about how
> Jeff isn't a citizen, eats babies, and wants to turn Haskell into an
> imperative language?

I'm a citizen! I have consciously never executed unsafePerformIO (I know
better!). I have been hanging about quite regularly for a little over a
year now, when I started playing with Yi, and then intermittently
contributing there. I now hang about in #yi most every day, and #haskell
quite frequently too.

I rarely have anything sufficiently interesting for the mailing list. ;)

Again, thanks (and Darrin, too)!

Jeff Wheeler

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


Re: [Haskell-cafe] Grouping - Map / Reduce

2009-03-24 Thread Luke Palmer
On Tue, Mar 24, 2009 at 3:51 PM, Luke Palmer  wrote:

> On Tue, Mar 24, 2009 at 3:15 PM, Gü?nther Schmidt wrote:
>
>> Hi,
>>
>> let say I got an unordered lazy list of key/value pairs like
>>
>> [('a', 99), ('x', 42), ('a', 33) ... ]
>>
>> and I need to sum up all the values with the same keys.
>>
>> So far I wrote a naive implementation, using Data.Map, foldl and
>> insertWith.
>>
>> The result of this grouping operation, which is effectively another list
>> of key/value pairs, just sums this time, needs to be further processed.
>>
>> The building of this map is of course a bottleneck, the successive
>> processing needs to wait until the entire list is eventually consumed
>> the Map is built and flattened again.
>>
>> Is there another way of doing this, something more "streaming
>> architecture" like?
>
>
> Yeah, make a trie.  Here's a quick example.
>
> import Data.Monoid
>
> newtype IntTrie a = IntTrie [a]
>
> singleton :: (Monoid a) => Int -> a -> IntTrie a
> singleton ch x = IntTrie [ if fromIntegral ch == i then x else mempty | i
> <- [0..] ]
>

This definition of singleton unnecessarily leaks memory in some cases.
Here's a better one:

singleton ch x = IntTrie $ replicate ch mempty ++ [x] ++ repeat mempty

Luke


>
> lookupTrie :: IntTrie a -> Int -> a
> lookupTrie (IntTrie xs) n = xs !! n
>
> instance (Monoid a) => Monoid (IntTrie a) where
> mempty = IntTrie (repeat mempty)
> mappend (IntTrie xs) (IntTrie ys) = IntTrie (infZipWith mappend xs ys)
>
> infZipWith f ~(x:xs) ~(y:ys) = f x y : infZipWith f xs ys
>
> test = mconcat [ singleton (n `mod` 42) [n] | n <- [0..] ] `lookupTrie` 10
>
> This is an inefficient way to find the class of n such that n mod 42 = 10.
> Note that it works on an infinite list of inputs.
>
> Here the "trie" was a simple list, but you could replace it with a more
> advanced data structure for better performace.
>
> Luke
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Erik de Castro Lopo ha scritto:

Manlio Perillo wrote:

I was speaking about the best way to write a function, so that it may 
help someone who is learning Haskell.


I've been learning Haskell for about 3 months.

I think its a mistake to write code so that its easy for someone
learning Haskell to read it. Code should be written to be easily
read by other experienced users of the langauge.



Note that to write code so that its easy to read, does not mean rewrite 
the code as I did in the example.


It also means to add good comments, in the right places.


Erik


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Zachary Turner ha scritto:

[...]

> but I do understand that one of the primary uses
cases and/or motivating factors for using Haskell is when you really 
just NEED that extra abstraction and power you get from being able to do 
these types of things.  Someone once said that "simple problems should 
be simple and difficult problems should be possible".  That doesn't mean 
the difficult problems become EASY.  One of the best uses for haskell is 
solving difficult problems.  It's obviously still going to be difficult 
to solve, and as such the writer (and hence by extension the reader) is 
going to have to be smart as well. 



I agree with you, and in fact I'm still learning Haskell.
The reason I'm still learning Haskell is because I like its syntax.
And yes, I also like the ability to write efficient function by 
composing other function.


But there is a limit.
In C you have the ability to write assembler code, but one usually think 
twice before doing so, since it will become unreadable to most of the 
people.


If you think that writing low level assembler code is the best solution, 
you should at least document it well, instead of assuming that the 
reader is as smart as you.



As I have written at the begin of the thread, there are people I know 
(*much* more smarter then me), that keep themselves away from Haskell 
because they start to read some code, and they feel something is wrong.


They *think* "ah, the author wrote code in this way just to show how 
smart he is; how can I learn a language if most of the available code is 
written in this way"?


Note the use of the verb "think".
This is only a sensation, and it is wrong; but sensations are important.


> [...]


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Loup Vaillant
2009/3/24 Manlio Perillo :
> Jonathan Cast ha scritto:
>>
>> [...]
>>
>> I think, in general, the best way to document the purpose of the
>> function is
>>
>>    -- | Split a function into a sequence of partitions of specified
>> lenth
>>    takeList :: [Int] -> [a] -> [[a]]

*That* was what I craved for. With the type and a name like
"partitions", I would hardly have to look at the code at all. The
comment is almost superfluous.

> Note that I was not speaking about the best way to document a function.
>
> I was speaking about the best way to write a function, so that it may help
> someone who is learning Haskell.

Then, the first version plus the documentation above would be perfect.
Instant understanding about the purpose of the function, and insight
about a how to write it.

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


Re: [Haskell-cafe] Grouping - Map / Reduce

2009-03-24 Thread Luke Palmer
On Tue, Mar 24, 2009 at 3:15 PM, Gü?nther Schmidt wrote:

> Hi,
>
> let say I got an unordered lazy list of key/value pairs like
>
> [('a', 99), ('x', 42), ('a', 33) ... ]
>
> and I need to sum up all the values with the same keys.
>
> So far I wrote a naive implementation, using Data.Map, foldl and
> insertWith.
>
> The result of this grouping operation, which is effectively another list
> of key/value pairs, just sums this time, needs to be further processed.
>
> The building of this map is of course a bottleneck, the successive
> processing needs to wait until the entire list is eventually consumed
> the Map is built and flattened again.
>
> Is there another way of doing this, something more "streaming
> architecture" like?


Yeah, make a trie.  Here's a quick example.

import Data.Monoid

newtype IntTrie a = IntTrie [a]

singleton :: (Monoid a) => Int -> a -> IntTrie a
singleton ch x = IntTrie [ if fromIntegral ch == i then x else mempty | i <-
[0..] ]

lookupTrie :: IntTrie a -> Int -> a
lookupTrie (IntTrie xs) n = xs !! n

instance (Monoid a) => Monoid (IntTrie a) where
mempty = IntTrie (repeat mempty)
mappend (IntTrie xs) (IntTrie ys) = IntTrie (infZipWith mappend xs ys)

infZipWith f ~(x:xs) ~(y:ys) = f x y : infZipWith f xs ys

test = mconcat [ singleton (n `mod` 42) [n] | n <- [0..] ] `lookupTrie` 10

This is an inefficient way to find the class of n such that n mod 42 = 10.
Note that it works on an infinite list of inputs.

Here the "trie" was a simple list, but you could replace it with a more
advanced data structure for better performace.

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 22:43 +0100, Manlio Perillo wrote:
> Jonathan Cast ha scritto:
> > [...]
> > 
> > I think, in general, the best way to document the purpose of the
> > function is
> > 
> > -- | Split a function into a sequence of partitions of specified
> > lenth
> > takeList :: [Int] -> [a] -> [[a]]
> > 
> 
> Note that I was not speaking about the best way to document a function.
> 
> I was speaking about the best way to write a function, so that it may 
> help someone who is learning Haskell.

I've already explicitly rejected the claim that professional Haskell
code should be written to aid beginning users.  Again, that's what
textbooks are for.

And I was explicitly commenting on the claim that it was obvious, from
any version posted thus far, what the function was supposed to do.  Your
suggested code hardly helps make the function's purpose clear; comments
(or, better yet, tests, such as:

prop_length = \ ns xn -> sum ns <= length xn ==>
map length (takeList ns xn) == ns

do a much better job of explaining purpose).

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
I'd love to help newbies get the hang of Haskell without having to jump in
the deep (and smart-infested) end first.  And I'd love for people to keep
writing smart code for non-newbies to enjoy.

Perhaps a practical suggestion would be some wiki pages devoted to pointing
out code with various learning qualities, to help haskellers of all levels
of experience learn effectively.

  - Conal

On Tue, Mar 24, 2009 at 2:43 PM, Manlio Perillo wrote:

> Jonathan Cast ha scritto:
>
>> [...]
>>
>> I think, in general, the best way to document the purpose of the
>> function is
>>
>>-- | Split a function into a sequence of partitions of specified
>> lenth
>>takeList :: [Int] -> [a] -> [[a]]
>>
>>
> Note that I was not speaking about the best way to document a function.
>
> I was speaking about the best way to write a function, so that it may help
> someone who is learning Haskell.
>
> > [...]
>
> Manlio
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Ross Mellgren
As (yet another?) Haskell newbie, with a day job using Java (where  
"keep it simple, stupid" is not a principle, it's a language enforced  
requirement), I would much prefer the function is implemented in the  
most concise and idiomatic style that the writer is capable of. That  
is, either the zipWith...scanl solution (or its variants) or the state  
solution.


I've found that I learn considerably more from functions written this  
way that also have a good documentation comment than from munching on  
the standard pattern matching recursion again and again. If the  
function is well described, and short in purpose and text, I can use  
the fact that with functional programming (with some exception)  
ensures that all I need to understand the behavior should be right in  
front of me and I can spend time learning the patterns.


Just my 2 cents,

-Ross

On Mar 24, 2009, at 5:43 PM, Manlio Perillo wrote:


Jonathan Cast ha scritto:

[...]
I think, in general, the best way to document the purpose of the
function is
   -- | Split a function into a sequence of partitions of specified
lenth
   takeList :: [Int] -> [a] -> [[a]]


Note that I was not speaking about the best way to document a  
function.


I was speaking about the best way to write a function, so that it  
may help someone who is learning Haskell.


> [...]

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


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Erik de Castro Lopo
Manlio Perillo wrote:

> I was speaking about the best way to write a function, so that it may 
> help someone who is learning Haskell.

I've been learning Haskell for about 3 months.

I think its a mistake to write code so that its easy for someone
learning Haskell to read it. Code should be written to be easily
read by other experienced users of the langauge.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Andres Loeh
>> The results of the Haskell logo competition are in!
>>
>> You can view them at 
>> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath
>>
>> Congratulations Jeff Wheeler!
>
> Is there also a measure of how strong the winner wins over the "losers"?

Scroll to the bottom of the results page linked above and click on the
button, and you'll get a matrix comparing each logo to each other logo.
You still have to interpret the results yourself, though.

Cheers,
  Andres

-- 

Andres Loeh, Universiteit Utrecht

mailto:and...@cs.uu.nl mailto:m...@andres-loeh.de
http://www.andres-loeh.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Max Rabkin
On Tue, Mar 24, 2009 at 11:41 PM, Henning Thielemann
 wrote:
>> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath
>>
> Is there also a measure of how strong the winner wins over the "losers"?

The runner up was beaten 135 votes to 100. The linked page gives the
results of the one-on-one contest between each entry and the winner,
as well as between each entry and the next better one.

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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Eelco Lempsink wrote:


The results of the Haskell logo competition are in!

You can view them at 
http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath


Congratulations Jeff Wheeler!


And ... please maintain the list of logos, since I think there are many 
good suggestions that could be used for other Haskell related projects.

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Jonathan Cast ha scritto:

[...]

I think, in general, the best way to document the purpose of the
function is

-- | Split a function into a sequence of partitions of specified
lenth
takeList :: [Int] -> [a] -> [[a]]



Note that I was not speaking about the best way to document a function.

I was speaking about the best way to write a function, so that it may 
help someone who is learning Haskell.


> [...]

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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Eelco Lempsink wrote:


The results of the Haskell logo competition are in!

You can view them at 
http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath


Congratulations Jeff Wheeler!


Is there also a measure of how strong the winner wins over the "losers"?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Gregg Reynolds
On Tue, Mar 24, 2009 at 12:41 PM, Manlio Perillo
 wrote:

> I too have this feeling, from time to time.
>
So do I, because I haven't had the time to learn what I need to learn
in order to read the code smoothly.  I find that when I do work out
the meaning, most often the style reflects conciseness or
expressiveness, not obfuscatory tricks that the language allows.
>
> Since someone is starting to write the Haskell coding style, I really
> suggest him to take this "problem" into strong consideration.

Rule One of the Haskell Coding Style Handbook:  learn Haskell first,
then worry about style.  After all, nobody in her right mind would
tackle a French style manual without learning French first.  Although
I suppose one could argue that learning Haskell in fact involves
learning various styles.  ;)

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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Xiao-Yong Jin wrote:


Jake McArthur  writes:


Xiao-Yong Jin wrote:
| The problem is that there will be many functions using such
| a function to invert a matrix, making this inversion
| function return Either/Maybe or packing it in a monad is
| just a big headache.

I disagree. If you try to take the inverse of a noninvertable matrix,
this is an *error* in your code. Catching an error you created in pure
code and patching it with chewing gum it is just a hack. A monadic
approach (I'm putting Either/Maybe under the same umbrella for brevity)
is the only solution that makes any sense to me, and I don't think it's
ugly as you are making it out to be.



Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
Why does it throws this /ugly/ /error/ when it is applied to
0?


I think "throw" should be reserved to exceptions (although it is still 
strange English). Actually 'div x 0' is 'undefined', just like in 
mathematics. This is justified by the fact, that you can easily check 
whether the denominator is zero or not and it is expected that either you 
check the denominator before calling 'div' or that you proof that in your 
application the denominator is non-zero anyway and thus save repeated 
checks for zero at run-time. The deficiency is not in 'div' but in the 
type system, which does not allow to declare an Int to be non-zero. In 
contrast to that, it is not easily checked, whether a matrix is regular. 
Thus you may prefer a Maybe result.

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Yitzchak Gale
Miguel Mitrofanov wrote:
>>> takeList = evalState . mapM (State . splitAt)

I wrote:
>> However, ironically, I stopped using them for pretty
>> much the same reason that Manlio is saying.

Dan Piponi wrote:
> Are you saying there's a problem with this implementation? It's the
> only one I could just read immediately...
> It says exactly what it means, almost in English.

Yes, I agree. But at a time when the majority
of experienced Haskellers couldn't easily see that because
they weren't comfortable enough with the State monad,
using it would have cost more on average (for debugging,
refactoring, etc.). Whereas now I don't think that's a
problem anymore.

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


Re: [Haskell-cafe] Are there performant mutable Arrays in Haskell?

2009-03-24 Thread Xiao-Yong Jin
"Brettschneider, Matthias" 
writes:

> Thx for your hints, I played around with them and the performance gets 
> slightly better. 
> But the major boost is still missing :) 
>
> I noticed, that one real bottleneck seems to be the conversion of the array 
> back into a list. 
> The interesting part is, if I use the elems function (Data.Array.Base) the 
> performance is about
> 4x better then with my own function. So I thought, I write my own version of 
> elems, (that just converts
> a part of the array to a list) and I fall back into the same performance as 
> my first approach. 
>
> To make a long story short, here is the library code: 
> elems arr = case bounds arr of
>   (_l, _u) -> [unsafeAt arr i | i <- [0 .. numElements arr - 1]
>
> And my version:
> boundedElems arr = case bounds arr of
>   (_l, _u) -> [unsafeAt arr i | i <- [1737 .. 1752]]
>
> Is there a reason, why the library version is 4 times faster, than mine?

There shouldn't be any reason.  Try putting

{-# INLINE boundedElems #-}

to make it inline, it might be faster.
-- 
c/*__o/*
<\ * (__
*/\  <
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 22:33 +0300, Eugene Kirpichov wrote:
> Pretty cool once you know what the function does, but I must admit I
> wouldn't immediately guess the purpose of the function when written in
> this way.

I wouldn't immediately guess the purpose of the function written in any
way.

I think, in general, the best way to document the purpose of the
function is

-- | Split a function into a sequence of partitions of specified
lenth
takeList :: [Int] -> [a] -> [[a]]

jcc


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


[Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Xiao-Yong Jin
Daniel Yokomizo  writes:

> On Tue, Mar 24, 2009 at 1:27 PM, Xiao-Yong Jin  wrote:
>> Henning Thielemann  writes:
>>
>>> Try to never use exception handling for catching programming errors!
>>> Division by zero is undefined, thus a programming error when it
>>> occurs.
>>>  http://www.haskell.org/haskellwiki/Error
>>>  http://www.haskell.org/haskellwiki/Exception
>>>   I'm afraid, a Maybe or Either or Exceptional (see explicit-exception
>>> package) return value is the only way to handle exceptional return
>>> values properly. Maybe in the larger context of your problem zero
>>> denominators can be avoided? Then go this way.
>>
>> Using div is just an example I'm testing with what I read in
>> the book Real World Haskell.  The real thing I'm trying to
>> do is inverting a matrix.  Say, I want to write
>>
>>> invMat :: Matrix -> Matrix
>>
>> You won't be able to invert all the matrix, mathematically.
>> And computationally, even a larger set of matrix might fail
>> to be inverted because of the finite precision.  It is
>> relatively easier and more efficient to spot such a problem
>> within this 'invMat' function.  Because testing the
>> singularity of a matrix is equally hard as invert it.  So
>> all I can do when 'invMat' spot a singular matrix are
>>
>>  a) Return Either/Maybe to signal an error.
>>  b) Wrap it in a monad.
>>  c) Define a dynamic exception and throw it.
>
> In general if a function is partial we can either make it total by
> extending its range or restricting its domain. Also we can signal it
> using runtime or compile-time mechanisms. Options a & b are equivalent
> (i.e. extend the range, compile-time notification) and option c is
> also another way of extending the range, but using runtime
> notification.
>
> If we try the other approach, we need to express the totality of
> invMat by restricting its domain, so we can add, for example, a
> phantom type to Matrix to signal it is invertible. As you need to
> construct the Matrix before trying to invert it you can always make
> the constructors smart enough to bundle the Matrix with such
> properties. Of course there's need to do some runtime verifications
> earlier, but the clients of invMat are required to do the verification
> earlier or pass it to their clients (up to the level that can handle
> with this issue):
>
> data Invertible
> tryInvertible :: Matrix a -> Maybe (Matrix Invertible)
> invMat :: Matrix Invertible -> Matrix Invertible
>
>
> You could use different forms of evidence (e.g. phantom types, type
> classes) but the idea is the same.

This is theoretically sound, we can make a type 'Integer
Invertible' and make a 'safeDiv' to get rid of one of the
ArithException.  But as I said above, "testing the
singularity of a matrix is equally hard as inverting it",
doing it with matrix is more impractical than make 'div'
safe.  I don't mind my haskell code runs 6 times slower than
c++ code.  But I'm not ready to make it 10 times slower just
because I want to do something twice and it might as well be
useless most of the time.
-- 
c/*__o/*
<\ * (__
*/\  <
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Luke Palmer
On Tue, Mar 24, 2009 at 3:28 PM, Luke Palmer  wrote:

> On Tue, Mar 24, 2009 at 3:14 PM, Xiao-Yong Jin wrote:
>
>> Jake McArthur  writes:
>>
>> > Xiao-Yong Jin wrote:
>> > | The problem is that there will be many functions using such
>> > | a function to invert a matrix, making this inversion
>> > | function return Either/Maybe or packing it in a monad is
>> > | just a big headache.
>> >
>> > I disagree. If you try to take the inverse of a noninvertable matrix,
>> > this is an *error* in your code. Catching an error you created in pure
>> > code and patching it with chewing gum it is just a hack. A monadic
>> > approach (I'm putting Either/Maybe under the same umbrella for brevity)
>> > is the only solution that makes any sense to me, and I don't think it's
>> > ugly as you are making it out to be.
>> >
>>
>> Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
>> Why does it throws this /ugly/ /error/ when it is applied to
>> 0?  Why is it not using some beautiful
>> 'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
>> /ugly/ and doesn't make any sense?
>
>
> It's a proof obligation, like using unsafePerformIO.  It is "okay" to use
> unsafePerformIO when it exhibits purely functional semantics, but it's
> possible to use it incorrectly, and there is no ImpureSemanticsException.
> If you are being rigorous, you simply have to prove that the denominator
> will not be zero, rather than relying on it to be caught at runtime.  You
> can move the check to runtime easily:
>
> safeDiv x 0 = Nothing
> safeDiv x y = Just (x `div` y)
>
> Going the other way, from a runtime check to an obligation, is impossible.
>

(well, except for div x y = fromJust (safeDiv x y).. but the runtime check
is still there in terms of operation)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Zachary Turner
On Tue, Mar 24, 2009 at 4:11 PM, Manlio Perillo wrote:

> Conal Elliott ha scritto:
>
>> Another helpful strategy for the reader is to get smarter, i.e. to invest
>> effort in rising to the level of the writer.   Or just choose a different
>> book if s/he prefers.  - Conal
>>
>>
> This strategy is doomed to failure, unfortunately.
> We live in the real world, compromises are necessary.
>

It depends, IMO.  Making changes to the programming style one uses, in
particular ones such as you propose, would ultimate lead to programs in
haskell being less flexible and/or powerful than if they are.  I'm a bit new
to haskell myself, but I do understand that one of the primary uses cases
and/or motivating factors for using Haskell is when you really just NEED
that extra abstraction and power you get from being able to do these types
of things.  Someone once said that "simple problems should be simple and
difficult problems should be possible".  That doesn't mean the difficult
problems become EASY.  One of the best uses for haskell is solving difficult
problems.  It's obviously still going to be difficult to solve, and as such
the writer (and hence by extension the reader) is going to have to be smart
as well.

C++ is actually beginning to suffer the complexity problem as well,
especially with C++0x, but I fundamentally disagree with the added
complexity in C++, specifically because it is a language which is supposed
to excel at solving solve all kinds of problems.  Haskell excels at solving
difficult problems, so I don't think the target audience for Haskell
necessarily needs to include people who can't figure out difficult code.
C++ otoh they need to agree on a target audience or set of problems that
it's geared toward, and then either s**t or get off the pot.  It's fine if
they keep adding complexity until the cows come home, but just agree up
front that that's what it is and programmers who aren't cut out for it use a
different language.  With Haskell I think you have that up-front agreement,
so there's no problem.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Luke Palmer
On Tue, Mar 24, 2009 at 3:14 PM, Xiao-Yong Jin  wrote:

> Jake McArthur  writes:
>
> > Xiao-Yong Jin wrote:
> > | The problem is that there will be many functions using such
> > | a function to invert a matrix, making this inversion
> > | function return Either/Maybe or packing it in a monad is
> > | just a big headache.
> >
> > I disagree. If you try to take the inverse of a noninvertable matrix,
> > this is an *error* in your code. Catching an error you created in pure
> > code and patching it with chewing gum it is just a hack. A monadic
> > approach (I'm putting Either/Maybe under the same umbrella for brevity)
> > is the only solution that makes any sense to me, and I don't think it's
> > ugly as you are making it out to be.
> >
>
> Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
> Why does it throws this /ugly/ /error/ when it is applied to
> 0?  Why is it not using some beautiful
> 'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
> /ugly/ and doesn't make any sense?


It's a proof obligation, like using unsafePerformIO.  It is "okay" to use
unsafePerformIO when it exhibits purely functional semantics, but it's
possible to use it incorrectly, and there is no ImpureSemanticsException.
If you are being rigorous, you simply have to prove that the denominator
will not be zero, rather than relying on it to be caught at runtime.  You
can move the check to runtime easily:

safeDiv x 0 = Nothing
safeDiv x y = Just (x `div` y)

Going the other way, from a runtime check to an obligation, is impossible.


>
> >
> > | It is impractical to use method (a),
> > | because not every function that uses 'invMat' knows how to
> > | deal with 'invMat' not giving an answer.  So we need to use
> > | method (b), to use monad to parse our matrix around.
> > |
> > |> > invMat :: Matrix -> NumericCancerMonad Matrix
> > |
> > | It hides the exceptional nature of numerical computations
> > | very well, but it is cancer in the code.  Whenever any
> > | function wants to use invMat, it is mutated.  This is just
> > | madness.  You don't want to make all the code to be monadic
> > | just because of singularities in numeric calculation.
> >
> > For functions that don't know or don't care about failure, just use fmap
> > or one of its synonyms.
> >
> > ~scalarMult 2 <$> invMat x
> >
> > See? The scalarMult function is pure, as it should be. There is no
> > madness here.
>
> Of course, 'scalarMult' is invulnerable and free of monad.
> But take a look at the following functions,
>
> > f1 = scalarMult 2 . invMat
> > f2 l r = l `multMat` invMat r
> > ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
> > ff x y = do let ff' = f1 x + f2 y
> > put . (addMat ff') . f1 << get
> > tell $ f2 ff'
> > when (matrixWeDontLike (f1 ff') $
> >  throwError MatrixWeDontLike
> > return $ scalarMult (1/2) ff'
>
> Yes, I know, it's not really complicate to rewrite the above
> code.  But, what do I really gain from this rewrite?
> --
>c/*__o/*
><\ * (__
>*/\  <
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Dan Piponi
> Miguel Mitrofanov wrote:
>> takeList = evalState . mapM (State . splitAt)

> However, ironically, I stopped using them for pretty
> much the same reason that Manlio is saying.

Are you saying there's a problem with this implementation? It's the
only one I could just read immediately. The trick is to see that
evalState and State are just noise for the type inferencer so we just
need to think about mapM splitAt. This turns a sequence of integers
into a sequence of splitAts, each one chewing on the leftovers of the
previous one. *Way* easier than both the zipWith one-liner and the
explicit version. It says exactly what it means, almost in English.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Bas van Dijk
2009/3/24 Peter Verswyvelen :
> But aren't these two definitions different algoritms? At first sight I think
> the second one is more efficient than the first one.

Some performance numbers:

--

module Main where

import System.Environment (getArgs)
import Control.Monad.State (State(..), evalState)

takeList1, takeList2, takeList3 :: [Int] -> [a] -> [[a]]

takeList1 [] _ =  []
takeList1 _ [] =  []
takeList1 (n : ns) xs  =  head : takeList1 ns tail
where (head, tail) = splitAt n xs

takeList2 ns xs = zipWith take ns . init . scanl (flip drop) xs $ ns

takeList3 = evalState . mapM (State . splitAt)

test :: Int -> [[Int]]
test n = takeList1 (take n [1..]) [1..]

main :: IO ()
main = print . sum . map sum . test . read . head =<< getArgs

--

compile with: ghc --make TakeList.hs -o takeList1 -O2

$ time ./takeList1 5000
739490938

real0m6.229s
user0m5.787s
sys 0m0.342s

$ time ./takeList2 5000
739490938

real0m5.089s
user0m4.455s
sys 0m0.348s

$ time ./takeList3 5000
739490938

real0m6.224s
user0m5.750s
sys 0m0.347s

--

regards

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Gregg Reynolds
On Tue, Mar 24, 2009 at 1:42 PM, Manlio Perillo
 wrote:
>
> But, as an example, when you read a function like:
>
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
>
> that can be rewritten (argument reversed) as:
>
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _         =  []
> takeList _ []         =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>    where (head, tail) = splitAt n xs
>
> I think that there is a problem.

This crops up all the time even in simple mathematics.  One way to
provide assistance to newcomers is to provide a quasi-English reading
of the notation.  Take as an example a simple set comprehension
expression (using Z email notation,
http://csci.csusb.edu/dick/samples/z.lexis.html):

   { x : Int | 0 < x < 10 /\ x %e Odd @ 2*x }

That's pretty opaque for beginners until they learn to read | as "such
that", %e as "member of" and @ as "generate", so that they can express
the idea in quasi-English:  "form a set by taking  all integers x such
that ... and ..., then generate the result by doubling them" or the
like.  Or take | as "filter" and @ as "map"; the point is it helps to
be able to express it in something like natural language.

Do something similar for your buildPartitions definition and I'll bet
you'll end up with something much more user friendly than takeList.

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Peter Verswyvelen
On Tue, Mar 24, 2009 at 10:11 PM, Manlio Perillo
wrote:

> This strategy is doomed to failure, unfortunately.


So it is the good strategy, because Haskell's slogan is "avoid success at
all cost" :-)


> We live in the real world, compromises are necessary.


I don't think so. It's just that we have different kinds of people with
different skills. If you try to please the whole world, you please nobody.

As a beginner Haskeller, I just know I need more practice. folding is now
natural to me, but monad transformers and applicative stuff not yet, but
that's a matter of time. I just need to practice practice practice.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
"The reasonable man adapts himself to the world; the unreasonable one
persists in trying to adapt the world to himself. Therefore all progress
depends on the unreasonable man."  - George Bernard Shaw

On Tue, Mar 24, 2009 at 2:11 PM, Manlio Perillo wrote:

> Conal Elliott ha scritto:
>
>> Another helpful strategy for the reader is to get smarter, i.e. to invest
>> effort in rising to the level of the writer.   Or just choose a different
>> book if s/he prefers.  - Conal
>>
>>
> This strategy is doomed to failure, unfortunately.
> We live in the real world, compromises are necessary.
>
> > [...]
>
>
> Manlio
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
Hah!  It sure is.  :)

On Tue, Mar 24, 2009 at 2:17 PM, Peter Verswyvelen wrote:

> Sometimes that is very hard when the writer is way smarter than the reader
> :-)
> 2009/3/24 Conal Elliott 
>
> Another helpful strategy for the reader is to get smarter, i.e. to invest
>> effort in rising to the level of the writer.   Or just choose a different
>> book if s/he prefers.  - Conal
>>
>>
>> On Tue, Mar 24, 2009 at 1:44 PM, Manlio Perillo > > wrote:
>>
>>> Yitzchak Gale ha scritto:
>>>
 [...]
 So the bottom line is that Manlio is right, really. It's just
 that Haskell is still very different than what most
 programmers are used to. So it does take a while to
 get a feeling for what is "too smart".


>>> Right, you centered the problem!
>>>
>>> The problem is where to place the separation line between "normal" and
>>> "too smart".
>>>
>>> Your function is readable, once I mentally separate each step.
>>> For someone with more experience, this operation may be automatic, and
>>> the function may appear totally natural.
>>>
>>> When writing these "dense" function, it is important, IMHO, to help the
>>> reader using comments, or by introducing intermediate functions.
>>>
>>>
>>> Manlio
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Lutz Donnerhacke
* Manlio Perillo wrote:
> But this may be really a question of personal taste or experience.
> What is more "natural"?
>
> 1) pattern matching
> 2) recursion
> or
> 1) function composition
> 2) high level functions

Composition of library functions is usually much more readable than hand
written recursion, simply because the typical idiom is highlighted instead
of checking yourself, that there is no strange matching against the obvious
case.

Composition of library functions is usually much more efficient and
preferable than hand written recursion, simply because the fine tuned fusion
capabilities.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Peter Verswyvelen
Sometimes that is very hard when the writer is way smarter than the reader
:-)
2009/3/24 Conal Elliott 

> Another helpful strategy for the reader is to get smarter, i.e. to invest
> effort in rising to the level of the writer.   Or just choose a different
> book if s/he prefers.  - Conal
>
>
> On Tue, Mar 24, 2009 at 1:44 PM, Manlio Perillo 
> wrote:
>
>> Yitzchak Gale ha scritto:
>>
>>> [...]
>>> So the bottom line is that Manlio is right, really. It's just
>>> that Haskell is still very different than what most
>>> programmers are used to. So it does take a while to
>>> get a feeling for what is "too smart".
>>>
>>>
>> Right, you centered the problem!
>>
>> The problem is where to place the separation line between "normal" and
>> "too smart".
>>
>> Your function is readable, once I mentally separate each step.
>> For someone with more experience, this operation may be automatic, and the
>> function may appear totally natural.
>>
>> When writing these "dense" function, it is important, IMHO, to help the
>> reader using comments, or by introducing intermediate functions.
>>
>>
>> Manlio
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Grouping - Map / Reduce

2009-03-24 Thread Gü?nther Schmidt

Hi,

let say I got an unordered lazy list of key/value pairs like

[('a', 99), ('x', 42), ('a', 33) ... ]

and I need to sum up all the values with the same keys.

So far I wrote a naive implementation, using Data.Map, foldl and insertWith.

The result of this grouping operation, which is effectively another list
of key/value pairs, just sums this time, needs to be further processed.

The building of this map is of course a bottleneck, the successive
processing needs to wait until the entire list is eventually consumed
the Map is built and flattened again.

Is there another way of doing this, something more "streaming
architecture" like?

Is Googles "Map - Reduce" related to this?

Günther


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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread John Van Enk
If any one seconds the motion, i'm picking up this part of the thread and
putting it in the humor section of the haskell wiki.
/jve


On Tue, Mar 24, 2009 at 4:48 PM, Ross Mellgren  wrote:

> import Diebold.Unsafe (unsafeChangeVotes)...
>
> ?
>
> -Ross
>
> On Mar 24, 2009, at 4:47 PM, John Van Enk wrote:
>
> Unless there's a rogue unsafeChangeVotes call in there somewhere.
>
> On Tue, Mar 24, 2009 at 4:46 PM, Ross Mellgren wrote:
>
>> Doesn't matter how many times you seq the results, the thunk has been
>> forced.
>>
>> -Ross
>>
>>
>> On Mar 24, 2009, at 4:45 PM, FFT wrote:
>>
>> I demand a recount! The one that launches the missile should have won!
>>>
>>> 2009/3/24 Eelco Lempsink :
>>>
 The results of the Haskell logo competition are in!

 You can view them at
 http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl
 ?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath

 Congratulations Jeff Wheeler!

 I'll set up a page with the results visibile.

 --
 Regards,

 Eelco Lempsink


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


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


[Haskell-cafe] Re: Exception handling in numeric computations

2009-03-24 Thread Xiao-Yong Jin
Jake McArthur  writes:

> Xiao-Yong Jin wrote:
> | The problem is that there will be many functions using such
> | a function to invert a matrix, making this inversion
> | function return Either/Maybe or packing it in a monad is
> | just a big headache.
>
> I disagree. If you try to take the inverse of a noninvertable matrix,
> this is an *error* in your code. Catching an error you created in pure
> code and patching it with chewing gum it is just a hack. A monadic
> approach (I'm putting Either/Maybe under the same umbrella for brevity)
> is the only solution that makes any sense to me, and I don't think it's
> ugly as you are making it out to be.
>

Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
Why does it throws this /ugly/ /error/ when it is applied to
0?  Why is it not using some beautiful
'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
/ugly/ and doesn't make any sense?

>
> | It is impractical to use method (a),
> | because not every function that uses 'invMat' knows how to
> | deal with 'invMat' not giving an answer.  So we need to use
> | method (b), to use monad to parse our matrix around.
> |
> |> > invMat :: Matrix -> NumericCancerMonad Matrix
> |
> | It hides the exceptional nature of numerical computations
> | very well, but it is cancer in the code.  Whenever any
> | function wants to use invMat, it is mutated.  This is just
> | madness.  You don't want to make all the code to be monadic
> | just because of singularities in numeric calculation.
>
> For functions that don't know or don't care about failure, just use fmap
> or one of its synonyms.
>
> ~scalarMult 2 <$> invMat x
>
> See? The scalarMult function is pure, as it should be. There is no
> madness here.

Of course, 'scalarMult' is invulnerable and free of monad.
But take a look at the following functions,

> f1 = scalarMult 2 . invMat
> f2 l r = l `multMat` invMat r
> ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
> ff x y = do let ff' = f1 x + f2 y
> put . (addMat ff') . f1 << get
> tell $ f2 ff'
> when (matrixWeDontLike (f1 ff') $
>  throwError MatrixWeDontLike
> return $ scalarMult (1/2) ff'

Yes, I know, it's not really complicate to rewrite the above
code.  But, what do I really gain from this rewrite?
-- 
c/*__o/*
<\ * (__
*/\  <
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Conal Elliott ha scritto:
Another helpful strategy for the reader is to get smarter, i.e. to 
invest effort in rising to the level of the writer.   Or just choose a 
different book if s/he prefers.  - Conal




This strategy is doomed to failure, unfortunately.
We live in the real world, compromises are necessary.

> [...]


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


Re: [Haskell-cafe] Making videos of your project

2009-03-24 Thread Don Stewart
claus.reinke:
> Perhaps the "make a video" slogan doesn't quite explain what is
> intended - it didn't to me!-) Reading John Udell's short article
>
> What is Screencasting?
> http://www.oreillynet.com/pub/a/oreilly/digitalmedia/2005/11/16/what-is-screencasting.html?page=1
>
> gave me a better idea: the screen video part is the modern, animated  
> version of manuals with screenshots, now with audio or text caption  
> annotations (a canned demo). He also gives some tool references, and some 
> suggestions for focussing the bandwidth on useful contents, editing, 
> privacy considerations, etc. Almost certainly, this
>
>>2. type 'recordmydesktop'
>>3. do something with haskell
>>4. hit control-C
>>5. upload out.ogv to youtube
>
> is not a useful recipe - screencasts need planning of the steps one
> wants to demonstrate, editing out of aimless moving around or
> thinking about what to show next, annotations that guide the viewer (text 
> labels or audio track that explains what can be seen,
> or what keyboard shortcuts are used, or what the plan is), and probably 
> several attempts to get one useful result (minimal bandwith/length/.. 
> with maximal "ah, that is how I do it" or "ah, that is how it works" or 
> "cool, I want to install that" effect). 
 
> But with a little effort, this could be very useful, more so than simple 
> screenshots, lots of text, or combinations thereof, if the
> focus is not so much on producing a video to watch, but on
> showing potential users what they are going to see, and how
> to work with it if they decide to install it. For instance, I'd now like  
> to replace my old tour of haskellmode for Vim with a screencast.

Great! Yes, this is exactly what I hope. It is so much clearer why I
would want to use something when I can see it in use.

 
> As a windows user, I tried playing with CamStudio and that almost seems 
> to do the job (capture, annotation, replay, conversion
> of .avi to compressed .swf) but I don't like the resolution of the .swf 
> it generates (screen text isn't as readable as I've seen in other
> screencasts). Perhaps I'm missing an option to improve the quality, or 
> can anyone recommend another free tool for windows, from
> positive experience (wikipedia has a whole list of tools
> http://en.wikipedia.org/wiki/Comparison_of_screencasting_software )?
>
> For the purpose I have in mind, it would be good to have
> many small pieces of screencast, one for each feature, or even better, 
> one continuous screencast with the ability to link directly to sections 
> dealing with particular topics - a hyperlinked animation. Is that 
> supported by some (free) tool?


That would be very cool.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
"Recursion is the goto of functional programming".  Also, "Do not confuse
what is natural with what is habitual."  - Conal

On Tue, Mar 24, 2009 at 1:51 PM, Manlio Perillo wrote:

> Jake McArthur ha scritto:
>
>> [...]
>> | With my function, instead, you only have to "follow" 1 operation:
>> |
>> | Prelude> (head, tail) = splitAt n xs
>>
>> I think you are way oversimplifying your own code.
>>
>> ~takeList :: [Int] -> [a] -> [[a]]
>> ~takeList [] _ =  []
>> ~takeList _ [] =  []
>> ~takeList (n : ns) xs  =  head : takeList ns tail
>> ~where (head, tail) = splitAt n xs
>>
>> In order to understand this, I have to look at three different cases, an
>> uncons, a splitAt, a cons, *and* a recursive call. This is *seven*
>> different things I have to absorb.
>>
>
> These cases are, IMHO, more "natural".
>
> We have a set of equations, pattern matching and recursion.
> These are one of the basic building block of Haskell.
>
> The only "foreign" building block is the splitAt function.
>
> But this may be really a question of personal taste or experience.
> What is more "natural"?
>
> 1) pattern matching
> 2) recursion
> or
> 1) function composition
> 2) high level functions
>
> ?
>
> > [...]
>
>
> Manlio
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Conal Elliott
Another helpful strategy for the reader is to get smarter, i.e. to invest
effort in rising to the level of the writer.   Or just choose a different
book if s/he prefers.  - Conal

On Tue, Mar 24, 2009 at 1:44 PM, Manlio Perillo wrote:

> Yitzchak Gale ha scritto:
>
>> [...]
>> So the bottom line is that Manlio is right, really. It's just
>> that Haskell is still very different than what most
>> programmers are used to. So it does take a while to
>> get a feeling for what is "too smart".
>>
>>
> Right, you centered the problem!
>
> The problem is where to place the separation line between "normal" and "too
> smart".
>
> Your function is readable, once I mentally separate each step.
> For someone with more experience, this operation may be automatic, and the
> function may appear totally natural.
>
> When writing these "dense" function, it is important, IMHO, to help the
> reader using comments, or by introducing intermediate functions.
>
>
> Manlio
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Jake McArthur ha scritto:

[...]
| With my function, instead, you only have to "follow" 1 operation:
|
| Prelude> (head, tail) = splitAt n xs

I think you are way oversimplifying your own code.

~takeList :: [Int] -> [a] -> [[a]]
~takeList [] _ =  []
~takeList _ [] =  []
~takeList (n : ns) xs  =  head : takeList ns tail
~where (head, tail) = splitAt n xs

In order to understand this, I have to look at three different cases, an
uncons, a splitAt, a cons, *and* a recursive call. This is *seven*
different things I have to absorb.


These cases are, IMHO, more "natural".

We have a set of equations, pattern matching and recursion.
These are one of the basic building block of Haskell.

The only "foreign" building block is the splitAt function.

But this may be really a question of personal taste or experience.
What is more "natural"?

1) pattern matching
2) recursion
or
1) function composition
2) high level functions

?

> [...]


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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Ross Mellgren

import Diebold.Unsafe (unsafeChangeVotes)
...

?

-Ross

On Mar 24, 2009, at 4:47 PM, John Van Enk wrote:


Unless there's a rogue unsafeChangeVotes call in there somewhere.

On Tue, Mar 24, 2009 at 4:46 PM, Ross Mellgren hask...@z.odi.ac> wrote:
Doesn't matter how many times you seq the results, the thunk has  
been forced.


-Ross


On Mar 24, 2009, at 4:45 PM, FFT wrote:

I demand a recount! The one that launches the missile should have won!

2009/3/24 Eelco Lempsink :
The results of the Haskell logo competition are in!

You can view them at
http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl? 
num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath


Congratulations Jeff Wheeler!

I'll set up a page with the results visibile.

--
Regards,

Eelco Lempsink


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


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

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



--
/jve


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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread John Van Enk
Unless there's a rogue unsafeChangeVotes call in there somewhere.

On Tue, Mar 24, 2009 at 4:46 PM, Ross Mellgren  wrote:

> Doesn't matter how many times you seq the results, the thunk has been
> forced.
>
> -Ross
>
>
> On Mar 24, 2009, at 4:45 PM, FFT wrote:
>
> I demand a recount! The one that launches the missile should have won!
>>
>> 2009/3/24 Eelco Lempsink :
>>
>>> The results of the Haskell logo competition are in!
>>>
>>> You can view them at
>>> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl
>>> ?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath
>>>
>>> Congratulations Jeff Wheeler!
>>>
>>> I'll set up a page with the results visibile.
>>>
>>> --
>>> Regards,
>>>
>>> Eelco Lempsink
>>>
>>>
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Luke Palmer
On Tue, Mar 24, 2009 at 2:45 PM, FFT  wrote:

> I demand a recount! The one that launches the missile should have won!


I guess nobody evaluated its merits.


>
>
> 2009/3/24 Eelco Lempsink :
> > The results of the Haskell logo competition are in!
> >
> > You can view them at
> >
> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath
> >
> > Congratulations Jeff Wheeler!
> >
> > I'll set up a page with the results visibile.
> >
> > --
> > Regards,
> >
> > Eelco Lempsink
> >
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread Ross Mellgren
Doesn't matter how many times you seq the results, the thunk has been  
forced.


-Ross

On Mar 24, 2009, at 4:45 PM, FFT wrote:


I demand a recount! The one that launches the missile should have won!

2009/3/24 Eelco Lempsink :

The results of the Haskell logo competition are in!

You can view them at
http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl? 
num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath


Congratulations Jeff Wheeler!

I'll set up a page with the results visibile.

--
Regards,

Eelco Lempsink


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



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


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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread FFT
I demand a recount! The one that launches the missile should have won!

2009/3/24 Eelco Lempsink :
> The results of the Haskell logo competition are in!
>
> You can view them at
> http://www.cs.cornell.edu/w8/~andru/cgi-perl/civs/results.pl?num_winners=1&id=E_d21b0256a4fd5ed7&algorithm=beatpath
>
> Congratulations Jeff Wheeler!
>
> I'll set up a page with the results visibile.
>
> --
> Regards,
>
> Eelco Lempsink
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Yitzchak Gale ha scritto:

[...]
So the bottom line is that Manlio is right, really. It's just
that Haskell is still very different than what most
programmers are used to. So it does take a while to
get a feeling for what is "too smart".



Right, you centered the problem!

The problem is where to place the separation line between "normal" and 
"too smart".


Your function is readable, once I mentally separate each step.
For someone with more experience, this operation may be automatic, and 
the function may appear totally natural.


When writing these "dense" function, it is important, IMHO, to help the 
reader using comments, or by introducing intermediate functions.



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


Re: Exception handling in numeric computations (was Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?)

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Daniel Yokomizo wrote:


If we try the other approach, we need to express the totality of
invMat by restricting its domain, so we can add, for example, a
phantom type to Matrix to signal it is invertible. As you need to
construct the Matrix before trying to invert it you can always make
the constructors smart enough to bundle the Matrix with such
properties. Of course there's need to do some runtime verifications
earlier, but the clients of invMat are required to do the verification
earlier or pass it to their clients (up to the level that can handle
with this issue):

data Invertible
tryInvertible :: Matrix a -> Maybe (Matrix Invertible)
invMat :: Matrix Invertible -> Matrix Invertible


This would be a very elegant solution. However when it comes to floating 
point numbers I'm afraid there are no much other ways than inverting a 
matrix if you want to know if it is invertible. You may however use 
representations of a matrix (like an LU decomposition or a QR 
decomposition) internally that are half-way of inversion.

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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Peter Verswyvelen
On Tue, Mar 24, 2009 at 7:48 PM, Jonathan Cast wrote:

> On Tue, 2009-03-24 at 19:42 +0100, Manlio Perillo wrote:
> > But, as an example, when you read a function like:
> >
> > buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
> >
> > that can be rewritten (argument reversed) as:
> >
> > takeList :: [Int] -> [a] -> [[a]]
> > takeList [] _ =  []
> > takeList _ [] =  []
> > takeList (n : ns) xs  =  head : takeList ns tail
> >  where (head, tail) = splitAt n xs
>
> Huh?  This is ugly and un-readable.  Seriously.
>

I think this is subjective. Personally I can understand the second
definition immediately, but the first one requires some puzzling. But that
might be because I'm relatively new to Haskell. Of course the usage of head
and tail in the example is unfortunate, one should not use these shadowing
names.

But aren't these two definitions different algoritms? At first sight I think
the second one is more efficient than the first one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Exception handling in numeric computations (was Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?)

2009-03-24 Thread Henning Thielemann


On Tue, 24 Mar 2009, Xiao-Yong Jin wrote:


invMat :: Matrix -> Matrix


You won't be able to invert all the matrix, mathematically.
And computationally, even a larger set of matrix might fail
to be inverted because of the finite precision.  It is
relatively easier and more efficient to spot such a problem
within this 'invMat' function.  Because testing the
singularity of a matrix is equally hard as invert it.  So
all I can do when 'invMat' spot a singular matrix are

 a) Return Either/Maybe to signal an error.


This is the way to go.


 b) Wrap it in a monad.


Either and Maybe are monads. These monads behave like exceptions in other 
languages. I like to call these exceptions.



 c) Define a dynamic exception and throw it.


You cannot throw an exception in code that does not return Maybe, Either, 
IO or such things. You can only abuse 'undefined' and turn it into a 
defined value later by a hack. Think of 'undefined' as an infinite loop, 
that cannot detected in general. GHC is kind enough to detect special 
cases, in order to simplify debugging. But this should be abused for 
exceptional return values.



The problem is that there will be many functions using such
a function to invert a matrix, making this inversion
function return Either/Maybe or packing it in a monad is
just a big headache.  It is impractical to use method (a),
because not every function that uses 'invMat' knows how to
deal with 'invMat' not giving an answer.


How shall it deal with 'undefined' then? 'undefined' can only be handled 
by a hack, so Maybe or Either are clearly better.



invMat :: Matrix -> NumericCancerMonad Matrix


It hides the exceptional nature of numerical computations
very well, but it is cancer in the code.  Whenever any
function wants to use invMat, it is mutated.  This is just
madness.


No it makes explicit what's going on. This is the idea of functional 
programming. You have nice Applicative infix operators in order to write 
everything in a functional look anyway. In contrast, I think it is mad 
that there is no function of type

  mulInt :: Int -> Int -> Maybe Int
 which allows us to catch overflows without using hacks. This function 
could be easily integrated in a compiler, since the CPUs show by a flag, 
that an overflow occurs. In most high level languages this is not 
possible, and thus programming in an overflow-proof way needs additional 
computations.


 You don't want to make all the code to be monadic just because of 
singularities in numeric calculation. Therefore, in my opinion, method 
(c) is my only option.


Then better stick to MatLab. :-(
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Manlio Perillo wrote:
| With the original version, you have to "follow" 3 separate operations:
|
| Prelude> let xs = [1, 2, 3, 4] :: [Int]
| Prelude> let ns = [3, 1] :: [Int]
| Prelude> let _1 = scanl (flip drop) xs ns
| Prelude> let _2 = init _1
| Prelude> let _3 = zipWith take ns _2
|
|
| With my function, instead, you only have to "follow" 1 operation:
|
| Prelude> (head, tail) = splitAt n xs

I think you are way oversimplifying your own code.

~takeList :: [Int] -> [a] -> [[a]]
~takeList [] _ =  []
~takeList _ [] =  []
~takeList (n : ns) xs  =  head : takeList ns tail
~where (head, tail) = splitAt n xs

In order to understand this, I have to look at three different cases, an
uncons, a splitAt, a cons, *and* a recursive call. This is *seven*
different things I have to absorb.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJQ1MACgkQye5hVyvIUKl+hQCfc7Yd8mi8uXDRTZQa11Pn8zeT
cZMAnApAcI+pr0wpYUP6Z0jHQ2vtf0ze
=Z5ze
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugs on iPhone

2009-03-24 Thread David Leimbach
2009/3/24 Rick R 

> Correct. My point was only in the case that it would need to statically
> link to a GPL'd lib (which I'm not sure if such a case exists)
> If the gcc license suddenly decided to claim compiled items as derivative
> works, the IT world as we know it would end.


Any linkage to GPL has different implications than dynamic or static linkage
to LGPL code.  And I'm not a lawyer, so I won't comment on this crap because
it's all freaking ridiculous.

People who believe in using and writing software that people are free to use
any way they want should just stay the hell away from anything from the
FSF.

I like freedom from restrictions, not freedom with restrictions.

Dave


>
>
> On Tue, Mar 24, 2009 at 11:06 AM, John Meacham  wrote:
>
>> On Mon, Mar 23, 2009 at 07:00:26PM -0400, Rick R wrote:
>> > The agreement doesn't specifically prohibit the use of interpreters
>> (just
>> > those than run external code). It also doesn't say anything about
>> machine
>> > generated code. The only thing one would have to ensure is that the
>> > dependencies of JHC are all compiled in, or statically linked. Shared
>> libs
>> > are disallowed in any app. If it has a runtime dependency on gcc (is
>> there
>> > such a thing?) Then you would have to statically link it and therefore
>> > couldn't sell your application. (gotta love GPL)
>>
>> No problem here, the gcc licence explicity states things compiled with it
>> are not
>> considered derivative works. And after all, Mac OS X is compiled with
>> gcc, apple X-Code uses gcc as its compiler and I think gcc may even be
>> the only objective C compiler out there.
>>
>>John
>>
>>
>> --
>> John Meacham - ⑆repetae.net⑆john⑈
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> We can't solve problems by using the same kind of thinking we used when we
> created them.
>- A. Einstein
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Yitzchak Gale
Manlio Perillo complained about:
>> buildPartitions xs ns = zipWith take ns . init . scanl (flip drop) xs $ ns

Miguel Mitrofanov wrote:
> takeList = evalState . mapM (State . splitAt)

Ha! Bravo!

As the author of the offending zipWith/scanl version,
I can say that love those State monad one-liners.
However, ironically, I stopped using them for pretty
much the same reason that Manlio is saying.

The difference is that zipWith and scanl are classic Haskell
idioms that any Haskell programmer will learn fairly early
on. Whereas State monad one-liners used to be thought of
as new and fancy and esoteric. But now they are becoming
more mainstream, so perhaps I should go back to them.

So the bottom line is that Manlio is right, really. It's just
that Haskell is still very different than what most
programmers are used to. So it does take a while to
get a feeling for what is "too smart".

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


Re: [Haskell-cafe] The votes are in!

2009-03-24 Thread John Van Enk
> and that baby eating is an acceptable part of Haskell optimization

Actually, yes. It's usually best used like this:

data Foo = Bar {-# UNPACK #-} {-# EAT BABY #-} !Int

On Tue, Mar 24, 2009 at 8:42 AM, Creighton Hogg  wrote:

> 2009/3/24 John Van Enk :
> > Is this the part where all the pundits come out and talk about how Jeff
> > isn't a citizen, eats babies, and wants to turn Haskell into an
> imperative
> > language?
>
> Well given the fact that Haskell has been called the world's best
> imperative language, that we have a multinational community, and that
> baby eating is an acceptable part of Haskell optimization* I think
> he'll fit in just fine.
>
> * Don Stewart might have a blog post about this, but I'm too lazy to look
> it up.
>



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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Jake McArthur ha scritto:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Manlio Perillo wrote:
| This is right.
| The problem is that often (IMHO) a function definition can be rewritten
| so that it is much more readable.
|
| As an example, with the takeList function I posted.

I looked at it, found nothing wrong with the original, and absolutely
hated your "fixed" version. 


With the original version, you have to "follow" 3 separate operations:

Prelude> let xs = [1, 2, 3, 4] :: [Int]
Prelude> let ns = [3, 1] :: [Int]
Prelude> let _1 = scanl (flip drop) xs ns
Prelude> let _2 = init _1
Prelude> let _3 = zipWith take ns _2


With my function, instead, you only have to "follow" 1 operation:

Prelude> (head, tail) = splitAt n xs

> [...]


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Miguel Mitrofanov wrote:
| Maybe it's just me, but I think that
|
| takeList ns xs = evalState (mapM (State . splitAt) ns) xs
|
| or even
|
| takeList = evalState . map (State . splitAt)
|
| would be much clearer than both versions.

Definitely. I stuck with only the functions that were already being used
because I figured the point was to make things readable with a limited
set of building blocks. Thanks for sharing though. That was definitely
not a solution that I was thinking of.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJN9gACgkQye5hVyvIUKn5AACgpLGOwp5asyFxPj6r/sjt4jz/
I7AAoIDDvYbpmWB8/Ag5ui+vNzvbHQ4l
=NxfM
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Eugene Kirpichov
Pretty cool once you know what the function does, but I must admit I
wouldn't immediately guess the purpose of the function when written in
this way.

2009/3/24 Miguel Mitrofanov :
>> | As an example, with the takeList function I posted.
>>
>> I looked at it, found nothing wrong with the original, and absolutely
>> hated your "fixed" version. I might have written it like this, instead:
>>
>> ~    buildPartitions xs ns = zipWith take ns . init . scanl (flip drop)
>> xs $ ns
>
> Maybe it's just me, but I think that
>
> takeList ns xs = evalState (mapM (State . splitAt) ns) xs
>
> or even
>
> takeList = evalState . map (State . splitAt)
>
> would be much clearer than both versions.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ACM Task for C++ and Java programmers in Haskell. How to make code faster?

2009-03-24 Thread Vasyl Pasternak
I changed the program, now it similar to the program from the wiki
(http://www.haskell.org/haskellwiki/Phone_number)

The version with ByteString compared to version with ordinary Strings
works 3.5 times faster.
(I put it to http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2830)

But version with Data.Trie dissapointed me, it works 5 times slover
than version with Data.Map ByteString.
(here is the code http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2829)

Anyway, thanks to everyone who helped me, Haskell is really powerfull
tool in clever hands :)


2009/3/23 wren ng thornton :
> Vasyl Pasternak wrote:
>> The entire code I placed on
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=2764
>>
>> Could someone help me to make this code faster? I'd like to see
>> solution that will be elegant and fast, without heavy optimizations,
>> that will make code unreadable. Also, if it possible, prepare the
>> program to support SMP parallelism.
>
> The solution's already been posted, but to make this particular code
> faster, I recommend using Data.Trie instead of Data.Map ByteString. Tries
> are faster for lookup since they don't redundantly check the prefix of the
> query; also they're better for memory usage because they don't store
> redundant copies of the prefixes.
>
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bytestring-trie
>
> --
> Live well,
> ~wren
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Best regards,
Vasyl Pasternak
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Miguel Mitrofanov

| As an example, with the takeList function I posted.

I looked at it, found nothing wrong with the original, and absolutely
hated your "fixed" version. I might have written it like this,  
instead:


~buildPartitions xs ns = zipWith take ns . init . scanl (flip  
drop)

xs $ ns


Maybe it's just me, but I think that

takeList ns xs = evalState (mapM (State . splitAt) ns) xs

or even

takeList = evalState . map (State . splitAt)

would be much clearer than both versions.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Eugene Kirpichov
2009/3/24 Manlio Perillo :
> Tim Newsham ha scritto:
>>>
>>> These friends are very interested in Haskell, but it seems that the main
>>> reason why they don't start to seriously learning it, is that when they
>>> start reading some code, they feel the "Perl syndrome".
>>>
>>> That is, code written to be "too smart", and that end up being totally
>>> illegible by Haskell novice.
>>>
>>> I too have this feeling, from time to time.
>>>
>>> Since someone is starting to write the Haskell coding style, I really
>>> suggest him to take this "problem" into strong consideration.
>>
>> When you think about it, what you are saying is that Haskell programmers
>> shouldn't take advantage of the extra tools that Haskell provides.
>
> No, I'm not saying this.
>
> But, as an example, when you read a function like:
>
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
>

Wow, very cool! And very readable; I actually got the idea of the
function is going to do after reading the scanl (flip drop) and the
rest of the function only convinced me that I was right.

The second version is far worse, because it forces me to think about
what to do if the lists are empty, how to decompose them if they
aren't - all this stuff is 'imperative' and irrelevant to the problem,
and is elegantly omitted in the one-liner.

> that can be rewritten (argument reversed) as:
>
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _         =  []
> takeList _ []         =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>    where (head, tail) = splitAt n xs
>
> I think that there is a problem.
>
> The buildPartition contains too many "blocks".
> And I have read code with even more "blocks" in one line.
>
> It may not be a problem for a "seasoned" Haskell programmer, but when you
> write some code, you should never forget that your code will be read by
> programmers that can not be at your same level.
>
> I think that many Haskell programmers forget this detail, and IMHO this is
> wrong.
>
>> Haskell provides the ability to abstract code beyond what many other
>> programming systems allow.  This abstraction gives you the ability to
>> express things much more tersely.  This makes the code a lot harder to read
>> for people who are not familiar with the abstractions being used.
>
> The problem is that I have still problems at reading and understanding code
> that is too much terse...
> Because I have to assemble in my mind each block, and if there are too many
> blocks I have problems.
>
>> [...]
>
>
> Manlio
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Tim Newsham
When you think about it, what you are saying is that Haskell programmers 
shouldn't take advantage of the extra tools that Haskell provides. 


No, I'm not saying this.

But, as an example, when you read a function like:

buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns

that can be rewritten (argument reversed) as:

takeList :: [Int] -> [a] -> [[a]]
takeList [] _ =  []
takeList _ [] =  []
takeList (n : ns) xs  =  head : takeList ns tail
   where (head, tail) = splitAt n xs


I think this is a perfect example.  Haskell allows you to abstract out the 
concepts of recursion, zipping and iteration.  Your alternative reproduces 
these explicitely and intermixes them.  You are saying that programmers 
should avoid using these higher level abstractions and instead fall back 
to more explicit constructs that are, for you, easier to read.


The problem is that I have still problems at reading and understanding code 
that is too much terse...
Because I have to assemble in my mind each block, and if there are too many 
blocks I have problems.


It takes practice to read and to write.  The benefit is more 
expressiveness and more code reuse.



Manlio


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Manlio Perillo wrote:
| This is right.
| The problem is that often (IMHO) a function definition can be rewritten
| so that it is much more readable.
|
| As an example, with the takeList function I posted.

I looked at it, found nothing wrong with the original, and absolutely
hated your "fixed" version. I might have written it like this, instead:

~buildPartitions xs ns = zipWith take ns . init . scanl (flip drop)
xs $ ns

I think this way separates the different "stages" of the function
somewhat better, but it's barely a change. The original was fine.

| In other cases, you can just break long lines, introducing intermediate
| functions that have a descriptive name *and* a type definition.
|
| Doing this is an art, but a coding style for Haskell should try to
| document this.

Agreed.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAknJL1gACgkQye5hVyvIUKnF/ACgjbd+gjolHCiS9tWosbiH3gnX
j0EAn2zbeanj9UUQnl1pnQ+GRdPpYiRj
=h5bU
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 19:42 +0100, Manlio Perillo wrote:
> Tim Newsham ha scritto:
> >> These friends are very interested in Haskell, but it seems that the 
> >> main reason why they don't start to seriously learning it, is that 
> >> when they start reading some code, they feel the "Perl syndrome".
> >>
> >> That is, code written to be "too smart", and that end up being totally 
> >> illegible by Haskell novice.
> >>
> >> I too have this feeling, from time to time.
> >>
> >> Since someone is starting to write the Haskell coding style, I really 
> >> suggest him to take this "problem" into strong consideration.
> > 
> > When you think about it, what you are saying is that Haskell programmers 
> > shouldn't take advantage of the extra tools that Haskell provides. 
> 
> No, I'm not saying this.
> 
> But, as an example, when you read a function like:
> 
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
> 
> that can be rewritten (argument reversed) as:
> 
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _ =  []
> takeList _ [] =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>  where (head, tail) = splitAt n xs

Huh?  This is ugly and un-readable.  Seriously.

> I think that there is a problem.

Damn straight.  It should be:

> buildPartitions xs ns =
> zipWith take ns $ init $ scanl (flip drop) xs ns

Or, if you're really worried about blocks/line, you can increase the
line count a bit (I do this regularly):

> buildPartitions xs ns =
> zipWith take ns $   -- Select just the indicated prefix of
each element
> init $  -- Skip the last (empty) element
> scanl (flip drop) xs $  -- Cumulatively remove prefixes of
indicated length
> ns

> The buildPartition contains too many "blocks".
> And I have read code with even more "blocks" in one line.
> 
> It may not be a problem for a "seasoned" Haskell programmer, but when 
> you write some code, you should never forget that your code will be read 
> by programmers that can not be at your same level.

Not if I can help it.

More seriously, beginner code belongs in the first two-three chapters of
Haskell programming textbooks, not anywhere else.  It's like putting Fun
with Dick & Jane-speak in an adult novel.[1]

> I think that many Haskell programmers forget this detail, and IMHO this 
> is wrong.
> 
> > Haskell provides the ability to abstract code beyond what many other 
> > programming systems allow.  This abstraction gives you the ability to 
> > express things much more tersely.  This makes the code a lot harder to 
> > read for people who are not familiar with the abstractions being used.  
> 
> The problem is that I have still problems at reading and understanding 
> code that is too much terse...
> Because I have to assemble in my mind each block, and if there are too 
> many blocks I have problems.

jcc

[1] Well, not that bad.  Beginner-level code is useful for teaching the
basics of the language; Fun with Dick & Jane is child abuse.


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Manlio Perillo

Jake McArthur ha scritto:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Manlio Perillo wrote:
| These friends are very interested in Haskell, but it seems that the main
| reason why they don't start to seriously learning it, is that when they
| start reading some code, they feel the "Perl syndrome".
|
| That is, code written to be "too smart", and that end up being totally
| illegible by Haskell novice.
|
| I too have this feeling, from time to time.

I used to think this as well, but have since changed my mind about most
cases. 


The same for me.

> [...]

All these factors combined just means that you have to concentrate
just as hard to understand one line of Haskell as you might 10 or 20
lines of other languages. There is 10 or 20 times the amount of 
information.




This is right.
The problem is that often (IMHO) a function definition can be rewritten 
so that it is much more readable.


As an example, with the takeList function I posted.

In other cases, you can just break long lines, introducing intermediate 
functions that have a descriptive name *and* a type definition.


Doing this is an art, but a coding style for Haskell should try to 
document this.


> [...]


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


  1   2   >