Re: [Haskell-cafe] Is this haskelly enough?
On 18 Jul 2007, at 8:52 pm, Bjorn Bringert wrote: Well, the original poster wanted advice on how to improve his Haskell style, not algorithmic complexity. I think that the appropriate response to that is to show different ways to write the same program in idiomatic Haskell. (a) I gave some of that; I wrote my solution before seeing anyone else's. (b) I find it hard to imagine a state of mind in which algorithmic complexity is seen as irrelevant to style. I am reminded of the bad old days when Quintus had customers who were infuriated because writing an exponential-time algorithm in a few lines of Prolog didn't mean it ran fast on large examples. Their code was short, so it HAD to be good code, which meant the slowness had to be our fault. Not so! (c) The key point in my posting was the reference to Gries' paper, in which he derives an imperative program in Dijkstra's notation USING A CALCULATIONAL STYLE, very like the bananas-lenses-and- barbed wire stuff popular in some parts of the functional community. /Björn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Stream processors as arrows
Miguel Mitrofanov, on 9 July [1]: > I'm trying to do Exercise 2.5.2 from John Hughes's "Programming with > Arrows". [...] Sorry for the delayed reply. I've only just started learning about arrow programming, and since no-one else has replied to you, here is what I've discovered so far... I think there are some problems with your implementation of "first". Here are some examples which don't behave the way I would expect: > delaySP = foldr Out returnA > > skipSP n = if n > 0 > then Inp (\_ -> skipSP (n-1)) > else returnA *Main> runSP (delaySP [-3,-2,-1] &&& returnA) [0..9] [(-3,0),(-2,1),(-1,2),(2,3),(3,4),(4,5),(5,6),(6,7),(7,8),(8,9)] I would expect 0 and 1 to be present in the sequence in the first component. *Main> runSP (skipSP 2 &&& returnA) [0..9] [(2,2),(3,3),(4,4),(5,5),(6,6),(7,7),(8,8),(9,9)] The second component seems to have been skipped as well as the first. The "tricky point" referred to in the tutorial exercise [2] seems to be that the two components running through first will inevitably get out of sync, possibly by an arbitrary number of elements. My first attempt was to use explicit queues: > import Data.Sequence > > data SP a b = Get (a -> SP a b) | Put b (SP a b) > > instance Arrow SP where > arr f = Get $ \x -> Put (f x) (arr f) > > Put y f >>> Get g = f >>> g y > Get f >>> Get g = Get (\x -> f x >>> Get g) > f >>> Put z g = Put z (f >>> g) > > first = step empty empty where > -- Invariant: at least one of [qfst,qsnd] must be empty. > step qfst qsnd (Put y sp) = case viewl qsnd of > EmptyL -> Get $ \(x,z) -> Put (y,z) (step (qfst |> x) qsnd sp) > z :< zs -> Put (y,z) (step qfst zs sp) > step qfst qsnd (Get fsp) = case viewl qfst of > EmptyL -> Get $ \(x,z) -> step qfst (qsnd |> z) (fsp x) > x :< xs -> step xs qsnd (fsp x) > > instance ArrowChoice SP where > left (Get fsp) = Get $ either (left . fsp) (\z -> Put (Right z) (left $ Get > fsp)) > left (Put y sp) = Put (Left y) (left sp) This produces something reasonably sensible for the examples above: *Main> runSP (delaySP [-3,-2,-1] &&& returnA) [0..9] [(-3,0),(-2,1),(-1,2),(0,3),(1,4),(2,5),(3,6),(4,7),(5,8),(6,9)] *Main> runSP (skipSP 2 &&& returnA) [0..9] [(2,0),(3,1),(4,2),(5,3),(6,4),(7,5),(8,6),(9,7)] However, if you think about it more closely, it is still not satisfactory: *Main> runSP (Put 42 returnA) [] [42] *Main> runSP (first (Put 42 returnA)) [] [] In the second case, I think the answer should really be [(42,_|_)]. A more severe problem is that because both runSP and the arrow combinators pattern-match on the SP constructors, it is impossible to use recursive arrow structures with this implementation of the SP arrow: > factorial :: (Num a, ArrowChoice arr) => arr a a > factorial = arr (choose (==0)) >>> > arr (const 1) ||| (returnA &&& (arr (flip (-) 1) >>> factorial) >>> arr > (uncurry (*))) > > choose c x > | c x = Left x > | otherwise = Right x *Main> factorial 4 24 *Main> runSP factorial [3,4] *** Exception: stack overflow Same goes for mapA given in the tutorial [2]. This problem also prevented me from defining an instance of ArrowLoop. So, I don't think explicit queues are the answer. I suspect one needs to use the circular/lazy programming technique described in section 2.3 [2] to implement the basic Arrow combinators, as well as ArrowLoop. With some luck, that might solve both of the above problems. [1]http://www.haskell.org/pipermail/haskell-cafe/2007-July/028180.html [2]http://www.cs.chalmers.se/~rjmh/afp-arrows.pdf ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] historical question about Haskell and Haskell Curry
On 7/18/07, Michael Vanier <[EMAIL PROTECTED]> wrote: We always say that Haskell is named for Haskell Curry because his work provided the logical/computational foundations for the language. How exactly is this the case? Specifically, does anyone claim that Curry's combinatorial logic is more relevant to the theoretical foundations of Haskell than e.g. Church's lambda calculus? If not, why isn't Haskell called "Alonzo"? ;-) I'd guess it's because Haskell is a language that provides type inference, and Curry's logic is implicitly typed, whereas Church's typed lambda calculus is typed explicitly. (Why no Haskell compilers' intermediate languages are named "Alonzo" is left as an exercise for the reader :-) Cheers, Tim -- Tim Chevalier* catamorphism.org *Often in error, never in doubt "Base eight is just like base ten, really... if you're missing two fingers." -- Tom Lehrer ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] gui libs? no [...] - bug report
Hi Claus Ising ghc-6.6 and Opera 9.20 i thought that everything would work until I tried the page in Firefox 2.0.0.1 Opera: Those maroon rectangles in all four corners appear, alse the text x/y: ... is shown when clicking. But the drawing doesn't appear, does'n show any errors within the Error Console either. In Firefox (2.0.0.3) Firebug does show the JS error: evt has no properties clicked()start (line 63) onclick(click clientX=0, clientY=0)start (line 1) addLabel(evt.clientX,evt.clientY) But the drawing ( |_| rotating clockwise) appears. Clicking has no effect If you don't know it yet mootools is a really nice JS framework providing transition suppert etc. Perhaps this might be useful somehow as well. Marc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] historical question about Haskell and Haskell Curry
We always say that Haskell is named for Haskell Curry because his work provided the logical/computational foundations for the language. How exactly is this the case? Specifically, does anyone claim that Curry's combinatorial logic is more relevant to the theoretical foundations of Haskell than e.g. Church's lambda calculus? If not, why isn't Haskell called "Alonzo"? ;-) Mike ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)
On Thu, 2007-07-19 at 00:12 +0100, Claus Reinke wrote: > gui libs are wonderful, but haskell sometimes has too few > and sometimes has too many. and those we have do not > work with every haskell implementation. and when they do > work (usually with ghc, these days), they need to be rebuilt > whenever ghc is updated, even if the gui lib hasn't changed > at all (one gui lib binding per ghc version). still, we put up > with that when we need all those gui lib features, because > we have to, and we're happy to live in one of those periods > when there are such bindings to full-featured gui libraries. You're right, that's annoying. It's particularly a problem for Windows GHC users who expect pre-built binaries, since GHC currently requires all libs to be rebuilt with each new minor GHC version. It's particularly annoying for GUI libs which are non-trivial to build from source (due to needing so many C header files and such) and so there is always a lag between when GHC gets updated and when someone (me) gets round to making a new binary build for Windows. Our hope is that we can get Gtk2Hs working with Yhc some day. That'd be interesting because it shouldn't have the same versionitis issues and the same compiled GUI program should run unaltered on Windows, Linux or OSX (and several others). > but what about quick and dirty/cheap and cheerful graphics? > over the years, HGL/SOEGraphics has served as a persistent > reminder that things keep changing, and that when they do, > something breaks. even if all people want to do is draw some > simple graphics, or animations. There's a SOEGraphics implementation with Gtk2Hs, but then of course see problem 1. :-) > i don't have a solution, but i'd like to throw another alternative > into the ring, based on the ongoing fight between web browsers > and other guis for world dominance.. [..] Sounds fun! :-) Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)
gui libs are wonderful, but haskell sometimes has too few and sometimes has too many. and those we have do not work with every haskell implementation. and when they do work (usually with ghc, these days), they need to be rebuilt whenever ghc is updated, even if the gui lib hasn't changed at all (one gui lib binding per ghc version). still, we put up with that when we need all those gui lib features, because we have to, and we're happy to live in one of those periods when there are such bindings to full-featured gui libraries. but what about quick and dirty/cheap and cheerful graphics? over the years, HGL/SOEGraphics has served as a persistent reminder that things keep changing, and that when they do, something breaks. even if all people want to do is draw some simple graphics, or animations. i don't have a solution, but i'd like to throw another alternative into the ring, based on the ongoing fight between web browsers and other guis for world dominance.. the idea is well known: build your app as a server, and put an ajax-based gui in front of it, even if server and browser run on the same machine. attached is a silly quick&dirty demo of some of the relevant concepts, including a fake haskell http-server, an html/canvas/httprequest/ javascript-based gui, and some simple graphics/buttons/text. tested on windows, with opera 9.01 and ghc 6.6.1. it will probably not work with other browsers, but it should work with opera on other platforms, or with other haskell implementations supporting Network. (you might have to hardcode the file name at the top of the source if not using ghc; to make it work with other browsers, you need workarounds for standard browser incompatibilities) to run, load Canvas.hs into ghci and call main. then start up opera, and visit 'http://localhost:8000/start' (to change that port number, change both 'main' in the haskell source, and 'get' in the html source). that should yield an html page with further instructions. have a look, and please let me know if it works on your os/ haskell implementation, and what you think about the idea. i won't do it myself, but perhaps someone could code up SOEGraphics based on this?-) and if not, this might still help out some of you who need simple low-overhead guis (things can get hairy very quickly if you need more than simple guis)? some of you might have to fight through implementing browser- based guis for their day jobs anyhow, but may want to put haskell behind those guis; or you might find haskell prototyping an easier sell, if the gui can be reused for the "real" implementation.. claus further reading/download: Opera browser (windows, macos, solaris, linux, ..) http://www.opera.com/download/ html 5 -- working draft, june 2007 (3.14.11 canvas element) http://www.whatwg.org/specs/web-apps/current-work/#the-canvas canvas tutorial http://developer.mozilla.org/en/docs/Canvas_tutorial http://developer.mozilla.org/en/docs/Drawing_Graphics_with_Canvas Canvas.hs Description: Binary data ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)
On 18/07/07, J. Garrett Morris <[EMAIL PROTECTED]> wrote: You're partway there - concatMap is flip (>>=), so you have the xs >>= (\x -> ) part. Ah, yes! I read about this equivalence in one of the other threads today but it didn't make any connection. Doh! I think I will have to, sooner or later, become more versed in the subtle ways of non-IO monads. They seem to be capable of some seriously tricksy shenanigans. In other news, I worked out a few minutes ago while walking home that the whole keepOneDiff function (used in my program above) is incredibly convoluted, to the point of Heath Robinson contortions. To be clear, I had: keepOneDiff = map snd . filter (\x -> (fst x) < 2) . map (difference &&& id) Where I could have just done this... keepOneDiff = filter ((< 2) . difference) Sometimes I am astounded at my own lack of vision. :-O Clearly, today has not been a good day. Cheers for all your help folks, Dougal. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor
On 23:25 Wed 18 Jul , Andreas Marth wrote: > Thanks for again pointing out that I didn't want another way to get the > information, but I have to defend Simon. > [...] > 1) make the wiki search function return all documents containig the search > term (who can do that?) > 2) consider creating a new wiki topic "Problems and solutions working with > haskell" On a related note, I have found that the Haskell wiki has some really great articles on topics, but there's often no clear path to get to them. I would argue that improving search isn't the right solution to this (search should be a last resort, IMHO). I've often thought the Haskell wiki could be improved with portal pages akin to what Wikipedia does for topics that are prominent on the front page. e.g. http://en.wikipedia.org/wiki/Portal:Science When one looks at the Haskell homepage now, there's a link to "Wiki articles" which just links to an alphabetised category (good if you know what you're looking for, not so good for browsing). Would adding some portal-like pages for major wiki topics (e.g. theory, applications, techniques, etc.) be useful? Or am I just missing some obvious pages somewhere? Cheers, Asumu Takikawa signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Frustrating experience of a wannabe contributor
On Wed, 2007-07-18 at 14:06 -0500, Antoine Latter wrote: > MediaWiki's search isn't fantastic - what I did was a google search on > "site:www.haskell.org DLL" > > It's not a very good answer, but it's the only answer I know. > In general I find Google's search to be more comprehensive and effective than pretty much any search provided by a site (for itself). Useful tricks for haskell, Search mailinglists: site:haskell.org inurl:pipermail Search new wiki: site:haskell.org inurl:haskellwiki Search old wiki: site:haskell.org inurl:hawiki ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Is this haskelly enough?
On Wednesday 18 July 2007 21:16, Johan Tibell wrote: > It would be nice if it was possible to capture this kind of behavior in a > high order function just like map though. I guess the problem is that the > function to map will take different number of arguments depending on the > use case. > > lookAtTwo a b = ... > > lookAtThree a b c = ... > > map' :: (a -> ... -> b) -> [a] -> [b] > > The parameter take a variable number of parameters. > > Note: I don't know if there is a sensible way to write map' at all. Perhaps > explicit recursion is better in this case. Oleg (unsurprisingly) has some type-class hackery for polyvariadic/keyword functions. Probably do what you need, possibly be overkill for what you want... here it is anyway. http://okmij.org/ftp/Haskell/keyword-arguments.lhs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor
Thanks for again pointing out that I didn't want another way to get the information, but I have to defend Simon. His first response was a reworking of the wiki page for the haskell mailing lists. What led me to learning about gmain and its search function. So I added the hint that you can use gmain to search in the mailing archives on that page. And now hopefully the next person who tries to find something in the mailing lists succeds in doing so. :-) That leaves 2 (of my original 3) points: 1) make the wiki search function return all documents containig the search term (who can do that?) 2) consider creating a new wiki topic "Problems and solutions working with haskell" As the 2nd point regards the main wiki page I think the community should be involved with that decision. I don't really want that topic but we are missing a categorie here. Kind regards Andreas PS: I don't consider my self a newcomer. :-) I am on this list already a couple of years, I just don't post to often. (Actually the recent discussion about maintaining the community and the progress of newcomers to experts inspired me to move forward and put something on the wiki.) - Original Message - From: "Steve Schafer" <[EMAIL PROTECTED]> To: Sent: Wednesday, July 18, 2007 10:32 PM Subject: Re: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor On Wed, 18 Jul 2007 13:00:20 -0700, you wrote: >You can even post via gmane. > >Tip: for more powerful searching, use Thunderbird + gmane's NNTP interface. I think people are missing the original poster's point. He's not looking for alternative ways to get from A to B; he's pointing out that a typical approach that one might try to get from A to B is broken. As an aside, this seems to be a prevalent issue, particularly with non-commercial technically-oriented communities. When a newcomer says, "Hey, I tried this [intuitively obvious] way to do something, and it didn't work," the welcoming response is NOT, "Oh, don't do that; do this other [less intuitive] thing instead." The welcoming response is to fix the damn thing so that the intuitive approach works! Steve Schafer Fenestra Technologies Corp. http://www.fenestra.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] Producing MinimumValue
Hi, Am Mittwoch, den 18.07.2007, 13:42 -0700 schrieb Alexteslin: > I am trying to define a function as part of the exercises that gives a > result of a minimum value of the input list of ints. Such as this: > > minimumValue :: [Int] -> Int > minimumValue ns ... > > using either filter or map functions but Not foldr1, because the exercise > precedes the section on foldr1. > I am confused because using filter - it generates a list on some constraint > function for each element. > > Any hints will be very appreciated. Thank you Are you allowed to define the function without any of filter or map, just yourself? minimumValue [a] = ... minimumValue (x:xs) = .. x .. minimumValue xs .. Greetings, Joachim -- Joachim Breitner e-Mail: [EMAIL PROTECTED] Homepage: http://www.joachim-breitner.de ICQ#: 74513189 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Producing MinimumValue
On 18/07/07, Alexteslin <[EMAIL PROTECTED]> wrote: Hello, I am trying to define a function as part of the exercises that gives a result of a minimum value of the input list of ints. Such as this: minimumValue :: [Int] -> Int minimumValue ns ... using either filter or map functions but Not foldr1, because the exercise precedes the section on foldr1. I am confused because using filter - it generates a list on some constraint function for each element. Any hints will be very appreciated. Thank you Are you allowed to use primitive recursion? minimumValue [x] = x minimumValue (x:xs) = ... -- exercise! -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Maintaining the community
Bryan Burgers wrote: I heard that Fermat didn't even actually have a proof. That's unsubstantiated conjecture! :-P Oh, sure, it took over 300 years to arrive at the modern-day proof, which runs to over 400 pages of cutting-edge mathematics spanning multiple very modern disiplins, and is so dense that reputedly only 6 people in the world actually understand it... but... um... what was I saying again? I haven't been paying attention to the subject, but I suppose I should pipe in now. I really enjoy Haskell. I'm probably like most people here in that I like learning new languages: I was told that Lisp is "the language to end all languages". Personally, I tried learning it, and concluded that it sucks. I did learn PostScript in my lunchbreak at work one time because I was bored though... And Tcl on another day... and I read "The Poiniant Guide to Ruby" (which was just the most bizzare thing EVER!) Haskell is a language that has lit up my world. All of the programs I write are heavily math-based, and Haskell seems to be just *perfect* for the job. (Aside from it being so hard to make it go any faster...) To quote somebody else, "Haskell has given a joy to programming that I didn't even know was missing!" Anyway, enough raphsody for now. ;-) I'm surprised at the Java comments... I always thought Java was a language for throwing together Tic-Tac-Toe demos? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)
On 7/18/07, Dougal Stanton <[EMAIL PROTECTED]> wrote: I worked out that [ (a,b) | a <- as, b <- bs ] must be equivalent to > comp = concatMap (\x -> map ((,) x) ys) xs but I can't really say how conditions like "a /= b" get slotted in to that style. Is there a reference for that? As I understand it, list comprehensions are equivalent to monadic expressions in the [] monad. The only trick is that conditions in the list comprehension have to be translated into guard expressions. For instance, [(x,y) | x <- xs, y <- ys, x /= y] translates into: do x <- xs y <- ys guard (x /= y) return (x,y) You're partway there - concatMap is flip (>>=), so you have the xs >>= (\x -> ) part. /g -- The man who'd introduced them didn't much like either of them, though he acted as if he did, anxious as he was to preserve good relations at all times. One never knew, after all, now did one now did one now did one. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Producing MinimumValue
Hello, I am trying to define a function as part of the exercises that gives a result of a minimum value of the input list of ints. Such as this: minimumValue :: [Int] -> Int minimumValue ns ... using either filter or map functions but Not foldr1, because the exercise precedes the section on foldr1. I am confused because using filter - it generates a list on some constraint function for each element. Any hints will be very appreciated. Thank you -- View this message in context: http://www.nabble.com/Producing-MinimumValue-tf4106379.html#a11677240 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor
On Wed, 18 Jul 2007 13:00:20 -0700, you wrote: >You can even post via gmane. > >Tip: for more powerful searching, use Thunderbird + gmane's NNTP interface. I think people are missing the original poster's point. He's not looking for alternative ways to get from A to B; he's pointing out that a typical approach that one might try to get from A to B is broken. As an aside, this seems to be a prevalent issue, particularly with non-commercial technically-oriented communities. When a newcomer says, "Hey, I tried this [intuitively obvious] way to do something, and it didn't work," the welcoming response is NOT, "Oh, don't do that; do this other [less intuitive] thing instead." The welcoming response is to fix the damn thing so that the intuitive approach works! Steve Schafer Fenestra Technologies Corp. http://www.fenestra.com/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)
On 18/07/07, apfelmus <[EMAIL PROTECTED]> wrote: I like it for its elegant point-free style :) Yes, well, I am rather enamoured of them! :-) Apparently, difference can only detect character replacements but not character insertion or deletion, but that's probably not your use case. Yes, that is the case. If I allowed words differing in length they would necessarily look different, so it would be less of a challenge. I could still challenge people to identify the two words of course. Any practice is good. You can avoid generating the superfluous half of the pairs by using tails listPairs ws = [ (head ws', w') | ws' <- tails ws, w' <- ws' , let w = head ws', length w == length w'] Of course, grouping words by length first and pairing the resulting groups is more efficient than filtering out all the pairs where length w /= length w'. But you restrict fingerspell to a fixed word length anyway, so it doesn't matter. I realised after I sent that post that I had *aready* filtered the words so they were all the same length. So the length condition in that list comprehension was completely superfluous. Meh. I will look at using tails to clean things up a bit. I tried to see if there were redundant parts I could remove today, but I was stymied by my lack of understanding of the list comprehensions. I worked out that [ (a,b) | a <- as, b <- bs ] must be equivalent to comp = concatMap (\x -> map ((,) x) ys) xs but I can't really say how conditions like "a /= b" get slotted in to that style. Is there a reference for that? Cheers, Dougal. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Frustrating experience of a wannabe contributor
You can even post via gmane. Tip: for more powerful searching, use Thunderbird + gmane's NNTP interface. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Using Haskell to investigate ML's value restriction
Hi, Ii is interesting that in ML, the presence of mutable ref cells and parametric polymorphism requires the whole language to be dominated by a "value restriction" [1] to ensure that the type system remains sound, whereas in Haskell, because IORef's can only be created (and used) in the IO monad, no such restriction is necessary. I've often wondered why such a simple thing as using a monad has this magical effect, especially since it seems to me that the real problem lies in the fact that type variables in HMD type inference are not generalised properly due to the absence of an explicit representation of the quantifier, so I decided to try using Haskell's more modern type system to investigate further, using the IO monad together with (unsafePerformIO) and (evaluate) to simulate the execution of an ML program: {-# OPTIONS_GHC -fglasgow-exts #-} module Test where import Data.IORef import System.IO.Unsafe (unsafePerformIO) import Control.Exception (evaluate) ref v = unsafePerformIO $ newIORef v put r f = unsafePerformIO $ writeIORef r f get r = unsafePerformIO $ readIORef r -- Gives a core dump as expected test1 :: IO () test1 = do let r = ref (\x -> x) evaluate (put r (\x -> x + 1)) evaluate (get r True) return () (test1) is based on one of the ML examples in [1], and when executed, causes a segmentation fault. The reason seems to be the strange type that is assigned to (r): *Test> let r = ref (\x -> x) *Test> :t r r :: forall t. IORef (t -> t) *Test> (To run this you need to use ghci -fglasgow-exts Test.hs to get ghci 6.6.1 to display the quantifier.) What's strange (to me) about the above typing is that the "forall" has moved outside the IORef constructor. In other words, although we supplied the constructor with a function which can operate on any value, we got back something which, for any value, contains a function which can operate on it. The reason afaics that (test1) goes wrong is that the let binding causes (r) to be bound to the type above, so the argument matches both forall a. Num a => a -> a and Bool -> Bool so the action (evaluate (get r True)) tries to apply a function which expects a number to a Bool. However if we add an explicit type to (r) to get (what I see as) the expected quantification, the type checker correctly rejects the program: test2 :: IO () test2 = do let r :: IORef (forall a. a -> a) = ref (\x -> x) evaluate (put r (\x -> x + 1)) evaluate (get r True) return () "no instance for Num a ..." which might seem like a reason not quite related to our chain of thought so I also tested this using: test3 :: IO () test3 = do let r :: IORef (forall a. a -> a) = ref (\x -> x) evaluate (put r (\'c' -> 'c')) evaluate (get r True) return () which gives "couldn't match expected type `a' (a rigid variable) against inferred type `Char'". In other words, the IORef must always contain a function that works with anything - we can't just give it a more specialized function, so the program is rejected for the reasons we expect. Interestingly, even without type annotations, if we use a case instead of a let, the typechecker also rejects the program: test4 :: IO () test4 = case ref (\x -> x) of r -> do evaluate (put r (\'c' -> 'c')) evaluate (get r True) return () this time by noting that (Bool -> t) does not match (Char -> Char). This illustrates (afaiu) that "case" does not introduce any quantification, in contrast to "let" hence the uninstantiated meta-tyvars of r have to unify with both its uses. In conclusion, it seems that the "magic" given by always having to use IORef's inside the IO monad (without unsafePerformIO of course) is due to the fact that when used this way types involving IORefs never get generalized wrongly since they're never created by a "let" binding. Another conclusion is that if we wanted at some point to have another new strict language with Haskell's nice type system and syntax as an alternative to the ML family, and we also wanted to have references (and continuations), then either the rule for generalizing the meta-type variables in a "let" binding would have to be changed or else we would still have to use monads. I'd be interested to know if the use of impredicative types would automatically solve the "wierd quantification" problem, since: *Test> :t ref ref :: forall a. a -> IORef a therefore applying this to an argument of type (forall b. b -> b) should hopefully give a result of type (IORef (forall b. b -> b)), thus the use of impredicative types might allow such a strict variant of Haskell to use side-effects instead of monads while still retaining type soundness... ? Best regards, Brian. [1] http://www.smlnj.org/doc/Conversion/types.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor
Now I learned that gmain has a niche interface that can search the mailing list & sort the results. :-) I changed the (read via gmain) into (read & search via gmain) for both links at that page. So one easily can see that he can search the archives via gmain. (I didn't know gmain at all, so had no idea that I could use it for a search.) Thanks Andreas - Original Message - From: "Simon Michael" <[EMAIL PROTECTED]> To: Sent: Wednesday, July 18, 2007 9:08 PM Subject: [Haskell-cafe] Re: Frustrating experience of a wannabe contributor > Hi Andreas - very good problem report, thanks. > > I have just cleaned up the archive links at > http://www.haskell.org/haskellwiki/Mailing_lists a bit. I added the > ever-excellent gmane and an overview of all archives. I think some of the > archive descriptive text is no longer needed, but I stopped here. > > Best > -Simon > > ___ > 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: Frustrating experience of a wannabe contributor
Hi Andreas - very good problem report, thanks. I have just cleaned up the archive links at http://www.haskell.org/haskellwiki/Mailing_lists a bit. I added the ever-excellent gmane and an overview of all archives. I think some of the archive descriptive text is no longer needed, but I stopped here. Best -Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Frustrating experience of a wannabe contributor
MediaWiki's search isn't fantastic - what I did was a google search on "site:www.haskell.org DLL" It's not a very good answer, but it's the only answer I know. On 7/18/07, Andreas Marth <[EMAIL PROTECTED]> wrote: - Original Message - From: "Antoine Latter" <[EMAIL PROTECTED]> To: Sent: Wednesday, July 18, 2007 8:26 PM Subject: Re: [Haskell-cafe] Frustrating experience of a wannabe contributor > The closest existing page I could find on the wiki was this one: > > http://www.haskell.org/haskellwiki/GHC/Using_the_FFI > How did you find it? If you look in my original post you can see that I found it too but only by searching for "create" and then manually checking. > But it is a Wiki. If you were to just make a page and put it > somewhere, I doubt anyone would get too mad. > Yes, but will the next one find it? And is there a standard way to find such things we can describe to a newbie? Kind regards, Andreas > On 7/18/07, Bulat Ziganshin <[EMAIL PROTECTED]> wrote: > > Hello Andreas, > > > > Wednesday, July 18, 2007, 8:17:38 PM, you wrote: > > > > > So I tried to find a place where it might have posted or at least fit into. > > > > there is a full list of wiki pages > > > > -- > > Best regards, > > Bulatmailto:[EMAIL PROTECTED] > > > > ___ > > 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[2]: [Haskell-cafe] Frustrating experience of a wannabe contributor
Hello Andreas, Wednesday, July 18, 2007, 10:36:14 PM, you wrote: > I am not sure what you are refering to. i will go into Special pages -> All pages and not seeing any "dll" here, will go to ask in haskell-cafe/irc -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Frustrating experience of a wannabe contributor
- Original Message - From: "Antoine Latter" <[EMAIL PROTECTED]> To: Sent: Wednesday, July 18, 2007 8:26 PM Subject: Re: [Haskell-cafe] Frustrating experience of a wannabe contributor > The closest existing page I could find on the wiki was this one: > > http://www.haskell.org/haskellwiki/GHC/Using_the_FFI > How did you find it? If you look in my original post you can see that I found it too but only by searching for "create" and then manually checking. > But it is a Wiki. If you were to just make a page and put it > somewhere, I doubt anyone would get too mad. > Yes, but will the next one find it? And is there a standard way to find such things we can describe to a newbie? Kind regards, Andreas > On 7/18/07, Bulat Ziganshin <[EMAIL PROTECTED]> wrote: > > Hello Andreas, > > > > Wednesday, July 18, 2007, 8:17:38 PM, you wrote: > > > > > So I tried to find a place where it might have posted or at least fit into. > > > > there is a full list of wiki pages > > > > -- > > Best regards, > > Bulatmailto:[EMAIL PROTECTED] > > > > ___ > > 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] Frustrating experience of a wannabe contributor
I am not sure what you are refering to. Are there any pages about DLLs that I didn't find? If so why couldn't I find them? Are you refering to wiki pages in general? I never said that there are no wiki pages. I just said that I couldn't find an appropriate place where I would post something about creating DLLs. A second point was that I think "wiki articles" and "wiki blogs" are not very well positioned under "Lerning Haskell" on the main wiki page. Am I missing something? (If yes then why?) Did I missunderstand you? Kind regards Andreas PS: Bulat I really appreciate your involvement here, in fact I wanted to try to contribute that what I feel I can contribute, but I failed. And I thought I describe my failure so we as a community can learn from it. - Original Message - From: "Bulat Ziganshin" <[EMAIL PROTECTED]> To: "Andreas Marth" <[EMAIL PROTECTED]> Cc: Sent: Wednesday, July 18, 2007 8:00 PM Subject: Re: [Haskell-cafe] Frustrating experience of a wannabe contributor > Hello Andreas, > > Wednesday, July 18, 2007, 8:17:38 PM, you wrote: > > > So I tried to find a place where it might have posted or at least fit into. > > there is a full list of wiki pages > > -- > Best regards, > Bulatmailto:[EMAIL PROTECTED] > > ___ > 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] Frustrating experience of a wannabe contributor
The closest existing page I could find on the wiki was this one: http://www.haskell.org/haskellwiki/GHC/Using_the_FFI But it is a Wiki. If you were to just make a page and put it somewhere, I doubt anyone would get too mad. On 7/18/07, Bulat Ziganshin <[EMAIL PROTECTED]> wrote: Hello Andreas, Wednesday, July 18, 2007, 8:17:38 PM, you wrote: > So I tried to find a place where it might have posted or at least fit into. there is a full list of wiki pages -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ 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] Frustrating experience of a wannabe contributor
Hello Andreas, Wednesday, July 18, 2007, 8:17:38 PM, you wrote: > So I tried to find a place where it might have posted or at least fit into. there is a full list of wiki pages -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Re[2]: [Haskell-cafe] Is this haskelly enough?
This is probably just me, but I've always mentally separated the list monad (representing choice) from operations on ordered sets implemented by lists (which don't always have to represent choice). In this case, since the remainder of the code wasn't monadic, I find it much easier to understand what concatMap (or concat . map if you don't like the merged function) does than what (>>= tails) would do. /g On 7/18/07, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: DFP> Yes, but that generality is entirely wasted here and thus an DFP> obscuring element. There is no way that this function can be DFP> generalized to work with other monads. As for me, concatMap (and concat.map as well) seems much more obscuring. (>>=) is so general, that I use it almost everywhere, but I have to dig into my memory to remember concatMap (or is it mapConcat?) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- The man who'd introduced them didn't much like either of them, though he acted as if he did, anxious as he was to preserve good relations at all times. One never knew, after all, now did one now did one now did one. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
> Btw, if you don't want the empty lists, you can use > > concatMap (init . tails) . tail . inits Would it not be more efficient and perspicuous to keep the sublists definition as is, just interchanging inits and tails? where sublists = filter (not . null) . concatMap tails . inits Or am I missing some argument about sublist sharing? Dan Bertram Felgenhauer wrote: > J. Garrett Morris wrote: >>-- the tails function returns each tail of the given list; the >> inits function >>-- is similar. By mapping inits over tails, we get all the sublists. >>where sublists = filter (not . null) . concatMap inits . tails > > Nice, but > > concatMap tails . inits > > is much better in my opinion, for several reasons: > > - inits is expensive (O(n^2)) while tails is cheap (O(n)), so it's > better to use inits only once. > - the result lists of inits can't be shared (which is essentially the > reason why it's so expensive); tails shares the common part of the > result lists. > - finally, concatMap tails . inits works nicely with infinite lists, > with every substring occuring in the result eventually > > Btw, if you don't want the empty lists, you can use > > concatMap (init . tails) . tail . inits > > Bertram ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Frustrating experience of a wannabe contributor
Today I had 2 hours time and thought I might contribute to the haskell community. The topic I thought I might be able to give some hints is about creating DLLs. So I went to www.haskell.org which redirected me to the wiki www.haskell.org/haskellwiki/Haskell. So I entered "DLL" into the search to find what is already there and thus began the unpleasant experience. There was nothing in the search result. So I tried to find a place where it might have posted or at least fit into. That was the next step into nowhere. There is an entry "Contributing to this site" which leads to http://www.haskell.org/haskellwiki/HaskellWiki:Contributing, but thats gives zero directions where to put what or how to contribute efficiently. There are two other categories under "Learning Haskell": "Wiki articles" and "Blog articles". After going to "Blog articles" it was clear that it was not the right place either. So I went to "Wiki articles" (http://www.haskell.org/haskellwiki/Category:Haskell) which had such interesting subcategories as "Orphaned projects" and "News". (Remember this is under "Learning Haskell".) At this point I dicided that I might eventually post here under "Tutorials", but first try to find out was is already there. With there I meant the knowledge in the mailing lists. So I went to http://www.haskell.org/haskellwiki/Mailing_lists and there to the archives http://www.haskell.org/pipermail/haskell/ and http://www.haskell.org/pipermail/haskell-cafe/. Unfortunately you cant search this. So I went back and after reading through the mailing list page again went to http://www.mail-archive.com/[EMAIL PROTECTED]/index.html. That is the place where you can search the archive. Unfortunately you get the results in a totally mixed up order. When you click on the "Date" link you get it sorted, but it is not your search that is sorted it is the whole archive that is sorted. If you search again you get the same mixed up result as before. So it is not possible t get your search results sorted. (I had a quick check at "refine search" link (http://www.mail-archive.com/faq.html#search) but that gives me only the syntax for different filters but no sorting.) That was the time where I decided it might be best to write this experience down to maybe give some impulses to change. I did a last search on the haskell wiki for "create" as I thought the would be something that would be used in the DLL context and sure enough that generates 133 results and 2 of them are about DLLs (http://www.haskell.org/haskellwiki/GHC/FAQ and http://www.haskell.org/haskellwiki/GHC/Using_the_FFI). So it is not that there isn't anything about DLLs on the wiki it just doesn't find it. (By the way http://www.haskell.org/haskellwiki/GHC/FAQ links to http://www.haskell.org/ghc/docs/latest/html/users_guide/win32-dlls.html#win3 2-dlls-foreign wich has a typo for generations but is not editable.) If that is the experience someone gets early on in his haskell adventure he might very well get frustrated. So what to do? 1.) make the wiki search function return all documents containig the search term 2.) create a USEFUL search function for the mailing archives 3.) consider creating a new wiki topic "Problems and solutions working with haskell" I am especially woried about the unusable information in the mailing list archives. We have a great community here and lots of wonderful information was exchanged here but it is not accesible right now! Sorry for the long post I hope it is useful in one way or another. PS: I am in this community for a few years already so this hassle didn't drive me away from haskell, but I must say that similar experiences drove me away from a few haskell projects I had interests in (wxHaskell comes to mind). And it might also be a good idea to have a category "Fata morgana of solved problems" or so. What would qualify? COM interaction, HDirect and from the mailing list today: haskell_mod. An early move of a project into that category might a) stipulate a change of maintainer ship early enough before to much knowledge is lost and b) gives a clear warning that things might be more difficult than all the research papers imply (see COM integration). ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)
Dougal Stanton wrote: > The following is a slap-dash program for generating a list of pairs of > words which differ by, at most, one letter. It's quite verbose at the > moment, because (a) that was the way I wrote it, a snippet at a time, > and (b) I lack the wit to make it shorter. > > Can anyone recommend ways to make this program more > efficient/neat/elegant? It runs in decent time on my machine, but it's > not exceedingly pretty and I'm sure it can be made shorter too. I like it for its elegant point-free style :) > -- Number of letters difference between two words. > difference :: Pair -> Int > difference = length . filter (==False) . uncurry (zipWith (==)) Apparently, difference can only detect character replacements but not character insertion or deletion, but that's probably not your use case. > -- Pairs of words of equal length, sorted to reduce > -- duplicates of (a,b), (b,a) type. They shouldn't > -- be completely eradicated because part of the game > -- is to spot when they;re the same word. > listPairs :: WordSet -> PairSet > listPairs ws = [ (w, w') | w <- ws, w' <- ws, length w == length w', w > <= w' ] You can avoid generating the superfluous half of the pairs by using tails listPairs ws = [ (head ws', w') | ws' <- tails ws, w' <- ws' , let w = head ws', length w == length w'] Of course, grouping words by length first and pairing the resulting groups is more efficient than filtering out all the pairs where length w /= length w'. But you restrict fingerspell to a fixed word length anyway, so it doesn't matter. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
Hi Dmitri, I built gtk2hs on Windows with GHC 6.6.1 and gtk2hs-0.9.11. Here's are the steps that worked for me: (not sure I didn't missed some) First you need to install a GTK+ development package for windows. I think mine comes from http://gladewin32.sourceforge.net/modules/wfdownloads/ Then you must have MSYS and MinGW installed on your computer. You'll find information on how to install this here: http://hackage.haskell.org/trac/ghc/wiki/Building/Windows. Once you've installed that stuff you can start a MSYS shell. You'll need to set some environment variables for GTK (adapt to your path): export GTK_BASEPATH=/c/GTK_2.0 export GTK_CONFIG_PATH=/c/GTK_2.0/lib/pkgconfig Cd to the gtk2hs source directory and type: ./configure --prefix=/c/Progra~1/Haskell make make install Hope this helps. Good luck, Olivier. On 7/18/07, Dmitri O.Kondratiev <[EMAIL PROTECTED]> wrote: On 7/17/07, Malte Milatz <[EMAIL PROTECTED]> wrote: > > Dmitri O.Kondratiev: > > It looks like Graphics.SOE does not anymore exist in GHC 6.6.1. > > Where one can get it or what to use instead of it? > > You may try Gtk2Hs, which includes an implementation of SOE, called > Graphics.SOE.Gtk. (It works independently of the actual Gtk API.) Use > then the darcs version, because I remember an SOE bug fixed since the > last release. > > Malte > > Malte, Thanks. The problem is that I need to run SOE on Win32. When I try to run a simple SOE app. in GHCi with Gtk2Hs Win32 release, this code: module GWindow where import Graphics.SOE.Gtk main() = runGraphics ( do w <- openWindow "Graphics Test" (300, 300) drawInWindow w (text (100, 200) "Hello Graphics World") k <- getKey w closeWindow w ) displays a window and hangs. I can get development release of Gtk2Hs with darcs, but how can I build it on Win32? Dima -- Dmitri O. Kondratiev [EMAIL PROTECTED] http://www.geocities.com/dkondr ___ 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] "How to Help Mailing Lists Help Readers"
Andy Oram over at O'Reilly just posted an article analyzing how mailing list readers are helped or hindered in the Perl and Ruby on Rails communities. His most interesting conclusion is that many posters come without the background needed to understand answers. That is certainly been the case on the cafe in many instances. I believe if he had analyzed the Haskell-Cafe list he would have found a much higher percentage of user questions are answered, and sometimes in incredible depth. His conclusion seems to be that, for newbies at least, books and articles that lead the reader gently into the new domain is the answer. As I've learned Haskell over the last year I've found that to definitely be the case. The article is at http://praxagora.com/andyo/professional/mailing_list_follow_up He'll also be speaking at OSCON next week and I look forward to hearing what he has to say. Justin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Is this haskelly enough?
On Wednesday 18 July 2007, Johan Tibell wrote: > It would be nice if it was possible to capture this kind of behavior in a > high order function just like map though. I guess the problem is that the > function to map will take different number of arguments depending on the > use case. > > lookAtTwo a b = ... > > lookAtThree a b c = ... > > map' :: (a -> ... -> b) -> [a] -> [b] > > The parameter take a variable number of parameters. > > Note: I don't know if there is a sensible way to write map' at all. Perhaps > explicit recursion is better in this case. Variable number of parameters? data Mapper alpha beta = Yield beta | Consume (alpha -> Mapper alpha beta) genMap :: Mapper alpha beta -> [alpha] -> [beta] genMap m = flip fix m $ \ loop m' xn -> case (m', xn) of (Yield y, xn) -> y : loop m xn (Consume f, []) -> [] (Consume f, x : xn) -> loop (f x) xn Discards the last few elements of the list if there aren't enough, but you can say genMap (Consume $ \ x -> Consume $ \ y -> Yield $ f x y) xn if you want, and you can even get true C-style varargs out of this. A little verbose, but non-obvious techniques often are. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
J. Garrett Morris wrote: >-- the tails function returns each tail of the given list; the > inits function >-- is similar. By mapping inits over tails, we get all the sublists. >where sublists = filter (not . null) . concatMap inits . tails Nice, but concatMap tails . inits is much better in my opinion, for several reasons: - inits is expensive (O(n^2)) while tails is cheap (O(n)), so it's better to use inits only once. - the result lists of inits can't be shared (which is essentially the reason why it's so expensive); tails shares the common part of the result lists. - finally, concatMap tails . inits works nicely with infinite lists, with every substring occuring in the result eventually Btw, if you don't want the empty lists, you can use concatMap (init . tails) . tail . inits Bertram ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
Sounds like what I want. I'll give it a try. Thanks. On 7/18/07, Tillmann Rendel <[EMAIL PROTECTED]> wrote: Johan Tibell wrote: > I found myself wanting a map that looks at neighboring elements. This is > where I used explicit recursion the most. Something like this: > > f [] = [] > f ((Foo a) : (Bar b) : xs) > | fooBar a b = Foo a : f xs > | otherwise = Bar b : f xs > > This is almost a map. A variation is when filtering and you want some > look-ahead to make the filtering decision. There's probably a good way > to do this I'm not aware of. If you want to map over all elements, but need to look ahead in the mapped function, you can map over the tails: map' :: ([a] -> b) -> [a] -> b map' f = map f . tails f should be something like f (a:b:c:_) = ... If you want to handle groups of n elements together, producing only one element per group, you can use unfoldr with splitAt: map'' :: Int -> ([a] -> b) -> [a] -> [b] map'' n f = map f . unfoldr (((not . null . fst) `guarding`) . splitAt n) guarding p x = guard (p x) >> return x If you want to decide in the mapped function how many elements to consume, you can use unfoldr directly. Tillmann Rendel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
Johan Tibell wrote: I found myself wanting a map that looks at neighboring elements. This is where I used explicit recursion the most. Something like this: f [] = [] f ((Foo a) : (Bar b) : xs) | fooBar a b = Foo a : f xs | otherwise = Bar b : f xs This is almost a map. A variation is when filtering and you want some look-ahead to make the filtering decision. There's probably a good way to do this I'm not aware of. If you want to map over all elements, but need to look ahead in the mapped function, you can map over the tails: map' :: ([a] -> b) -> [a] -> b map' f = map f . tails f should be something like f (a:b:c:_) = ... If you want to handle groups of n elements together, producing only one element per group, you can use unfoldr with splitAt: map'' :: Int -> ([a] -> b) -> [a] -> [b] map'' n f = map f . unfoldr (((not . null . fst) `guarding`) . splitAt n) guarding p x = guard (p x) >> return x If you want to decide in the mapped function how many elements to consume, you can use unfoldr directly. Tillmann Rendel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Maintaining the community
On 7/18/07, Martin Coxall <[EMAIL PROTECTED]> wrote: On 7/18/07, Jon Harrop <[EMAIL PROTECTED]> wrote: > On Tuesday 17 July 2007 23:26:08 Hugh Perkins wrote: > > Am I the only person who finds it interesting/worrying that there are few > > to no people in the group who are ex-C# programmers. I mean, you could > > argue that C# programmers are simply too stupid to do Haskell, but ... you > > know, there is another explanation ;-) > > To understand this, I think you must look at the number of technical users for > each language. There are a huge number of technical C++ and Java programmers > but a tiny number of technical C# programmers in comparison. The few > technical C# programmers are migrating to F# because it is next door and F# > programmers are better looking. Most C# programmers are (a) GUI programmers and (b) former VB programmers. This means they are *guaranteed* to be less attractive that the average C++ developer. I have proof. But it's too big to be contained in this margin. Martin I heard that Fermat didn't even actually have a proof. You wouldn't be trying to hoodwink us in the same way, would you? :) I haven't been paying attention to the subject, but I suppose I should pipe in now. I really enjoy Haskell. I'm probably like most people here in that I like learning new languages: I've given Scheme a fair shot; F# captured my interest for a while, and right now I'm toying with Erlang. I've tried Python, used Perl for a job, determined after an hour that PHP wasn't for me, and even looked at Ruby. The list goes on. (Always, of course, I keep GHC on my computer.) But for work, I use C#. And I, for one, am looking forward to C#3.0, because it will be easier to apply my FP experience to problems when FP is the better way to solve a problem. (You've heard the maxim that when all you have is a hammer, everything looks like a nail; the flip side of it is that when you've got a whole tool set including a screwdriver and you see a screw, but your company only lets you use your hammer, it can be frustrating to beat on the screw with the hammer.) And since I'm fresh out of college with no experience, I'm neither in a position to even suggest a language change in my company, nor do I have the experience to move to the occassional Scheme or Erlang job opening I see (I don't know if I've ever seen a Haskell job opening, and I'm guessing if I did it would get snatched up by a more qualified programmer quite quickly). I guess the point being made is that there are a smaller percentage of attractive programmers in C#; but it looked to me that people were implying that there are /no/ knowledgeable programmers in C#; and I'd just like to assert that maybe there are some that don't really have a choice right now. :) Bryan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
On 7/17/07, Malte Milatz <[EMAIL PROTECTED]> wrote: Dmitri O.Kondratiev: > It looks like Graphics.SOE does not anymore exist in GHC 6.6.1. > Where one can get it or what to use instead of it? You may try Gtk2Hs, which includes an implementation of SOE, called Graphics.SOE.Gtk. (It works independently of the actual Gtk API.) Use then the darcs version, because I remember an SOE bug fixed since the last release. Malte Malte, Thanks. The problem is that I need to run SOE on Win32. When I try to run a simple SOE app. in GHCi with Gtk2Hs Win32 release, this code: module GWindow where import Graphics.SOE.Gtk main() = runGraphics ( do w <- openWindow "Graphics Test" (300, 300) drawInWindow w (text (100, 200) "Hello Graphics World") k <- getKey w closeWindow w ) displays a window and hangs. I can get development release of Gtk2Hs with darcs, but how can I build it on Win32? Dima -- Dmitri O. Kondratiev [EMAIL PROTECTED] http://www.geocities.com/dkondr ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] RE: haskell for web
On 18-jul-2007, at 14:09, Marc Weber wrote: On Tue, Jul 17, 2007 at 03:27:20PM -0700, brad clawsie wrote: On Wed, Jul 18, 2007 at 12:17:12AM +0200, Hugh Perkins wrote: On 7/17/07, Martin Coxall <[EMAIL PROTECTED]> wrote: I wonder why 'we' aren't pushing things like this big time. When Ruby took off, more than anything else it was because of Rails. i agree that web programming is a domain that cannot be ignored i have wondered what it would take to get a mod_haskell for apache Asking google and the wiki search? http://haskell.org/haskellwiki/News/1999 http://losser.st-lab.cs.uu.nl/mod_has (v0.1.7, 14 January 2000) But I haven't checked how up to date those sources are. Not at all. Eelco has repeatedly admitted these sources have greatly bitrotted, and are in dire need of resuscitation. With regards, Arthur. -- /\/ | [EMAIL PROTECTED] | Work like you don't need the money /__\ / | A friend is someone with whom | Love like you have never been hurt /\/__ | you can dare to be yourself | Dance like there's nobody watching ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
Arie Groeneveld wrote: Ok, so when do I use nub instead of 'map head.group.sort'? Never. If |nub_sort=map head.group.sort| is applicable, then you are dealing with a member of class Ord, so use the O(n*log n) |nub_sort|. If you want to preserve the relative order of the input list, use something like nub_cache :: Ord a => [a] -> [a] nub_cache = onub Set.empty where onub seen (x:xs) | Set.member x seen = onub seen xs | otherwise = x : onub (Set.insert x seen) xs onub _ _ = [] |nub_cache| also works for infinite lists, btw. /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
Arie Groeneveld wrote: Hi, Wondering about time space consuming: 'nub' vs 'map head.group.sort' Consider: ry = [1..1] ++ replicate 13 5 ++ replicate 21 34 *Main> length . nub $ ry 1 (5.18 secs, 105 bytes) *Main> length . map head . group . sort $ ry 1 (0.03 secs, 6293384 bytes) Time space nub --- + fnub+++ - + is better ;-) Thanks @@i=arie nub is working on unsorted input. If you want (nub.sort) then the best thing to use is a merge sort that discards duplicates as it works. Copying and modifying GHC's Data.List.sort code: > -- stolen from http://darcs.haskell.org/packages/base/Data/List.hs > -- with 'merge' changed to discard duplicates. nsort l = mergesort compare l nsortBy cmp l = mergesort compare l mergesort :: (a -> a -> Ordering) -> [a] -> [a] mergesort cmp = mergesort' cmp . map wrap mergesort' :: (a -> a -> Ordering) -> [[a]] -> [a] mergesort' cmp [] = [] mergesort' cmp [xs] = xs mergesort' cmp xss = mergesort' cmp (merge_pairs cmp xss) merge_pairs :: (a -> a -> Ordering) -> [[a]] -> [[a]] merge_pairs cmp [] = [] merge_pairs cmp [xs] = [xs] merge_pairs cmp (xs:ys:xss) = merge cmp xs ys : merge_pairs cmp xss merge :: (a -> a -> Ordering) -> [a] -> [a] -> [a] merge cmp xs [] = xs merge cmp [] ys = ys merge cmp (x:xs) (y:ys) = case x `cmp` y of GT -> y : merge cmp (x:xs) ys LT -> x : merge cmpxs (y:ys) EQ -> x : merge cmpxsys wrap :: a -> [a] wrap x = [x] Then you can use nsort or nsortBy, which benchmark (with -O2) as slightly faster than (map head . group . sort) Cheers, Chris ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
On 7/18/07, Arie Groeneveld <[EMAIL PROTECTED]> wrote: Ok, so when do I use nub instead of 'map head.group.sort' ? Using nub gave me a lot of trouble in terms of time consumption while handling long lists. Well, nub is non-strict, so you can use it on infinite or partial lists, provided you don't consume too much of the result. e.g. Prelude Data.List> take 10 $ nub [1..] [1,2,3,4,5,6,7,8,9,10] Prelude Data.List> take 10 $ map head . group . sort $ [1..] Interrupted. (Yes, taking nub of [1..] is silly; it's just an example.) Stuart ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
I think that it's simply a buildfile error, that requires X11 even if you are on windows. The problem is that the building process requires running a configure script, so it requires a cygwin environment under windows. If you need HGL only for "educational" purposes, I strongly suggest you to download and use Hugs (it has HGL precompiled). If you need HGL for more "advanced" purposes, the first step is installing a cygwin environment and remove X11-any and all the lines containing X11 from the HGL.cabal file. Salvatore ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
On Wed, Jul 18, 2007 at 03:58:58PM +0400, Dmitri O.Kondratiev wrote: > Andrea thanks! > I tried to install HGL on Win32 and got this unresolved dependency: > > HGL-3.1>runghc Setup.hs configure > Configuring HGL-3.1... > configure: Dependency base-any: using base-2.1.1 > Setup.hs: cannot satisfy dependency X11-any > > > Any ideas? yes, you need to install the X11 package: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/X11-1.2.2 I must tell you the truth: I don't run Windows (and never did in the last 8 years) and I don't know if/how you can install X11 on it. But since HGL is "a simple graphics library, designed to give the programmer access to most interesting parts of the Win32 Graphics Device Interface and X11 library ..." I think that runhaskell Setup.hs etc etc should do the job. I tried HGL on linux recently and it worked smoothly without any complain (very fun playing with it, btw). Otherwise try coming back here, I'm sure some else will give you an advise. Hope this helps. Andrea ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
Arie, Ok, so when do I use nub instead of 'map head.group.sort' ? Well, for one thing, |map head . group . sort| produces a sorted list, wheras |nub| preserves the order of the input list. Cheers, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
Miguel Mitrofanov wrote: > AG> Wondering about time space consuming: 'nub' vs 'map > AG> head.group.sort' > > Prelude> :t Data.List.nub > Data.List.nub :: (Eq a) => [a] -> [a] > Prelude> :t Data.List.sort > Data.List.sort :: (Ord a) => [a] -> [a] > > nub uses less information than sort, so it MUST be slower. Ok, so when do I use nub instead of 'map head.group.sort' ? Using nub gave me a lot of trouble in terms of time consumption while handling long lists. @@i=arie ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Time consumption nub
AG> Wondering about time space consuming: 'nub' vs 'map AG> head.group.sort' Prelude> :t Data.List.nub Data.List.nub :: (Eq a) => [a] -> [a] Prelude> :t Data.List.sort Data.List.sort :: (Ord a) => [a] -> [a] nub uses less information than sort, so it MUST be slower. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[2]: [Haskell-cafe] Is this haskelly enough?
DFP> Yes, but that generality is entirely wasted here and thus an DFP> obscuring element. There is no way that this function can be DFP> generalized to work with other monads. As for me, concatMap (and concat.map as well) seems much more obscuring. (>>=) is so general, that I use it almost everywhere, but I have to dig into my memory to remember concatMap (or is it mapConcat?) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] RE: haskell for web
On Tue, Jul 17, 2007 at 03:27:20PM -0700, brad clawsie wrote: > On Wed, Jul 18, 2007 at 12:17:12AM +0200, Hugh Perkins wrote: > > On 7/17/07, Martin Coxall <[EMAIL PROTECTED]> wrote: > >> > >> I wonder why 'we' aren't pushing things like this big time. When Ruby > >> took off, more than anything else it was because of Rails. > > i agree that web programming is a domain that cannot be ignored > > i have wondered what it would take to get a mod_haskell for apache Asking google and the wiki search? http://haskell.org/haskellwiki/News/1999 http://losser.st-lab.cs.uu.nl/mod_has (v0.1.7, 14 January 2000) But I haven't checked how up to date those sources are. Marc Weber ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
*Andrea Rossato* wrote: Hi! as far as I know what you are looking for (Graphics.SOE) is part of HGL. Have a look here: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HGL-3.1 Hope I got it right and that this helps. All the best, Andrea Andrea thanks! I tried to install HGL on Win32 and got this unresolved dependency: HGL-3.1>runghc Setup.hs configure Configuring HGL-3.1... configure: Dependency base-any: using base-2.1.1 Setup.hs: cannot satisfy dependency X11-any Any ideas? Thanks, Dmitri -- Dmitri O. Kondratiev [EMAIL PROTECTED] http://www.geocities.com/dkondr ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
On Jul 17, 2007, at 10:13 PM, Tony Morris wrote: David F. Place wrote: The use of >>= is just an obscure way of saying (flip concatMap). Correction. The use of >>= is a more general way of saying (flip concatMap). Tony Morris Yes, but that generality is entirely wasted here and thus an obscuring element. There is no way that this function can be generalized to work with other monads. ___ (---o---o-o-o---o-o-o( David F. Place mailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Time consumption nub
Hi, Wondering about time space consuming: 'nub' vs 'map head.group.sort' Consider: ry = [1..1] ++ replicate 13 5 ++ replicate 21 34 *Main> length . nub $ ry 1 (5.18 secs, 105 bytes) *Main> length . map head . group . sort $ ry 1 (0.03 secs, 6293384 bytes) Time space nub --- + fnub+++ - + is better ;-) Thanks @@i=arie ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] GHC 6.6.1: Where is Graphics.SOE ?
On Tue, Jul 17, 2007 at 06:52:43PM +0400, Dmitri O.Kondratiev wrote: > I am trying to use Graphics.SOE (that was present at least in GHC 6.4) to > go through "Simple Graphics" examples as described in Pail Hudak book "The > Haskell School of Expression. Learning functional programming through > multimedia". > It looks like Graphics.SOE does not anymore exist in GHC 6.6.1. Where one > can get it or what to use instead of it? > Do I understand right that Graphics library in GHC 6.6.1 is split between > OpenGL and GLUT modules? > Any tutorials on OpenGL and GLUT modules similar to Paul Hudak "Simple > Graphics"? Hi! as far as I know what you are looking for (Graphics.SOE) is part of HGL. Have a look here: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HGL-3.1 Hope I got it right and that this helps. All the best, Andrea ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Is this haskelly enough?
It would be nice if it was possible to capture this kind of behavior in a high order function just like map though. I guess the problem is that the function to map will take different number of arguments depending on the use case. lookAtTwo a b = ... lookAtThree a b c = ... map' :: (a -> ... -> b) -> [a] -> [b] The parameter take a variable number of parameters. Note: I don't know if there is a sensible way to write map' at all. Perhaps explicit recursion is better in this case. On 7/18/07, apfelmus <[EMAIL PROTECTED]> wrote: Johan Tibell wrote: > I found myself wanting a map that looks at neighboring elements. This is > where I used explicit recursion the most. Something like this: > > f [] = [] > f ((Foo a) : (Bar b) : xs) > | fooBar a b = Foo a : f xs > | otherwise = Bar b : f xs > > This is almost a map. A variation is when filtering and you want some > look-ahead to make the filtering decision. There's probably a good way > to do this I'm not aware of. There are some cases missing, like f [x] = ?? f (Bar a : Foo b : xs) = ?? A better example is probably takeUntilConvergence epsilon (x:x':xs) | abs (x-x') < epsilon = [x] | otherwise= x:takeUntilConvergence epsilon (x':xs) useful for numeric iterations like sqrt a = last $ takeUntilConvergence (1e-10) $ iterate (\x -> (x+a/x)/2) 1 Another way to implement takeUntilConvergence is to zip the list with its tail: takeUntilConvergence epsilon xs = fst . head . dropUntil ((< epsilon) . snd) $ zipWith (\x x' -> (x,abs(x-x')) xs (tail xs) Regards, apfelmus ___ 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: "no-coding" functional data structures via lazyness
Dave Bayer wrote: > Here is a prime sieve that can hang within a factor of two of the fastest > code in that thread, until it blows up on garbage collection: > > - > > diff :: Ord a => [a] -> [a] -> [a] > diff xs@(x:xt) ys@(y:yt) = case compare x y of > LT -> x : (diff xt ys) > EQ -> (diff xt yt) > GT -> (diff xs yt) > diff _ _ = undefined > > union :: Ord a => [a] -> [a] -> [a] > union xs@(x:xt) ys@(y:yt) = case compare x y of > LT -> x : (union xt ys) > EQ -> x : (union xt yt) > GT -> y : (union xs yt) > union _ _ = undefined > > twig :: Ord a => [a] -> [a] -> [a] > twig (x:xt) ys = x : (union xt ys) > twig _ _ = undefined > > pair :: Ord a => [[a]] -> [[a]] > pair (x:y:xs) = twig x y : (pair xs) > pair _ = undefined > > tree :: Ord a => [[a]] -> [a] > tree xs = > let g (x:xt) = x : (g $ pair xt) > g _ = undefined > in foldr1 twig $ g xs > > This differs from your code in that it works with infinite lists, so > it can't build a balanced tree; the best it can do is to build a vine > of subtrees that double in size. Yes, the shape of the implicit tree has to be known in advance, there's no way to change it dynamically. But there's no need to balance it perfectly as long as access to a leaf takes only logarithmic time. So, the function tree is fine. I'd even turn it into a higher-order function foldInfTree1 :: (a -> a -> a) -> [a] -> a foldInfTree1 f xs = foldr1 f $ deepen xs where pairs []= [] pairs [x] = [x] pairs (x:x':xs) = f x x' : pairs xs deepen [] = [] deepen (x:xs) = x : deepen (pairs xs) In case of an infinite list, the resulting tree of `f`s has an infinite right spine but every other path is finite. Moreover, the length of a path to the n-th list element is bounded by something like 2*log n. With this higher-order function, your tree becomes tree = foldInfTree1 twig But I'm not sure whether this tree structure really works well for infinite lists, see my remark below. > seed :: Integral a => [a] > seed = [2,3,5,7,11,13] > > wheel :: Integral a => [a] > wheel = drop 1 [ 30*j+k | j <- [0..], k <- [1,7,11,13,17,19,23,29] ] > > primes :: Integral a => [a] > primes = seed ++ (diff (drop 3 wheel) multiples) > > multiples :: Integral a => [a] > multiples = tree ps > where f p n = mod n p /= 0 > g (_,ns) p = ([ n*p | n <- ns ], filter (f p) ns) > ps = map fst $ tail $ scanl g ([], wheel) $ drop 3 primes Hm, this looks very suspicious, I guess there's something wrong with using scanl g . You filter out multiples that are divisible by prior primes, but that should be the job of the heap. In other words, the filter (f p) is the core of the algorithm here, making it almost equivalent to the simple sieve xs p = filter (\n -> n `mod` p /= 0) xs primes = map head $ scanl sieve [2..] primes The heap is not needed at all. In fact, it may even be the second reason for the memory consumption here. To see why, lets draw the structure of the tree with parentheses 1 (2 3) ((4 5) (6 7)) (((8 9) (10 11)) ((12 13) (14 15))) ... Every pair inside a parenthesis is meant to be merged with twig , it's just too noisy to write every twig explicitly. Also, I left out the outermost chain of parenthesis implied by the foldr . Now, as soon as the twig on ((8 9) (10 11)) and ((12 13) (14 15)) changes into a union , the twig between (12 13) and (14 15) will be calculated and compared against the remaining (9 `union` (10 `union` 11)). But evaluating the 12-th is to soon at this stage since 9,10 and 11 are surely smaller, the sequence of primes is monotone. Unfortunately, this gap widens, so that you need to evaluate the (2^k+2^(k-1))-th prime when the (2^k+1)-th prime would be next. In the end, it seems that this tree structure doesn't work well on stuff that is somewhat monotone. I guess that you'll run into problems with termination as soon as you remove the filter (f p) . Besides perhaps termination, I guess that your reason for applying filter (f p) repeatedly was to start the wheel at the right position. Normally, the multiples would just be multiples = tree $ map multiple primes multiple p = map (p*) [p..] But given that we could start roll the wheel starting from p, the list of factors can be reduced dramatically multiple p = map (p*) $ wheel `rollFrom` p This can be done by representing the wheel differently: -- Wheel (modulus) (list of remainders) data Wheel = Wheel Int [Int] wheel30 = Wheel 30 [1,7,11,13,17,19,23,29] (Wheel n rs) `rollFrom` k = map (k+) $ differences $ until (\rs -> k `mod` n == head rs `mod` n) tail (cycle rs) where differences xs = zipWith subtract' xs (tail xs) subtract' x y = (y - x) `mod` n > I can imagine a lazy functional language that would support reification > of suspended closures, so one could incrementally
Re: [Haskell-cafe] Is this haskelly enough?
On Jul 18, 2007, at 2:13 , ok wrote: On Jul 17, 2007, at 22:26 , James Hunt wrote: As a struggling newbie, I've started to try various exercises in order to improve. I decided to try the latest Ruby Quiz (http:// www.rubyquiz.com/quiz131.html) in Haskell. Haskell guru level: I am comfortable with higher order functions, but never think of using the list monad. Developing the answer went like this: - find all sublists - annotate each with its sum - find the best (sum, list) pair - throw away the sum best_sublist = snd . maximum . annotate_with_sums . all_sublists All sublists was easy: all_sublists = concatMap tails . inits Confession: the one mistake I made in this was using map here instead of concatMap, but the error message from Hugs was sufficiently clear. Annotating with sums is just doing something to each element, so annotate_with_sums = map (\xs -> (sum xs, xs)) Put them together and you get best_sublist = snd . maximum . map (\xs -> (sum xs, xs)) . concatMap tails . inits The "trick" here is that as far as getting a correct answer is concerned, we don't *care* whether we compare two lists with equal sums or not, either will do. To do without that trick, best_sublist = snd . maximumBy c . map s . concatMap tails . inits where s xs = (sum xs, xs) f (s1,_) (s2,_) = compare s1 s2 Confession: I actually made two mistakes. I remembered the inits and tails functions, but forgot to import List. Again, hugs caught this. However, the key point is that this is a TRICK QUESTION. What is the trick about it? This is a well known problem called The Maximum Segment Sum problem. It's described in a paper "A note on a standard strategy for developing loop invariants and loops" by David Gries (Science of Computer Programming 2(1984), pp 207-214). The Haskell code above finds each segment (and there are O(n**2) of them, at an average length of O(n) each) and computes the sums (again O(n) each). So the Haskell one-liner is O(n**3). But it CAN be done in O(n) time. Gries not only shows how, but shows how to go about it so that you don't have to be enormously clever to think of an algorithm like that. What would be a good exercise for functional programmers would be to implement the linear-time algorithm. The algorithm given by Gries traverses the array one element at a time from left to right, so it's not that hard. The tricky thing is modifying the algorithm to return the list; it might be simplest to just keep track of the end-points and do a take and a drop at the end. I think it is at least mildly interesting that people commented about things like whether to do it using explicit parameters ("pointful" style) or higher-order functions ("pointless" style) and whether to use the list monad or concatMap, but everyone seemed to be happy with a cubic time algorithm when there's a linear time one. Well, the original poster wanted advice on how to improve his Haskell style, not algorithmic complexity. I think that the appropriate response to that is to show different ways to write the same program in idiomatic Haskell. /Björn___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Is this haskelly enough?
Johan Tibell wrote: > I found myself wanting a map that looks at neighboring elements. This is > where I used explicit recursion the most. Something like this: > > f [] = [] > f ((Foo a) : (Bar b) : xs) > | fooBar a b = Foo a : f xs > | otherwise = Bar b : f xs > > This is almost a map. A variation is when filtering and you want some > look-ahead to make the filtering decision. There's probably a good way > to do this I'm not aware of. There are some cases missing, like f [x] = ?? f (Bar a : Foo b : xs) = ?? A better example is probably takeUntilConvergence epsilon (x:x':xs) | abs (x-x') < epsilon = [x] | otherwise= x:takeUntilConvergence epsilon (x':xs) useful for numeric iterations like sqrt a = last $ takeUntilConvergence (1e-10) $ iterate (\x -> (x+a/x)/2) 1 Another way to implement takeUntilConvergence is to zip the list with its tail: takeUntilConvergence epsilon xs = fst . head . dropUntil ((< epsilon) . snd) $ zipWith (\x x' -> (x,abs(x-x')) xs (tail xs) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is this haskelly enough?
I found myself wanting a map that looks at neighboring elements. This is where I used explicit recursion the most. Something like this: f [] = [] f ((Foo a) : (Bar b) : xs) | fooBar a b = Foo a : f xs | otherwise = Bar b : f xs This is almost a map. A variation is when filtering and you want some look-ahead to make the filtering decision. There's probably a good way to do this I'm not aware of. Johan On 7/17/07, David F. Place <[EMAIL PROTECTED]> wrote: You hardly ever need to use explicit recursion in Haskell. Every useful way of doing recursion has already been captured in some higher order function. For example here is your subarrays implemented using unfoldr: subarrays xs = concat $ unfoldr f xs where f [] = Nothing f xs = Just ( [ys | n <- [1..length xs], ys <- [(take n xs)]], tail xs) On Jul 17, 2007, at 4:26 PM, James Hunt wrote: > Hi, > > As a struggling newbie, I've started to try various exercises in > order to improve. I decided to try the latest Ruby Quiz (http:// > www.rubyquiz.com/quiz131.html) in Haskell. Would someone be kind > enough to cast their eye over my code? I get the feeling there's a > better way of doing it! > > subarrays :: [a] -> [[a]] > subarrays [] = [[]] > subarrays xs = (sa xs) ++ subarrays (tail xs) > where sa xs = [ys | n <- [1..length xs], ys <- [(take n xs)]] > > maxsubarrays :: [Integer] -> [Integer] > maxsubarrays xs = msa [] (subarrays xs) > where >msa m [] = m >msa m (x:xs) > | sum x > sum m = msa x xs > | otherwise = msa m xs > > --for testing: should return [2, 5, -1, 3] > main = maxsubarrays [-1, 2, 5, -1, 3, -2, 1] > > I've read tutorials about the syntax of Haskell, but I can't seem > to find any that teach you how to really "think" in a Haskell way. > Is there anything (books, online tutorials, exercises) that anyone > could recommend? > > Thanks, > James > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ (---o---o-o-o---o-o-o( David F. Place mailto:[EMAIL PROTECTED] ___ 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] Maintaining the community
On 7/18/07, Jon Harrop <[EMAIL PROTECTED]> wrote: On Tuesday 17 July 2007 23:26:08 Hugh Perkins wrote: > Am I the only person who finds it interesting/worrying that there are few > to no people in the group who are ex-C# programmers. I mean, you could > argue that C# programmers are simply too stupid to do Haskell, but ... you > know, there is another explanation ;-) To understand this, I think you must look at the number of technical users for each language. There are a huge number of technical C++ and Java programmers but a tiny number of technical C# programmers in comparison. The few technical C# programmers are migrating to F# because it is next door and F# programmers are better looking. Most C# programmers are (a) GUI programmers and (b) former VB programmers. This means they are *guaranteed* to be less attractive that the average C++ developer. I have proof. But it's too big to be contained in this margin. Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Maintaining the community
On 7/17/07, Thomas Conway <[EMAIL PROTECTED]> wrote: On 7/18/07, Hugh Perkins <[EMAIL PROTECTED]> wrote: > Am I the only person who finds it interesting/worrying that there are few to > no people in the group who are ex-C# programmers. I mean, you could argue > that C# programmers are simply too stupid to do Haskell, but ... you know, > there is another explanation ;-) I wouldn't say too stupid, but it may be a cultural thing. People working in C++ are more likely to be doing what I would call "technical" programming, and correspondingly more likely to be interested in Haskell, and to appreciate what it has to offer from painful personal experience. From what I know of the marketplace, people working in C# are more likely to be doing client/integration work where technical finesse is less important, and are therefore less likely to see the point. Quite. Any C++ developer who has spent any time with Boost knows and has experienced the horror of Boost::Lambda. C++ template metaprogramming *is* a pattern-matching pure functional language with type classes (template classes), but it's syntatically ugly and far too minimal. The Boost community are doing a valiant job of trying to add higher order capabilities to C++, but the langauge is just not set up for it. Maybe when C++0x matures, and C++ has concepts, variadic template parameters etc., things will be more civilized. Or we can use Haskell, which has them now. FWIW, C# is slowly gaining higher order concepts too. C# 2.0: Ad hoc polymorphism, closures (anonymous delegates). C# 3.0: Lambda expressions, higher-order functions over collections, LINQ, etc. Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe