Re: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-25 Thread Peter Verswyvelen
Thanks Paul Paul for the answers. I'll certainly read the paper Paul Liu reported. I just deleted 100 lines of text which explained my problem in more detail, and while I was explaining it, I answered it myself. Typical. I thought the lambda function that memo1 returns would be called over

Re: [Haskell-cafe] PROPOSAL: New efficient Unicode string library.

2007-09-25 Thread Vitaliy Akimov
Hi, thanks for proposal, Why questions connected with converting are considered only? The library i18n should give a number of other services such as normalization, comparison, sorting, etc. Furthermore it's not so easy to keep such library up to date. Why simply do not make a bindings to IBM ICU

Re: [Haskell-cafe] C's fmod in Haskell

2007-09-25 Thread Henning Thielemann
On Tue, 25 Sep 2007, ok wrote: On 25 Sep 2007, at 10:55 am, Thomas Conway wrote: This old chestnut! It's a common problem in practice. As I recall, the behaviour of C's % operator allows implementations to yield either behaviour. I just checked ISO 9899:1999 which defines fmod. It specifies

Re: [Haskell-cafe] Template Haskell newbie questions

2007-09-25 Thread Hugo Pacheco
The sel function was just the simpliest example I remembered of. Yes, I would need to generate code at runtime according since the generated code would depend on the function arguments, but have already guessed It wouldn't be possible. Anyway, thanks for the clarification, hugo

[Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
While using Haskell, I often find myself writing convoluted constructions such as this: show_system = unlines . zipWith (\l ms - Eq ++ show l ++ : ++ (concat $ intersperse + $ zipWith (\n x - x ++ x ++ show n) [1..] (init ms)) ++ = ++ last ms )

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Neil Mitchell
Hi show_system = unlines . zipWith (\l ms - Eq ++ show l ++ : ++ (concat $ intersperse + $ zipWith (\n x - x ++ x ++ show n) [1..] (init ms)) ++ = ++ last ms ) [1..] . map (map (take 8 . show)) And people complain that

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Neil Mitchell wrote: Hi And people complain that *Perl* is bad? This function is quite obviously absurd. I mean, it works, but can *you* figure out what it does without running it? No. Can you say what the intention of this code is? Maybe a few examples? The type signature? That way

Re: [Haskell-cafe] bindings to the xmms_remote API, GList and something more

2007-09-25 Thread Andrea Rossato
On Mon, Sep 24, 2007 at 11:00:00AM +0100, Jules Bean wrote: I saw it. In total, four messages from you in this thread. I'm really sorry about that, but it was due to a problem and a misunderstanding with the administrator of my STMP server: at first it appeared the server was dropping my mail,

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Dougal Stanton
On 25/09/2007, Andrew Coppin [EMAIL PROTECTED] wrote: Type signature is show_system :: [[Double]] - String It takes a matrix representing a system of equations, and pretty prints it. Unfortunately, doing complex formatting like that is... well, complex. The input is quite simple (it's a

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Neil Mitchell
Hi complex. The input is quite simple (it's a bunch of numbers), the output is quite simple (it's a neatly formatted string), but the process in the middle is... a mess. I'd like to find a more readable way of doing stuff like this. It's not just this specific function; any general hints

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:31:34AM +0100, Dougal Stanton wrote: On 25/09/2007, Andrew Coppin [EMAIL PROTECTED] wrote: In this instance I would suggest: (1) Text.Printf (2) Pull out some of those things into separate functions with where/let clauses. If it's a matrix you should probably

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Neil Mitchell wrote: Hi A nice auxiliary would help: showEqn :: Int - [Double] - String showEqn i vs = ... where (add,ans) = (init vs, last vs) Then you can half the complexity. There are probably a few useful functions that aren't in the standard libraries (consperse, joinWith

Re: [Haskell-cafe] Shouldnt this be lazy too?

2007-09-25 Thread Henning Thielemann
On Mon, 24 Sep 2007, Neil Mitchell wrote: Hi In this world, use length (take 11 [1..]) 10... not (null (drop 10 [1..])) is surely faster (not tested...) Faster? There might be a few microseconds in it. Clearer? Possibly... ;-) lengthNat [1..] 10 Couldn't be clearer, and can be made

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Dougal Stanton wrote: In this instance I would suggest: (1) Text.Printf You've got to be kidding... I went to all the trouble of learning a scary logic programming language [sic] just to avoid that damned printf() function! :-/ (2) Pull out some of those things into separate functions

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 5:48 , Andrew Coppin wrote: Dougal Stanton wrote: In this instance I would suggest: (1) Text.Printf You've got to be kidding... I went to all the trouble of learning a scary logic programming language [sic] just to avoid that damned printf() function! :-/ Enh.

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Tristan Allwood wrote: Just to follow those sentiments, the version I knocked out quickly looked like: (It's not quite the same as the original function, I think I'm lacking a map (map (take 8)) on the first line). showSystems :: Show a = [[a]] - String showSystems = unlines . zipWith

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Brandon S. Allbery KF8NH wrote: On Sep 25, 2007, at 5:48 , Andrew Coppin wrote: You've got to be kidding... I went to all the trouble of learning a scary logic programming language [sic] just to avoid that damned printf() function! :-/ Enh. :) On the other hand, I do wonder that nobody's

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: BTW, one *extremely* common function that I've never seen mentioned anywhere is this one: map2 :: (a - b) - [[a]] - [[b]] map2 f = map (map f) Because someone would have to think of a name for it, when (map . map) is likely to be

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 5:56 , Andrew Coppin wrote: More seriously, I have no idea how you'd implement this in Haskell. Presumably the standard show instance for Int, Double, etc. is in native C? You could probably reimplement it in Haskell for the integer case, but not for floating-point...

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin
Aaron Denney wrote: On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: BTW, one *extremely* common function that I've never seen mentioned anywhere is this one: map2 :: (a - b) - [[a]] - [[b]] map2 f = map (map f) Because someone would have to think of a name for it, when

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Brandon S. Allbery KF8NH wrote: On Sep 25, 2007, at 5:56 , Andrew Coppin wrote: More seriously, I have no idea how you'd implement this in Haskell. Presumably the standard show instance for Int, Double, etc. is in native C? You could probably reimplement it in Haskell for the integer case,

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 5:45 , Andrew Coppin wrote: Still, since Haskell seems to be devoid of any more advanced way of formatting numbers beyond low-level character jiggling... Text.Printf.printf is your friend. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:53:55AM +0100, Andrew Coppin wrote: Tristan Allwood wrote: Just to follow those sentiments, the version I knocked out quickly looked like: (It's not quite the same as the original function, I think I'm lacking a map (map (take 8)) on the first line). showSystems

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: Aaron Denney wrote: On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: BTW, one *extremely* common function that I've never seen mentioned anywhere is this one: map2 :: (a - b) - [[a]] - [[b]] map2 f = map (map f)

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin
Aaron Denney wrote: On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: OK, *now* I'm puzzled... Why does map . map type-check? (map . map) = (.) map map (.) :: (a - b) - (b - c) - a - c = (a - b) - (b - c) - (a - c) The first two arguments of (.) are 1-argument functions.

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: I just found it rather surprising. Every time *I* try to compose with functions of more than 1 argument, the type checker complains. Specifically, suppose you have foo = f3 . f2 . f1 Assuming those are all 1-argument functions, it

Re: [Haskell] Re: [Haskell-cafe] PROPOSAL: Rename [EMAIL PROTECTED] haskell-announce@

2007-09-25 Thread Andrzej Jaworski
(...) I subscribe to haskell so as not to miss anything important, and when something I'm interested in moves to haskell-cafe, (...) Wrong assumption. Even if you know the author it makes more sense to wait and see how others respond to his newest input. This means that you should check up

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin
Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: I just found it rather surprising. Every time *I* try to compose with functions of more than 1 argument, the type checker complains. There is no function that takes more than one argument in Haskell. ;-) map _could_ be

[Haskell-cafe] representing differencial equations in haskell

2007-09-25 Thread Thomas Girod
Hi there. Let's say I have mathematical model composed of several differential equations, such as : di/dt = cos(i) dc/dt = alpha * (i(t) - c(t)) (sorry my maths are really bad, but I hope you get the point) I would like to approximate the evolution of such a system iteratively. How would you

Re[2]: [Haskell-cafe] Template Haskell newbie questions

2007-09-25 Thread Bulat Ziganshin
Hello Hugo, Tuesday, September 25, 2007, 1:05:28 PM, you wrote: Yes, I would need to generate code at runtime according since the you have selected improper instrument for it. look at GHC-as-a-lbrary and hs-plugins by Donald Stewart -- Best regards, Bulat

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: Forget PrintfType - I can't even understand the haddoc page yet! (printf performs I/O, yet it is outside the I/O monad. It seems to accept an arbitrary number of arguments, which is obviously impossible. It's *almost* as

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread jerzy . karczmarczuk
Andrew Coppin writes: ...I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, zipWith (*) expects two arguments, and yet sum . zipWith (*) fails to type-check. You just instead write \xs ys - sum $ zipWith(*) xs ys

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin
Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, zipWith (*) expects two arguments, and yet sum . zipWith (*) fails to type-check. You

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: printf don't always perform IO : if you ask it for a String it will happily turn into sprintf for you, if you use it in the IO Monad, it will indeed perform IO, but there's nothing fundamentally IO bound in printf logic.

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Dominic Steinitz
Andrew Coppin andrewcoppin at btinternet.com writes: I just found it rather surprising. Every time *I* try to compose with functions of more than 1 argument, the type checker complains. Specifically, suppose you have foo = f3 . f2 . f1 Assuming those are all 1-argument functions, it

Re: [Haskell-cafe] RE: simple function: stack overflow in hugsvsnonein ghc

2007-09-25 Thread Claus Reinke
return (replicate 100 'a') = \x-print $ spant (const True) x ERROR - Garbage collection fails to reclaim sufficient space i.e. as the function unfold, the thunk representing the second term builds up on the heap. (not sure why it works for an infinite list, hugs must drop the reference to

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Miguel Mitrofanov
How can one function have more than one type signature? It's called polymorphism. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Claus Reinke
This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, zipWith (*) expects two arguments, and yet sum . zipWith (*) fails to type-check. You just instead write \xs ys - sum $ zipWith(*) xs ys which works as

Re: [Haskell-cafe] representing differencial equations in haskell

2007-09-25 Thread Antoine Latter
I don't see anything in hackage off the top of my head. If it's a set of DEs like that, Runge-Kutta is a good place to start if you want to code your own integrator: http://en.wikipedia.org/wiki/Runge-Kutta#The_classical_fourth-order_Runge.E2.80.93Kutta_method But if it were me I would just use

Re: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-25 Thread Paul Hudak
Peter Verswyvelen wrote: I thought the lambda function that memo1 returns would be called over and over again, and instead of reevaluating the stream from the beginning, it would just return the stream since it is in the cache, but actually it just gets called twice in recursive situations:

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Martin Lütke
Dominic Steinitz schrieb: Andrew Coppin andrewcoppin at btinternet.com writes: I just found it rather surprising. Every time *I* try to compose with functions of more than 1 argument, the type checker complains. Specifically, suppose you have foo = f3 . f2 . f1 Assuming those are all

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 6:55 , Andrew Coppin wrote: This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. You can, it just requires more juggling. Play around with lambdabot's @pl for a bit. -- brandon s. allbery

Re: [Haskell-cafe] representing differencial equations in haskell

2007-09-25 Thread Henning Thielemann
On Tue, 25 Sep 2007, Thomas Girod wrote: Let's say I have mathematical model composed of several differential equations, such as : di/dt = cos(i) dc/dt = alpha * (i(t) - c(t)) (sorry my maths are really bad, but I hope you get the point) I would like to approximate the evolution of such a

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Andrew Coppin
Martin Lütke wrote: Dominic Steinitz schrieb: Look at the type of (.).(.) which should tell you how to compose functions with more than one variable. Mind you, I don't think it improves readability. Dominic. Interesting function. It got a sibling: (.)(.) :: (a1 - b - c) - a1 - (a -

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 7:25 , Andrew Coppin wrote: Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: printf don't always perform IO : if you ask it for a String it will happily turn into sprintf for you, if you use it in the IO Monad, it will indeed perform IO, but there's

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH
On Sep 25, 2007, at 7:24 , Andrew Coppin wrote: which *just happens* to be what we want. But in the general case where you want f3 (f2 (f1 x y z)) there's nothing you can do except leave point-free. You mean leave point-ful. And the point-free version of that is (((f3 . f2) .) .) . f1

Re: Re[2]: [Haskell-cafe] Template Haskell newbie questions

2007-09-25 Thread Hugo Pacheco
hs-plugins does look promising. thanks for the hint, hugo ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] representing differencial equations in haskell

2007-09-25 Thread Paul L
Here is a minimal answer using Yampa-like Signal Function and Arrow notation. You have to load this using ghci -farrows. import Control.Arrow The differential equation you gave are indeed: i = integral (cos i) + i0 c = integral (alpha * (i - c)) + c0 where i0 and c0 are the initial

Re: [Haskell-cafe] Shouldnt this be lazy too?

2007-09-25 Thread Jules Bean
Vimal wrote: From the wiki: If you write it, you force Haskell to create all list nodes. ... Alright. Now, lets look at the definition again: length [] = 0 length (x:xs) = 1 + length xs We see that the value of *x* isnt needed at all. So, why does GHC allocate so much memory creating all

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 11:40 +0100, Andrew Coppin wrote: Aaron Denney wrote: On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote: OK, *now* I'm puzzled... Why does map . map type-check? (map . map) = (.) map map (.) :: (a - b) - (b - c) - a - c = (a - b) - (b - c) -

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 12:24 +0100, Andrew Coppin wrote: Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, zipWith (*) expects two

[Haskell-cafe] getting more out of ghci [longish]

2007-09-25 Thread Claus Reinke
== intro no, i'm not talking about using a nice frontend to ghci, with added functionality, although the haskell modes for emacs and vim, and other such gui/ide/editor efforts, are well worth looking into!-) also, i'm not going to talk about the eagerly anticipated ghci debugger. what i am

RE: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-25 Thread Peter Verswyvelen
Hello Paul, Actually the function may be called more than twice -- but each time after the first, it uses the cached value instead of recomputing it. Yes, I got confused, since I first thought that the lambda returned from memo would be called at each frame (aka time sample). I made some

[Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Hi, I'm in the process of designing a little language inspired by Haskell but imperative, and have hit an issue regarding infix syntax which may be of interest also to anyone thinking about future revisions of Haskell or the problem of consistent parameter order in libraries. I'm wondering

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Brian Hulley wrote: I'm wondering if anyone can shed light on the reason why x # y gets desugared to (#) x y and not (#) y x Can anyone think of an example where the current desugaring of infix arguments gives the correct order when the function is used in a postfix application?

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Jonathan Cast
On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote: Brian Hulley wrote: I'm wondering if anyone can shed light on the reason why x # y gets desugared to (#) x y and not (#) y x Can anyone think of an example where the current desugaring of infix arguments

Re[2]: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Bulat Ziganshin
Hello Andrew, Tuesday, September 25, 2007, 5:21:35 PM, you wrote: Interesting function. It got a sibling: (.)(.) :: (a1 - b - c) - a1 - (a - b) - a - c sexy function with sexy type :) -- Best regards, Bulatmailto:[EMAIL PROTECTED]

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Dan Weston
Wise your proposal is. Too long the desugaring I of languages functional not understanding have labored. Anastrophe the rule should be. Working have I been on a language Yoda that these rules implements it aspires to. If the lojban/loglan schism is any precedent, Yoda will split soon enough

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Ryan Ingram
My comments inlined below... On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: let shiftLeftByThree = shiftL' 3 in map shiftLeftByThree [10, 78, 99, 102] let shiftLeftByThree = (`shiftL` 3) in ... Can anyone think of an example where the current desugaring of infix

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Jonathan Cast wrote: On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote: Brian Hulley wrote: I'm wondering if anyone can shed light on the reason why x # y gets desugared to (#) x y and not (#) y x Of course, this is all a consequence of the well-known failure

[Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Evan Klitzke
Has anybody made (or have a link to) a Haskell reference cheat sheet? I'm thinking of a nice LaTeXed PDF in the 1-10 page range (e.g. something like this http://www.tug.org/texshowcase/cheat.pdf) with the basics of the language syntax, the type declarations for the common type classes, the type

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Lennart Augustsson
It's reasonably easy to read. But you could make it more readable. Type signatures, naming the first lambda... On 9/25/07, Andrew Coppin [EMAIL PROTECTED] wrote: While using Haskell, I often find myself writing convoluted constructions such as this: show_system = unlines . zipWith

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Ben
+1 Message: 9 Date: Tue, 25 Sep 2007 13:04:56 -0700 From: Evan Klitzke [EMAIL PROTECTED] Subject: [Haskell-cafe] Haskell Cheat Sheet? To: haskell-cafe@haskell.org Message-ID: [EMAIL PROTECTED] Content-Type: text/plain Has anybody made (or have a link to) a Haskell reference cheat sheet?

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Lennart Augustsson
Text.printf only has one type. But it is a bit involved. Just use it without worrying exactly how it works. :) Like 's ++ printtf %g*x%d x i' On 9/25/07, Andrew Coppin [EMAIL PROTECTED] wrote: Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: printf don't always perform

Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Philippa Cowderoy
On Tue, 25 Sep 2007, Lennart Augustsson wrote: It's reasonably easy to read. But you could make it more readable. Type signatures, naming the first lambda... It might be reasonable to define something like mapMatrix that happens to be map . map, too. Along with at least a type synonym for

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread brad clawsie
On Tue, Sep 25, 2007 at 01:04:56PM -0700, Evan Klitzke wrote: Has anybody made (or have a link to) a Haskell reference cheat sheet? the zvon ref is pretty close: http://www.zvon.org/other/haskell/Outputglobal/index.html in that it includes an overview of operators and common apis nice that

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Dan Piponi
On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: ...I seem to dimly recall that there is a natural language somewhere that also uses it but I can't remember which one. Every permutation of [S,V,O] appears in 'nature': http://en.wikipedia.org/wiki/Word_order. Also, a problem might be that it

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Ryan Ingram wrote: My comments inlined below... On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: let shiftLeftByThree = shiftL' 3 in map shiftLeftByThree [10, 78, 99, 102] let shiftLeftByThree = (`shiftL` 3) in ... Aha! but this is using section syntax which is

[Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Seth Gordon
Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for Computer Scientists_ suitable for self-study? (Do they have problem sets that can be checked by either looking up answers in The Back of the Book, or by trying to compile/run some code that the

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Tim Chevalier
On 9/25/07, Seth Gordon [EMAIL PROTECTED] wrote: Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for Computer Scientists_ suitable for self-study? (Do they have problem sets that can be checked by either looking up answers in The Back of the Book, or

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Philippa Cowderoy
On Tue, 25 Sep 2007, Seth Gordon wrote: Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for Computer Scientists_ suitable for self-study? Basic Category Theory depends on your mindset somewhat. TaPL is great though, and frequently recommended. The

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Andrew Coppin
brad clawsie wrote: nice that it is in html. the pdf thing seems a bit contrived to me. Clearly you've never tried printing hard copies of HTML. ;-) Personally, I think having *both* is a nice idea. You can browse around the HTML, or you can print out hard copies to sit next to your

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Stefan Holdermans
Seth, You asked: Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for Computer Scientists_ suitable for self-study? And Tim answered: Graduate-level textbooks don't have answers in the back of the book, as a rule. In TAPL, some of the questions

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Creighton Hogg
On 9/25/07, Philippa Cowderoy [EMAIL PROTECTED] wrote: On Tue, 25 Sep 2007, Seth Gordon wrote: Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for Computer Scientists_ suitable for self-study? Basic Category Theory depends on your mindset

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Dan Piponi wrote: On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: ..I seem to dimly recall that there is a natural language somewhere that also uses it but I can't remember which one. Every permutation of [S,V,O] appears in 'nature': http://en.wikipedia.org/wiki/Word_order. Thanks

[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Philippa Cowderoy [EMAIL PROTECTED] wrote: On Tue, 25 Sep 2007, Lennart Augustsson wrote: It's reasonably easy to read. But you could make it more readable. Type signatures, naming the first lambda... It might be reasonable to define something like mapMatrix that happens

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Brent Yorgey
On 9/25/07, brad clawsie [EMAIL PROTECTED] wrote: On Tue, Sep 25, 2007 at 01:04:56PM -0700, Evan Klitzke wrote: Has anybody made (or have a link to) a Haskell reference cheat sheet? the zvon ref is pretty close: http://www.zvon.org/other/haskell/Outputglobal/index.html in that it

Re: [Haskell-cafe] C's fmod in Haskell

2007-09-25 Thread ok
[Concerning the fact that fmod(x,y) = -fmod(-x,y)] I wrote: Interesting, perhaps. Surprising, no. fmod() is basically there for the sake of sin(), cos(), and tan() (or any other periodic and either symmetric or antisymmetric function). On 25 Sep 2007, at 8:58 pm, Henning Thielemann wrote:

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Dan Weston
The absolute easiest, clearest, and most entertaining book on Category Theory (which I highly recommend) is: Conceptual Mathematics: A First Introduction to Categories (Paperback) by F. William Lawvere and Stephen Hoel Schanuel, $25 It literally reads like a series of college lectures (called

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Don Stewart
evan: Has anybody made (or have a link to) a Haskell reference cheat sheet? I'm thinking of a nice LaTeXed PDF in the 1-10 page range (e.g. something like this http://www.tug.org/texshowcase/cheat.pdf) with the basics of the language syntax, the type declarations for the common type classes,

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Dan Weston
One suggestion: Section 3.6 defines a function fix: fix :: Eq x = (x - x) - x - x fix f x = if x == x' then x else fix f x' where x' = f x This confusingly differs in both type and meaning from the traditional function Control.Monad.Fix.fix and is not even used elsewhere in the

[Haskell-cafe] Re: Math.Statistics

2007-09-25 Thread ok
There are a number of interesting issues raised by mbeddoe's Math.Statistics. 0. Coding issues. Why use foldr1 (*) instead of product? covm xs = split' (length xs) cs where cs = [ cov a b | a - xs, b - xs] split' n = unfoldr (\y - if null y then Nothing

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Sam Hughes
Brian Hulley wrote: Dan Piponi wrote: On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: .. I don't understand what you mean. For example, with the prefix definition of a function with multiple clauses, the function name at the start of each clause is already lined up since it must appear

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Derek Elkins
On Tue, 2007-09-25 at 12:24 +0100, Andrew Coppin wrote: Chaddaï Fouché wrote: 2007/9/25, Andrew Coppin [EMAIL PROTECTED]: This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, zipWith (*) expects two

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread David Menendez
On 9/25/07, Andrew Coppin [EMAIL PROTECTED] wrote: This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. [...] I can't figure out why map . map works, but sum . zipWith (*) doesn't work. As I say, the only reason I can see is

Re: [Haskell-cafe] PROPOSAL: New efficient Unicode string library.

2007-09-25 Thread Deborah Goldsmith
I'll look over the proposal more carefully when I get time, but the most important issue is to not let the storage type leak into the interface. From an implementation point of view, UTF-16 is the most efficient representation for processing Unicode. It's the native Unicode

Re: [Haskell-cafe] Pierce on type theory and category theory

2007-09-25 Thread Derek Elkins
On Tue, 2007-09-25 at 16:18 -0500, Creighton Hogg wrote: On 9/25/07, Philippa Cowderoy [EMAIL PROTECTED] wrote: On Tue, 25 Sep 2007, Seth Gordon wrote: Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic Category Theory for

[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-25 Thread Aaron Denney
On 2007-09-26, Deborah Goldsmith [EMAIL PROTECTED] wrote: From an implementation point of view, UTF-16 is the most efficient representation for processing Unicode. This depends on the characteristics of the text being processed. Spacewise, English stays 1 byte/char in UTF-8. Most European

Re: [Haskell-cafe] Haskell Cheat Sheet?

2007-09-25 Thread Devin Mullins
On Tue, Sep 25, 2007 at 05:19:20PM -0700, Dan Weston wrote: which is undefined (and seems to be missing an argument), when invariably its type is in practice restricted to: fix :: ((a - b) - (a - b)) - (a - b) Oh, come on! I use fibs = fix $ (0:) . (1:) . uncurry ($) . (zipWith (+) tail)

Re: [Haskell-cafe] PROPOSAL: Rename haskell@ to haskell-announce@

2007-09-25 Thread Devin Mullins
On Mon, Sep 24, 2007 at 07:39:32PM +0100, Andrzej Jaworski wrote: I can see only two options available to us right now to preserve readability in the fast growing Haskell community: divide haskell@ into more specific lists (haskell-cafe should preserve its right to long threads !!!) or ascribe

[Haskell-cafe] Re: Haskell Cheat Sheet?

2007-09-25 Thread ChrisK
I disagree -- see below Dan Weston wrote: I suggest that it be removed and the real Control.Monad.Fix.fix function be defined in its own section, with an side-by-side comparison with a named recursive function. This would be useful because the type fix :: (a - a) - a is highly

Re: [Haskell-cafe] Composition Operator

2007-09-25 Thread Devin Mullins
On Tue, Sep 25, 2007 at 12:08:34AM -0500, Derek Elkins wrote: () is terminal, not initial. There exists a unique function to it (ignoring bottoms) from anything, namely, const (). A point of A categorically, is just a function from the terminal object to A, () - A. For the notion of pointed

Re: [Haskell-cafe] PROPOSAL: Rename haskell@ to haskell-announce@

2007-09-25 Thread nornagon
On 26/09/2007, Devin Mullins [EMAIL PROTECTED] wrote: Yes, I suppose the above doesn't require a new protocol -- mailing-list + funny-ass MUA would do. ITYM funny ass-MUA. Sorry, I'll go back to lurking. . -- Jeremy ___ Haskell-Cafe mailing list