Re: [Haskell-cafe] constant functions

2006-12-29 Thread ajb
G'day all. Quoting Matthew Brecknell [EMAIL PROTECTED]: Yes. Function application (-) is right-associative in a type expression. What about a value expression? f a b === (f a) b Looks like an inconsistency? Not if you think about it. :-) And if you don't want to think about it, this

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Donald Bruce Stewart
pphetra: I would like to write a program that can do something like this. ;; lisp syntax * (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5) I end up like this. data Store a = E a | S [Store a] deriving (Show) flat :: [Store a] - [a] flat [] = [] flat ((E x):xs) = [x] ++

Re: [Haskell-cafe] constant functions

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 03:36:45AM -0500, [EMAIL PROTECTED] wrote: And if you don't want to think about it, this should make everything clear: f :: A - (B - (C - D)) f a :: B - (C - D) (f a) b :: C - D ((f a) b) c :: d Nice illustration. It's as if the letters jumped over

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 07:58:54PM +1100, Donald Bruce Stewart wrote: Since this data type: data Store a = E a | S [Store a] deriving (Show) Is isomorphic to the normal Data.Tree type anyway, so we'll use that: It's a bit different - store has labels only in its leaves.

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Neil Mitchell
Hi f1 :: [Int] - [[Int]] f1 [] = [] f1 (a:as) = [a] : f1 as f1 is simply a map f3 la lb = let a = head la b = head lb in if sum a = sum b then a : f3 (tail la) lb else

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Stefan O'Rear
On Thu, Dec 28, 2006 at 11:56:58PM -0800, pphetra wrote: data Store a = E a | S [Store a] deriving (Show) flat :: [Store a] - [a] flat [] = [] flat ((E x):xs) = [x] ++ flat xs flat ((S x):xs) = flat x ++ flat xs so *Main flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5]

RE: [Haskell-cafe] Coverage Condition?

2006-12-29 Thread Simon Peyton-Jones
GHC is simply being more conservative. GHC 6.4.2 was straying too close to non-termination, as our paper shows: http://research.microsoft.com/~simonpj/papers/fd-chr Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:haskell-cafe- | [EMAIL PROTECTED] On Behalf Of

Re[2]: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Bulat Ziganshin
Hello Steve, Friday, December 29, 2006, 5:41:40 AM, you wrote: then I can't avoid naming and using an intermediate variable. And that annoys me. The u in process2 is of no more value to me (pardon the pun) as the one in process1, but I am forced to use it simply because the data flow is no

Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Bulat Ziganshin
Hello Grady, Friday, December 29, 2006, 10:12:12 AM, you wrote: not get that in the way I want. I suppose there may have to be some slowdown -- if the compiler specializes every piece of code for every instance of a typeclass it might encounter, it could bloat the executable beyond all

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Conor McBride
Hi pphetra wrote: Compare to a Lisp solution, It 's not looking good. Any suggestion. I'm trying to understand what your issue is here. What's not looking good? I would like to write a program that can do something like this. ;; lisp syntax I suppose, if it were the implementation of

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Paul Moore
On 12/29/06, Conor McBride [EMAIL PROTECTED] wrote: Or is your issue more superficial? Is it just that * (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5) looks shorter than so *Main flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5] Speaking as a relative newbie to Haskell, the thing that

Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 02:06:32PM +, Paul Moore wrote: Speaking as a relative newbie to Haskell, the thing that tripped me up was the fact that you can't have nested lists like the Lisp '(1 (2 (3 4) 5)) example in Haskell, because its type is not well-defined. More precisely: You can't

Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Kirsten Chevalier
On 12/29/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: i propose you to use INLINE pragma: {-# INLINE foo #-} unless your function is recursive. in this case, you should use SPECIALIZE pragma: {-# SPECIALIZE foo :: Double - Double - Double #-} I suggest *not* using these pragmas unless a

Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Greg Buchholz
Steve Schafer wrote: Here's the essence of the problem. If I have this: process1 x y = let u = foo x y; v = bar u; w = baz v in w I can easily rewrite it in point-free style: process1 = baz . bar . foo Not unless you have a much fancier version of

Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Steve Schafer
On Fri, 29 Dec 2006 09:01:37 -0800, you wrote: Steve Schafer wrote: I can easily rewrite it in point-free style: process1 = baz . bar . foo Not unless you have a much fancier version of function composition, like... http://okmij.org/ftp/Haskell/types.html#polyvar-comp Sorry; I

Re: Re[2]: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Steve Schafer
On Fri, 29 Dec 2006 14:23:20 +0300, you wrote: it force you to give names to intermediate results which is considered as good programing style - program becomes more documented. But that would imply that function composition and in-line function definition are also Bad Style. Steve Schafer

Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Tomasz Zielonka
On Tue, Dec 26, 2006 at 09:56:11PM -0500, Steve Schafer wrote: But that isn't quite the case. Each step consumes not only the results of the previous step, but also some combination of the results of prior steps and/or the original inputs. One way to look at this is a directed graph, a sort of

Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Conal Elliott
To get another perspective, let's eliminate some unnecessary naming and see what linear pipelines emerge: process item mediaKind mediaSize language = let (numberedQuestions,questionCategories) = numberQuestions pagemaster $ stripUndisplayedQuestions mediaKind $

Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Greg Buchholz
Conal Elliott wrote: Warning: I haven't tried to type-check and may have made a clerical error. Since questionCategories isn't used, use fst eliminate another let. Then, for my personal preference, and just to mix things up, switch to where style: process item mediaKind mediaSize language

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Neil Mitchell
Hi Quan I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ? map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as box The final f3 clause can be made a bit neater: f3

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread David House
Sorry to Neil for multiple copies. On 29/12/06, Neil Mitchell [EMAIL PROTECTED] wrote: I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ? map (:[]), :[] takes a single element and puts it into a list. Some

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Bryan Burgers
I am not sure how to express f1 with map? how do I say (lambda (ls) (map (lambda (x) (list x)) ls)) in Haskell? map ([]) ? map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as box Another way to express f1 with map is: f1 xs = map (\x -

Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Grady Lemoine
I've performed some experiments in GHCi, and it looks like even for a simple function (+) (which should be the worst case, since if the computation is simple, any extra time required to dispatch the call will show up more strongly in comparison) it doesn't really matter. I get essentially the

[Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread apfelmus
I assume that your proper goal is not to structure pipeline processes in full generality, but to simplify the current one at hand. No, I'm looking for full generality. ;) I have dozens of these kinds of quasi-pipelines, all similar in overall appearance, but different in detail. Ah, the

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Quan Ta
On 12/29/06, Neil Mitchell [EMAIL PROTECTED] wrote: map (:[]), :[] takes a single element and puts it into a list. Some people refer to this as box The final f3 clause can be made a bit neater: f3 la@(a:as) lb@(b:bs) | sum a = sum b = a : f3 as lb |

Re: [Haskell-cafe] constant functions

2006-12-29 Thread David House
On 29/12/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: And if you don't want to think about it, this should make everything clear: My additions displayed below: f :: A - B - C - D f :: A - (B - (C - D)) By right-associativity of f. f a :: B - (C - D) (f a) b :: C - D ((f

Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Lennart Augustsson
Before you start adding pragmas, try compiling with -O, it does a lot of the specialization automatically. -- Lennart On Dec 29, 2006, at 15:00 , Grady Lemoine wrote: I've performed some experiments in GHCi, and it looks like even for a simple function (+) (which should be the worst

[Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread Paul Moore
I'm thinking around the design of a couple of things, and am hitting an issue which I know how I would solve in Python, but I'm not sure what a good idiomatic Haskell approach would be. The problem is that I am trying to write a function which takes a rather large number of arguments, many of

Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread Neil Mitchell
Hi Paul, To make things concrete, the example I'm really thinking of is a send an email function, which would take a subject, a body, a list of recipients, optional lists of cc and bcc recipients, an optional mailserver (default localhost), an optional port (default 25), and possibly optional

Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread David House
On 29/12/06, Paul Moore [EMAIL PROTECTED] wrote: I looked at wxHaskell for inspiration - its approach (button f [text := Quit, on command := close f]) looks quite readable, but slightly unusual (to me) for Haskell. It also seems fairly complex to implement (ie, my head hurt when I tried to

Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread David House
On 29/12/06, Paul Moore [EMAIL PROTECTED] wrote: I looked at wxHaskell for inspiration - its approach (button f [text := Quit, on command := close f]) looks quite readable, but slightly unusual (to me) for Haskell. It also seems fairly complex to implement (ie, my head hurt when I tried to

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread jeff p
Hello, breakUp s | L.null s = [] | otherwise = h:(breakUp r) where (h,r) = L.splitAt 72 s Running this on the 2G file blows up the stack pretty quickly, taking the first 1 million records (there are 20M of them) with a big stack parameter gives about 25%

Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Udo Stenzel
Steve Schafer wrote: Here's the essence of the problem. If I have this: process1 x y = let u = foo x y; v = bar u; w = baz v in w I can easily rewrite it in point-free style: process1 = baz . bar . foo That should have been process1 = (.) (baz . bar) . foo

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Stefan O'Rear
On Fri, Dec 29, 2006 at 04:56:34PM -0800, Ranjan Bagchi wrote: I'm loading a big file (~2G), again, with 72-byte C structs. I've done pretty well [thanks to everyone] interpreting the fields, but I'm finding the traversal of the file to be pretty inefficient. breakUp s | L.null s

[Haskell-cafe] Newbie question

2006-12-29 Thread Pieter Laeremans
Hi, I'm reading the Haskell school of expression by Paul Hudok. Great book. However I would like some feedback about a solution to an exercise The problem is quite simple : define f1 and f2 (using higher order functions ) such that f1 (f2 (*) [1..4]) 5 = [5,10,15,20] I have come up with the

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Matthew Brecknell
breakUp s | L.null s = [] | otherwise = h:(breakUp r) where (h,r) = L.splitAt 72 s Running this on the 2G file blows up the stack pretty quickly, taking the first 1 million records (there are 20M of them) with a big stack parameter gives about 25%

Re: [Haskell-cafe] Newbie question

2006-12-29 Thread Bernie Pope
On 30/12/2006, at 1:33 PM, Pieter Laeremans wrote: Hi, I'm reading the Haskell school of expression by Paul Hudok. Great book. Hudak. And I concur, a great book. However I would like some feedback about a solution to an exercise The problem is quite simple : define f1 and f2 (using

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Bernie Pope
On 30/12/2006, at 1:32 PM, Matthew Brecknell wrote: In my (limited) Haskell experience, I was continually being surprised by inexplicable stack blowouts until I spent a little time doing some focussed experiments, mainly involving folds over large lists. If you haven't done that, I would

Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword argumentsto functions

2006-12-29 Thread Brian Hulley
Paul Moore wrote: I'm thinking around the design of a couple of things, and am hitting an issue which I know how I would solve in Python, but I'm not sure what a good idiomatic Haskell approach would be. The problem is that I am trying to write a function which takes a rather large number of

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Ranjan Bagchi
On Dec 29, 2006, at 6:32 PM, Matthew Brecknell wrote: breakUp s | L.null s = [] | otherwise = h:(breakUp r) where (h,r) = L.splitAt 72 s Running this on the 2G file blows up the stack pretty quickly, taking the first 1 million records (there are 20M of them)

[Haskell-cafe] Literate Haskell source files. How do I turn them into something I can read?

2006-12-29 Thread Michael T. Richter
I'm trying to wrap my mind around the darcs source code as a preliminary to looking into GHC's guts. All of darcs is written as .lhs files which have bizarre mark-up in them which distracts me from the actual Haskell source I'm trying to figure out and get used to. Apparently the GHC compiler

Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Cale Gibbard
On 30/12/06, Ranjan Bagchi [EMAIL PROTECTED] wrote: I guess the consumer's really important (Didn't even occur to me, I was concentrating on how I was generating the list). I was trying to de-lazy the list, I did the following: bs = [...] recs' = (take 100) breakUp bs recs = foldr seq recs'

Re: [Haskell-cafe] Literate Haskell source files. How do I turn them into something I can read?

2006-12-29 Thread Cale Gibbard
On 30/12/06, Michael T. Richter [EMAIL PROTECTED] wrote: I'm trying to wrap my mind around the darcs source code as a preliminary to looking into GHC's guts. All of darcs is written as .lhs files which have bizarre mark-up in them which distracts me from the actual Haskell source I'm trying