[Haskell-cafe] List comprehensions with Word8

2013-05-16 Thread Jose A. Lopes
Hello everyone, I was playing with Word8 and list comprehensions and the following examples came up. I have to admit the behavior looks quite strange because it does not seem to be consistent. Can someone shed some light on reason behind some of these outputs? By the way, I have abbreviated

Re: [Haskell-cafe] List comprehensions with Word8

2013-05-16 Thread Felipe Almeida Lessa
Prelude 10 `mod` 256 0 So [1..10] == [1..0]. Cheers, On Thu, May 16, 2013 at 6:15 PM, Jose A. Lopes jose.lo...@ist.utl.pt wrote: Hello everyone, I was playing with Word8 and list comprehensions and the following examples came up. I have to admit the behavior looks quite

Re: [Haskell-cafe] List comprehensions with Word8

2013-05-16 Thread Tikhon Jelvis
...@ist.utl.pt wrote: Hello everyone, I was playing with Word8 and list comprehensions and the following examples came up. I have to admit the behavior looks quite strange because it does not seem to be consistent. Can someone shed some light on reason behind some of these outputs? By the way

Re: [Haskell-cafe] List comprehensions with Word8

2013-05-16 Thread Steve Schafer
On Thu, 16 May 2013 23:15:33 +0200, you wrote: Hello everyone, I was playing with Word8 and list comprehensions and the following examples came up. I have to admit the behavior looks quite strange because it does not seem to be consistent. Can someone shed some light on reason behind some

Re: [Haskell-cafe] List comprehensions with Word8

2013-05-16 Thread Casey McCann
is left as an exercise for the reader.) - C. On Thu, May 16, 2013 at 5:15 PM, Jose A. Lopes jose.lo...@ist.utl.pt wrote: Hello everyone, I was playing with Word8 and list comprehensions and the following examples came up. I have to admit the behavior looks quite strange because it does not seem

[Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Tako Schotanus
of preventing the repetition, of course there is, I'm just wondering about this very specific case within list comprehensions. -Tako ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Miguel Mitrofanov
..100] , length c 15]* NB: Just to make clear, I'm not asking if there is an alternative way of preventing the repetition, of course there is, I'm just wondering about this very specific case within list comprehensions. -Tako ___ Haskell-Cafe mailing

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Stephen Lavelle
wondering about this very specific case within list comprehensions. -Tako ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Ozgur Akgun
On 16 February 2011 09:19, Tako Schotanus t...@codejive.org wrote: I wondered if there was a way for a guard in a list comprehension to refer to the item being produced? I'm just wondering about this very specific case Then, the answer is no. As others have noted, let binding is the way

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Tako Schotanus
Ok, thanks all, that was what I was looking for :) -Tako On Wed, Feb 16, 2011 at 10:46, Ozgur Akgun ozgurak...@gmail.com wrote: On 16 February 2011 09:19, Tako Schotanus t...@codejive.org wrote: I wondered if there was a way for a guard in a list comprehension to refer to the item being

[Haskell-cafe] Re: Generalizing nested list comprehensions

2010-02-27 Thread Heinrich Apfelmus
Daniel Fischer wrote: Ishaaq Chandy wrote: If this question sounds a bit noob-ish, that would be because I am one - so apologies in advance! I have functions that look something like these: f1 :: [a] - [b] f1 xs = [foo [x1, x2] | x1 - xs, x2 - bar x1, baz x1 /= baz x2]

[Haskell-cafe] Generalizing nested list comprehensions

2010-02-26 Thread Ishaaq Chandy
xs (fn 2 xs) == f2 xs (fn 3 xs) == f3 xs (fn 25 xs) == f25 xs - obviously if I were to implement f25 as nested list comprehensions it would be ridiculously tedious! Any ideas how I can implement fn? Thanks, Ishaaq -- View this message in context: http://old.nabble.com/Generalizing-nested

Re: [Haskell-cafe] Generalizing nested list comprehensions

2010-02-26 Thread Daniel Fischer
on the pattern set by f1, f2 and f3 such that: fn :: Int - [a] - [b] and: (fn 1 xs) == f1 xs (fn 2 xs) == f2 xs (fn 3 xs) == f3 xs (fn 25 xs) == f25 xs - obviously if I were to implement f25 as nested list comprehensions it would be ridiculously tedious! Any ideas how I can implement fn

[Haskell-cafe] (possibly) a list comprehensions question

2009-11-19 Thread Ozgur Akgun
Hi Cafe! I am struggling with an interesting problem while defining a function. It looks quite easy to me, but I couldn't manage to have a proper implementation yet. To illustrate what I'm trying to achive, I'll introduce special cases of the desired function, and hopefully build towards a

Re: [Haskell-cafe] (possibly) a list comprehensions question

2009-11-19 Thread Eugene Kirpichov
You can easily use sequence. The less easy part is understanding why it works. Are you familiar with monads? If you are not, try to take the source code of 'sequence', inline it and understand why *that* works. Prelude map sum $ sequence [[1,2], [10,20], [100,200]]

Re: [Haskell-cafe] (possibly) a list comprehensions question

2009-11-19 Thread Neil Brown
is the list monad, as already posted. If that confuses you, here is a version using list comprehensions (well, mostly): allPossibilities :: [[a]] - [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls] The second line prefixes all possibilities

Re: [Haskell-cafe] (possibly) a list comprehensions question

2009-11-19 Thread Ozgur Akgun
this function to accept a list of lists of arbitrary length, and produce the required result. Hi, The concise solution is the list monad, as already posted. If that confuses you, here is a version using list comprehensions (well, mostly): allPossibilities :: [[a]] - [[a]] allPossibilities

[Haskell-cafe] Re: (possibly) a list comprehensions question

2009-11-19 Thread yair...@gmail.com
solution is the list monad, as already posted.  If that confuses you, here is a version using list comprehensions (well, mostly): allPossibilities :: [[a]] - [[a]] allPossibilities [] = [[]] allPossibilities (l:ls) = [ x : xs | x - l, xs - allPossibilities ls] The second line prefixes

Re: [Haskell-cafe] Re: (possibly) a list comprehensions question

2009-11-19 Thread Ozgur Akgun
question is, how can I generalize this function to accept a list of lists of arbitrary length, and produce the required result. Hi, The concise solution is the list monad, as already posted. If that confuses you, here is a version using list comprehensions (well, mostly

[Haskell-cafe] Re: Implicit concatenation in list comprehensions

2009-07-22 Thread Jon Fairbairn
Bulat Ziganshin bulat.zigans...@gmail.com writes: Hello Neil, Tuesday, July 21, 2009, 1:26:55 PM, you wrote:  ++ [ -i      | not (null (ghcOptSearchPath opts)) ]  ++ [ -i, dir | dir - ghcOptSearchPath opts ] Following the discussions, I now support this extension too - I keep seeing more

Re: [Haskell-cafe] Re: Implicit concatenation in list comprehensions

2009-07-22 Thread Lanny Ripple
Speaking as a perl programmer I find that a bit insulting. We do see how awful some of it is. perl4-perl5-perl6 have been as much about cleanup as adding functionality. And I would have thought this forum would have been more aware that after Audrey built the first perl6 interpreter basically

[Haskell-cafe] Re: Implicit concatenation in list comprehensions

2009-07-22 Thread Simon Michael
It was the perl community that brought me to haskell - by their interesting choice of implementation language for Pugs - and I'm grateful to them for this among other things! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Implicit concatenation in list comprehensions

2009-07-22 Thread Bulat Ziganshin
Hello Simon, Wednesday, July 22, 2009, 11:47:17 PM, you wrote: It was the perl community that brought me to haskell - by their interesting choice of implementation language for Pugs - for me, Pugs development tale is Beast and Beauty of programming world :) -- Best regards, Bulat

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Duncan Coutts
On Sun, 2009-07-19 at 23:07 +0100, Thomas Schilling wrote: 2009/7/19 Max Bolingbroke batterseapo...@hotmail.com Dear Cafe, For fun, I spent a few hours yesterday implement support for this syntax in GHC, originally propsed by Koen Claessen: [k, =, v, | (k, v) - [(foo, 1), (bar,

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Neil Mitchell
Except that it's ugly compared to the proposed extension. With the extension you can put things in the same, right place: renderGhcOptions opts =     ghcOptExtraPre opts  -- source search path  ++ [ -i      | not (null (ghcOptSearchPath opts)) ]  ++ [ -i, dir | dir - ghcOptSearchPath opts

Re[2]: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Bulat Ziganshin
Hello Neil, Tuesday, July 21, 2009, 1:26:55 PM, you wrote:  ++ [ -i      | not (null (ghcOptSearchPath opts)) ]  ++ [ -i, dir | dir - ghcOptSearchPath opts ] Following the discussions, I now support this extension too - I keep seeing more and more places in my code where it would be very

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Thomas Schilling
I'm not convinced ugly is a good reason to add more complexity to the language syntax. I am not aware of a good metric to measure the costs/beneficts of new syntactic constructs. Part of the costs are the number of tools that need to be adapted and the extend of their loss of utility if they are

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Dan Weston
Bulat Ziganshin wrote: Hello Neil, Tuesday, July 21, 2009, 1:26:55 PM, you wrote: ++ [ -i | not (null (ghcOptSearchPath opts)) ] ++ [ -i, dir | dir - ghcOptSearchPath opts ] Following the discussions, I now support this extension too - I keep seeing more and more places in my code

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Felipe Lessa
On Tue, Jul 21, 2009 at 12:29:18PM -0700, Dan Weston wrote: This would mean that [ | c ] = concat $ do { c; return [] } The right is legal Haskell and gives []. The left is (not yet) legal. Should it be? Please, please, do not allow that. People wanting [] should write []. Thanks! --

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
I think the tuple sections are a great idea! It also makes tuple types and constructors more alike: x :: (,) String Double x = (,) Pi 3.14159 I can also see some uses in writing pointfree code. I would definitely want this in a future GHC (or any other Haskell compiler/interpreter) release. I'm

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
On Mon, Jul 20, 2009 at 1:27 PM, Roel van Dijkvandijk.r...@gmail.com wrote: I think the tuple sections are a great idea! It also makes tuple types and constructors more alike: x :: (,) String Double x = (,) Pi 3.14159 I just realised this is already in GHC :-) But does you patch also add the

RE: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Sittampalam, Ganesh
Roel van Dijk wrote: On Mon, Jul 20, 2009 at 1:27 PM, Roel van Dijkvandijk.r...@gmail.com wrote: I think the tuple sections are a great idea! It also makes tuple types and constructors more alike: x :: (,) String Double x = (,) Pi 3.14159 I just realised this is already in GHC :-) But

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
I am also wondering what the following would/should mean:   (1, , ( , 2), ) 'a' 'b' 'c' I would expect it to be a type error, since I think the following is the only sane type the tuple can have (assuming numeric literals :: Int): (1, , ( , 2), ) :: a - b - (Int, a, c - (c, Int), b)

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Max Bolingbroke
2009/7/20 Roel van Dijk vandijk.r...@gmail.com: I just realised this is already in GHC :-) But does you patch also add the equivalent for tuple type annotations? x :: (String, ) Double x = (Pi, ) 3.14159 It doesn't, and indeed it would only work in the special case where your only missing

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Nicolas Pouillard
Excerpts from Max Bolingbroke's message of Sun Jul 19 16:58:08 +0200 2009: Dear Cafe, For fun, I spent a few hours yesterday implement support for this syntax in GHC, originally propsed by Koen Claessen: [...] P.S. I also implemented tuple sections

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread porges
2009/7/21 Roel van Dijk vandijk.r...@gmail.com: I am also wondering what the following would/should mean:   (1, , ( , 2), ) 'a' 'b' 'c' I would expect it to be a type error, since I think the following is the only sane type the tuple can have (assuming numeric literals :: Int): (1, , ( , 2),

[Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Max Bolingbroke
Dear Cafe, For fun, I spent a few hours yesterday implement support for this syntax in GHC, originally propsed by Koen Claessen: [k, =, v, | (k, v) - [(foo, 1), (bar, 2)] [foo, =, 1, , bar, =, 2, ] This is a generalisation of list comprehensions that allows several items to be concatenated

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Neil Mitchell
Hi Max, For fun, I spent a few hours yesterday implement support for this syntax in GHC, originally propsed by Koen Claessen: [k, =, v, | (k, v) - [(foo, 1), (bar, 2)] [foo, =, 1, , bar, =, 2, ] This is a generalisation of list comprehensions that allows several items

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Thomas Hartman
in GHC, originally propsed by Koen Claessen: [k, =, v, | (k, v) - [(foo, 1), (bar, 2)] [foo, =, 1, , bar, =, 2, ] This is a generalisation of list comprehensions that allows several items to be concatenated onto the result list at once, by having several comma-separated items before the pipe

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Robin Green
) - [(foo, 1), (bar, 2)] [foo, =, 1, , bar, =, 2, ] This is a generalisation of list comprehensions that allows several items to be concatenated onto the result list at once, by having several comma-separated items before the pipe. I like the power this feature gives, and if it was already

Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Thomas Schilling
be simulated via: [ x | (k, v) - [(foo, 1), (bar, 2)], x - [k, =, v, ]] [foo,=,1, ,bar,=,2, ] I believe that the added syntax (which every complete tool operating on Haskell code would have to support) is not worth its price. This is a generalisation of list comprehensions that allows several

[Haskell-cafe] List comprehensions and impredicative rank-N types

2009-06-11 Thread Vladimir Reshetnikov
Hi, Consider the following definitions: --- {-# LANGUAGE RankNTypes, ImpredicativeTypes #-} foo :: [forall a. [a] - [a]] foo = [reverse] bar :: [a - b] - a - b bar fs = head fs ---

[Haskell-cafe] Converting list comprehensions to combinatory style

2009-03-07 Thread R J
Can anyone help with this problem from Bird: a. Convert the following list comprehensions to combinatory style: i. [(x, y) | x - [1..n], odd x, y - [1..n]] ii. [(x, y) | x - [1..n], y - [1..n], odd x] b. Are they equal? c. Compare the costs of evaluating the two expressions. I

Re: [Haskell-cafe] Converting list comprehensions to combinatory style

2009-03-07 Thread Daniel Fischer
Am Samstag, 7. März 2009 23:06 schrieb R J: Can anyone help with this problem from Bird: a. Convert the following list comprehensions to combinatory style: i. [(x, y) | x - [1..n], odd x, y - [1..n]] ii. [(x, y) | x - [1..n], y - [1..n], odd x] b. Are they equal? c. Compare

[Haskell-cafe] Re: generalized list comprehensions

2008-11-10 Thread Johannes Waldmann
Well, my original post wasn't that negative ... Indeed then f [by e] seems a nice idea *but* the point was that I'd like to have this in any monad. The type of f in then f should be m a - m b, not just m a - m a, because then you don't need special syntax for group, which is somewhat like [a]

RE: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Mitchell, Neil
Generalised? Heck, I don't use list comprehension at all! :-P Perhaps you should! :-) You definitely should! Take a look at the Uniplate paper for some wonderful concise uses of list comprehensions for abstract syntax tree traversals. If you use a language like F# they become even more

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Duncan Coutts
On Sun, 2008-11-09 at 19:18 +, Andrew Coppin wrote: Derek Elkins wrote: As far as I can tell, no one actually uses parallel list comprehensions. With any luck, the same will be true for generalized list comprehensions. Generalised? Heck, I don't use list comprehension at all

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Andrew Coppin
Duncan Coutts wrote: On Sun, 2008-11-09 at 19:18 +, Andrew Coppin wrote: Generalised? Heck, I don't use list comprehension at all! :-P Perhaps you should! :-) When I first started with Haskell I kind of had the idea that list comprehensions were just for beginners and that 'real

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Andrew Coppin
Mitchell, Neil wrote: In general: if boolean then [value] else [] Can be written as: [value | boolean] Is there any specific reason why this is valid? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Luke Palmer
Because expressions are treated as guards in list comprehensions. I.e.: [ foo | x - a, b, y - c, d ] Is interpreted as: do x - a guard b y - c guard d return foo Luke ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Jonathan Cast
On Mon, 2008-11-10 at 18:20 +, Andrew Coppin wrote: Mitchell, Neil wrote: In general: if boolean then [value] else [] Can be written as: [value | boolean] Is there any specific reason why this is valid? Is there any specific reason to dis-allow it? The grammar here

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Jonathan Cast
the idea that list comprehensions were just for beginners and that 'real' hackers used just concatMaps and filters. A couple years later I 'rediscovered' list comprehensions and I now use them frequently. There are many cases in real programs where simple and not-so-simple list

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Andrew Coppin
of filtering?) The only time I use list comprehensions is when I quickly want a Cartesian product. I wasn't really aware it could filter as well. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Duncan Coutts
On Mon, 2008-11-10 at 18:20 +, Andrew Coppin wrote: Mitchell, Neil wrote: In general: if boolean then [value] else [] Can be written as: [value | boolean] Is there any specific reason why this is valid? It is due to the rules for the translation of list comprehensions

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Duncan Coutts
On Mon, 2008-11-10 at 18:19 +, Andrew Coppin wrote: I don't actually use *lists* all that much - or at least not list transformations. And if I'm going to do something complicated, I'll usually write it as a do-expression rather than a comprehension. Just a random example out of

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Jonathan Cast
interesting. I didn't know that a Boolean was a valid generator. (Presumably this has the effect of filtering?) The only time I use list comprehensions is when I quickly want a Cartesian product. I wasn't really aware it could filter as well. Funny. About the only time I use list comprehensions

Re: [Haskell-cafe] Re: generalized list comprehensions

2008-11-10 Thread Max Bolingbroke
2008/11/10 Johannes Waldmann [EMAIL PROTECTED]: Well, my original post wasn't that negative ... Indeed then f [by e] seems a nice idea *but* the point was that I'd like to have this in any monad. The type of f in then f should be m a - m b, not just m a - m a, because then you don't need

Re: [Haskell-cafe] generalized list comprehensions

2008-11-10 Thread Derek Elkins
? This is the motivation of list comprehensions. In naive set theory, set comprehensions are one way of an equivalence between predicates and sets. It's the Cartesian product aspect that should be considered unusual if anything. The binding aspect of list generators corresponds to naming

Re: [Haskell-cafe] generalized list comprehensions

2008-11-09 Thread Max Bolingbroke
comprehensions. AFAIK it was removed because it gave confusing error messages to new users of the language (what is this Monad thing? I just want a list of stuff!). List comprehensions really have diverged from being a special do notation at the list monad, since you are able to write

Re: [Haskell-cafe] generalized list comprehensions

2008-11-09 Thread Johannes Waldmann
like [(x, y) | x - xs | y - ys], and it's not clear how to define zip for a monad - but perhaps there is some extension of a monad where it makes sense? Well, I question that the above notation makes sense (for lists). It is trying to be too clever. standard list comprehensions at least

Re: [Haskell-cafe] generalized list comprehensions

2008-11-09 Thread Andrew Coppin
Derek Elkins wrote: As far as I can tell, no one actually uses parallel list comprehensions. With any luck, the same will be true for generalized list comprehensions. Generalised? Heck, I don't use list comprehension at all! :-P ___ Haskell-Cafe

Re: [Haskell-cafe] generalized list comprehensions

2008-11-09 Thread Derek Elkins
times have changed. Sure, I believe the feature was called monad comprehensions. AFAIK it was removed because it gave confusing error messages to new users of the language (what is this Monad thing? I just want a list of stuff!). List comprehensions really have diverged from being a special

Re: [Haskell-cafe] generalized list comprehensions

2008-11-09 Thread Yitzchak Gale
Derek Elkins wrote: As far as I can tell, no one actually uses parallel list comprehensions. With any luck, the same will be true for generalized list comprehensions. I second this. -Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] generalized list comprehensions

2008-11-08 Thread Johannes Waldmann
Looking at this funny new feature http://haskell.org/ghc/docs/6.10.1/html/users_guide/syntax-extns.html#generalised-list-comprehensions I have just one question - why doesn't this work with the do-notation? I avoid list comprehensions because I feel that return belongs at the end, not in front

Re: [Haskell-cafe] generalized list comprehensions

2008-11-08 Thread Max Bolingbroke
2008/11/8 Johannes Waldmann [EMAIL PROTECTED]: Looking at this funny new feature http://haskell.org/ghc/docs/6.10.1/html/users_guide/syntax-extns.html#generalised-list-comprehensions I have just one question - why doesn't this work with the do-notation? I avoid list comprehensions because I

Re: [Haskell-cafe] generalized list comprehensions

2008-11-08 Thread Johannes Waldmann
list comprehensions for purely optical reasons (putting the cart before the horse), so I write do in the list monad. Of course I prefer let to where for the same reasons, so for me you could indeed replace guard by where, and return by select, and x - foo by from x in foo and it'd look like the real

Re: [Haskell-cafe] simple Haskell question - List comprehensions

2008-03-12 Thread Philip Müller
Dan Licata schrieb: Does that help? Yeah, it did - Thanks! - Philip ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] simple Haskell question - List comprehensions

2008-03-09 Thread Philip Müller
Hi, I'm just working through Hutton's Programming in Haskell and I found an exercise which I can't solve, although it looks simple. Maybe someone here could give me a hint? Exercise: Show how the single comprehension [(x,y) | x - [1,2,3], y - [4,5,6]] with two generators can be re-expressed

Re: [Haskell-cafe] simple Haskell question - List comprehensions

2008-03-09 Thread Miguel Mitrofanov
Exercise: Show how the single comprehension [(x,y) | x - [1,2,3], y - [4,5,6]] with two generators can be re-expressed using two comprehensions with single generators. Hint: make use of the library function _concat_. Another hint: it can be rewritten as concatMap (\x - concatMap (\y -

Re: [Haskell-cafe] simple Haskell question - List comprehensions

2008-03-09 Thread Sebastian Sylvan
[(x,y) | x - [1,2,3], y - [4,5,6]] with two generators can be re-expressed using two comprehensions with single generators. Hint: make use of the library function _concat_. Another hint, list comprehensions are just values of type [ a ] (a would be Integer in this case). So in other words

Re: [Haskell-cafe] map and list comprehensions

2006-02-06 Thread Paul Hudak
John Peterson wrote: I think the point was that all syntax (like list comprehensions or pattern matching) in Haskell is tied directly to the Prelude. So [ f x ...] is ALWAYS using the Prelude definitions of things while map could be hidden and redefined. Yes, of course. I was implicitly

Re: Old alternative syntax for list comprehensions?

2003-07-16 Thread Jay Cox
But I have a vague recollection of an alternative syntax, something like [(i,j) \ i - [..], j - [1..]] that generated a list something like [(1,1),(1,2),(2,1),(1,3),(2,2),(3,1),...]. Did I dream this, or was it a feature of Miranda*, Gopher or Hugs many years ago? Peter A long time ago I

Old alternative syntax for list comprehensions?

2003-07-14 Thread Peter Pudney
I recently wanted to generate an infinite list of pairs [(i,j) | i - [1..], j - [1..]] Of course, this list comprehension never gets around to generating pairs (2,_). The solution I was after is easily done: [(i,s-i) | s - [2..], i - [1..s-1]] But I have a vague recollection of an

Re: Old alternative syntax for list comprehensions?

2003-07-14 Thread Andrew J Bromage
G'day all. On Mon, Jul 14, 2003 at 11:08:55PM -0400, Ken Shan wrote: I just wanted to see that asterisk again. ...and semicolons returned to their rightful place as separators for list comprehension/diagonalisation qualifiers. Cheers, Andrew Bromage

List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften
Hello, Recently, I came accross this expression: [ x + y | x - xs | y - ys ] As far as I can see (Haskell Report), this is not allowed by the haskell 98 standard. So I assume it to be an ex- tension. Where can I find information about this? Thanks, Rijk

Re: List comprehensions

2003-01-30 Thread Oliver Braun
* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]: Recently, I came accross this expression: [ x + y | x - xs | y - ys ] ^ Put a comma ',' here. Regards, Olli -- obraun@ -+-[ informatik.unibw-muenchen.de ]-+-[ IIS _ INF _

Re: List comprehensions

2003-01-30 Thread Rijk J. C. van Haaften
* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]: Recently, I came accross this expression: [ x + y | x - xs | y - ys ] ^ Put a comma ',' here. That's something totally different. Two examples: 1. Comma [ x + y | x - [1,2], y -

Re: List comprehensions

2003-01-30 Thread Ross Paterson
On Thu, Jan 30, 2003 at 11:41:49AM +0100, Rijk J. C. van Haaften wrote: Recently, I came accross this expression: [ x + y | x - xs | y - ys ] As far as I can see (Haskell Report), this is not allowed by the haskell 98 standard. So I assume it to be an ex- tension. Where can I find

Re: List comprehensions

2003-01-30 Thread Oliver Braun
* Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 12:06 +0100]: * Rijk J. C. van Haaften [EMAIL PROTECTED] [2003-01-30 11:41 +0100]: Recently, I came accross this expression: [ x + y | x - xs | y - ys ] ^ Put a comma ',' here. That's

RE: List comprehensions

2003-01-30 Thread Jan de Wit
, a GHC extension. See http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#PA RALLEL-LIST-COMPREHENSIONS for more info. The code above does the same as zipWith (+) xs ys, basically. Cheers, Jan ### This message has been scanned by F-Secure

Re: List comprehensions

2003-01-30 Thread Jon Fairbairn
On 2003-01-30 at 11:08GMT Ross Paterson wrote: On Thu, Jan 30, 2003 at 11:41:49AM +0100, Rijk J. C. van Haaften wrote: Recently, I came accross this expression: [ x + y | x - xs | y - ys ] As far as I can see (Haskell Report), this is not allowed by the haskell 98 standard. So I