list comprehension with multiple generator|targets

I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like, data V = A | B | C pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x -- can that be a list comprehension, like pv s = [ 'A' | A <- s -- ?? ] thanks, Donn

I don't think list comprehension is the solution. What you want is a map.
Would this work?
data V = A | B | C
f :: [V] -> String
f l = flip map l $ \x -> case x of
A -> 'A'
B -> 'B'
C -> 'C'
main = print $ f [A,B,C,C,A]
2014-11-09 21:58 GMT-05:00 Donn Cave
I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Viva Cila

On 11/10/2014 03:10 AM, Raphaël Mongeau wrote:
I don't think list comprehension is the solution. What you want is a map.
Would this work?
data V = A | B | C
f :: [V] -> String f l = flip map l $ \x -> case x of A -> 'A' B -> 'B' C -> 'C'
Looks like the job for LambdaCase, ‘flip map l $ \case …’ Also it doesn't do what the OPs function does because it doesn't skip C.
main = print $ f [A,B,C,C,A]
2014-11-09 21:58 GMT-05:00 Donn Cave
: I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn
-- Mateusz K.

On 11/10/2014 02:58 AM, Donn Cave wrote:
I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn
You basically want map and filter. Moreover, you are also inlining a toChar function which complicates matters. If you have ‘Eq V’ instance and ‘toChar’ function then you could write it as [ toChar y | y <- [ x | x <- s, x /= C ] ] Where inner comprehension is just filter and outer is just map. It doesn't make much sense to do it this way and it imposes an extra constraint, Eq. Alternative (with LambdaCase): map toChar $ filter (\case { C -> False; _ -> True }) s But that's ugly and we still need toChar. Further, although not really applicable here, there might not be a reasonable toChar :: V -> Char for every constructor of V. So in conclusion, the way you have now is pretty good: it avoids Eq constraint and it doesn't force us to write (possibly partial) toChar. So to answer your question, no, you can't extend this very easily to multiple without effectively inlining your existing ‘pv’ function into the comprehension. -- Mateusz K.

Wow, didn't know about the LambdaCase.
Here is the code with LambdaCase, filter and Eq
{-# LANGUAGE LambdaCase #-}
data V = A | B | C deriving (Eq)
f :: [V] -> String
f l = flip map (filter (/= C) l) $ \case
A -> 'A'
B -> 'B'
main = print $ f [A,B,C,C,A]
2014-11-09 22:28 GMT-05:00 Mateusz Kowalczyk
On 11/10/2014 02:58 AM, Donn Cave wrote:
I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn
You basically want map and filter. Moreover, you are also inlining a toChar function which complicates matters.
If you have ‘Eq V’ instance and ‘toChar’ function then you could write it as
[ toChar y | y <- [ x | x <- s, x /= C ] ]
Where inner comprehension is just filter and outer is just map. It doesn't make much sense to do it this way and it imposes an extra constraint, Eq. Alternative (with LambdaCase):
map toChar $ filter (\case { C -> False; _ -> True }) s
But that's ugly and we still need toChar. Further, although not really applicable here, there might not be a reasonable toChar :: V -> Char for every constructor of V.
So in conclusion, the way you have now is pretty good: it avoids Eq constraint and it doesn't force us to write (possibly partial) toChar.
So to answer your question, no, you can't extend this very easily to multiple without effectively inlining your existing ‘pv’ function into the comprehension.
-- Mateusz K. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Viva Cila

On 11/10/2014 03:32 AM, Raphaël Mongeau wrote:
Wow, didn't know about the LambdaCase.
Here is the code with LambdaCase, filter and Eq
{-# LANGUAGE LambdaCase #-}
data V = A | B | C deriving (Eq)
f :: [V] -> String f l = flip map (filter (/= C) l) $ \case A -> 'A' B -> 'B'
main = print $ f [A,B,C,C,A]
The problem with this solution is that your pattern match is partial. Add a D constructor and you get a pattern match failure. You could extend to ‘\case { A -> Just 'A'; …; _ -> Nothing }’ and use mapMaybe instead of map but it doesn't answer the question of using list comprehensions.
2014-11-09 22:28 GMT-05:00 Mateusz Kowalczyk
: On 11/10/2014 02:58 AM, Donn Cave wrote:
I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn
You basically want map and filter. Moreover, you are also inlining a toChar function which complicates matters.
If you have ‘Eq V’ instance and ‘toChar’ function then you could write it as
[ toChar y | y <- [ x | x <- s, x /= C ] ]
Where inner comprehension is just filter and outer is just map. It doesn't make much sense to do it this way and it imposes an extra constraint, Eq. Alternative (with LambdaCase):
map toChar $ filter (\case { C -> False; _ -> True }) s
But that's ugly and we still need toChar. Further, although not really applicable here, there might not be a reasonable toChar :: V -> Char for every constructor of V.
So in conclusion, the way you have now is pretty good: it avoids Eq constraint and it doesn't force us to write (possibly partial) toChar.
So to answer your question, no, you can't extend this very easily to multiple without effectively inlining your existing ‘pv’ function into the comprehension.
-- Mateusz K. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Mateusz K.

quoth Mateusz Kowalczyk
{-# LANGUAGE LambdaCase #-}
data V = A | B | C deriving (Eq)
f :: [V] -> String f l = flip map (filter (/= C) l) $ \case A -> 'A' B -> 'B'
main = print $ f [A,B,C,C,A]
The problem with this solution is that your pattern match is partial. Add a D constructor and you get a pattern match failure. You could extend to ‘\case { A -> Just 'A'; …; _ -> Nothing }’ and use mapMaybe instead of map but it doesn't answer the question of using list comprehensions.
Indeed, I'd rigged up something with Maybe for this, like pv a = [t | Just t <- pvc a] where pvc A = Just 'A' pvc B = Just 'B' _ = Nothing ... when it occurred to me that I might be wasting the power of the list comprehensions that I so rarely use. Guess not! Thanks, Donn

This :
pv a = [t | Just t <- pvc a]
is strange, can we really do pattern matching inside list comprehension?
If I try to make your code work its lead me to this:
import Data.Maybe
data V = A | B | C
pv l = catMaybes [pvc e | e <- l]
where
pvc A = Just 'A'
pvc B = Just 'B'
pvc _ = Nothing
main = print $ pv [A,B,C,C,A]
As you can see, [pvc e | e <- l] is just "map (plv) l" and I think the
where is more clear with a lambdaCase.
{-# LANGUAGE LambdaCase #-}
import Data.Maybe
data V = A | B | C
pv l = catMaybes $ flip map l $ \case
A -> Just 'A'
B -> Just 'B'
_ -> Nothing
main = print $ pv [A,B,C,C,A]
No, this solution does not use list comprehension, but your problem need
some form of pattern matching and as Mateusz said, inlining it inside the
function would be ugly. Since all the real work of your problem is in the
case with the Maybe and the _ I think list comprehension can't offer much.
I think its interesting how the case is doing the job of the earlier
discussed filter AND the mapping to a char. And as a bonus it support
adding D, E, F ... to the V data without much trouble.
2014-11-09 22:47 GMT-05:00 Donn Cave
quoth Mateusz Kowalczyk
[... re someone else's example ] {-# LANGUAGE LambdaCase #-}
data V = A | B | C deriving (Eq)
f :: [V] -> String f l = flip map (filter (/= C) l) $ \case A -> 'A' B -> 'B'
main = print $ f [A,B,C,C,A]
The problem with this solution is that your pattern match is partial. Add a D constructor and you get a pattern match failure. You could extend to ‘\case { A -> Just 'A'; …; _ -> Nothing }’ and use mapMaybe instead of map but it doesn't answer the question of using list comprehensions.
Indeed, I'd rigged up something with Maybe for this, like
pv a = [t | Just t <- pvc a] where pvc A = Just 'A' pvc B = Just 'B' _ = Nothing
... when it occurred to me that I might be wasting the power of the list comprehensions that I so rarely use. Guess not! Thanks,
Donn _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Viva Cila

On Sun, Nov 9, 2014 at 11:07 PM, Raphaël Mongeau
This : pv a = [t | Just t <- pvc a] is strange, can we really do pattern matching inside list comprehension?
Yes; that's part of the point of list comprehensions, and of their extension to (and, back in the very early days, contraction from) monad comprehensions. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

quoth Raphaël_Mongeau
This : pv a = [t | Just t <- pvc a] is strange, can we really do pattern matching inside list comprehension?
Sure, but from a list - I'm sorry, I meant "map pvc a", not "pvc a". pv a = [t | Just t <- map pvc a] where pvc A = Just 'A' pvc B = Just 'B' pvc _ = Nothing You know, the pattern match in the list comprehension is just what I wanted it for in the first place - remember ['A' | A <- s] ? That's OK, it just isn't useful because I can do this for only one target.
... and I think is more clear with a lambdaCase.
lambdaCase is a great thing, but given that it's hardly any different
pv l = catMaybes $ flip map l $ \case A -> Just 'A' B -> Just 'B' _ -> Nothing
from pv l = catMaybes $ map pvc l where pvc A = Just 'A' pvc B = Just 'B' pvc _ = Nothing ... in this case I don't think we're desperate enough to use a nonstandard extension. Donn

On 11/10/2014 04:24 AM, Donn Cave wrote:
quoth Raphaël_Mongeau
This : pv a = [t | Just t <- pvc a] is strange, can we really do pattern matching inside list comprehension?
Sure, but from a list - I'm sorry, I meant "map pvc a", not "pvc a".
pv a = [t | Just t <- map pvc a] where pvc A = Just 'A' pvc B = Just 'B' pvc _ = Nothing
You know, the pattern match in the list comprehension is just what I wanted it for in the first place - remember ['A' | A <- s] ? That's OK, it just isn't useful because I can do this for only one target.
... and I think is more clear with a lambdaCase.
lambdaCase is a great thing, but given that it's hardly any different
pv l = catMaybes $ flip map l $ \case A -> Just 'A' B -> Just 'B' _ -> Nothing
from
pv l = catMaybes $ map pvc l where pvc A = Just 'A' pvc B = Just 'B' pvc _ = Nothing
catMaybes . map f = mapMaybe f Also I wonder if laziness saves us here: in the original program we effectively do map and filter at the same time. If we were to take (catMaybes . map f) with strict evaluation then we'd be traversing twice: once to map and once to catMaybes… Just something to think about, I think performance would be no worse anyway, at least not by much.
... in this case I don't think we're desperate enough to use a nonstandard extension.
I wouldn't worry about using a ‘non-standard’ extension: you're probably not going to stick to H98 or H2010 in non-trivial programs either way. LambaCase is just a trivially expandable sugar anyway, modulo clean identifier name. -- Mateusz K.

quoth Mateusz Kowalczyk
Also I wonder if laziness saves us here: in the original program we effectively do map and filter at the same time. If we were to take (catMaybes . map f) with strict evaluation then we'd be traversing twice: once to map and once to catMaybes… Just something to think about, I think performance would be no worse anyway, at least not by much.
Might be right, I really have little idea what's going on underneath there - I'd have guessed that lazy or not, the two functions are doing all the work of traversing their separate lists even if at any conceptual moment those lists are nothing but a head and a tail. The rationale is mostly about a cleaner presentation. I was thinking of this problem a few weeks back when we were talking about C programmers learning Haskell. I'd guess they'd find a certain lack of elegance in the Maybe strategy, compared to what would be a pretty simple and direct problem in C, like "for (i = j = 0; i < n; ++i) if (toChar(vx[i], &cx[j]) ++j;" The recursive function I wrote for reference is my least favorite solution, less clear and more prone to stupid coding errors. If my list comprehension idea had been valid, I think it would have been a very concise presentation.
... in this case I don't think we're desperate enough to use a nonstandard extension.
I wouldn't worry about using a ‘non-standard’ extension: you're probably not going to stick to H98 or H2010 in non-trivial programs either way. LambaCase is just a trivially expandable sugar anyway, modulo clean identifier name.
I do make frequent use of ForeignFunctionInterface, but perhaps that's the exception that proves the rule inasmuch as it has little to do with the language per se. I'm happy that I don't have to deal with programs that couldn't have been written without extensions. Donn

On 11/10/2014 03:28 AM, Mateusz Kowalczyk wrote:
On 11/10/2014 02:58 AM, Donn Cave wrote:
I'm guessing this isn't supported, but might be worth asking - can I extend a list comprehension like ['A' | A <- s] to multiple values? Like,
data V = A | B | C
pv :: [V] -> [Char] pv [] = [] pv (A:x) = 'A':(pv x) pv (B:x) = 'B':(pv x) pv (_:x) = pv x
-- can that be a list comprehension, like
pv s = [ 'A' | A <- s -- ?? ]
thanks, Donn
You basically want map and filter. Moreover, you are also inlining a toChar function which complicates matters.
If you have ‘Eq V’ instance and ‘toChar’ function then you could write it as
[ toChar y | y <- [ x | x <- s, x /= C ] ]
Where inner comprehension is just filter and outer is just map. It doesn't make much sense to do it this way and it imposes an extra constraint, Eq. Alternative (with LambdaCase):
map toChar $ filter (\case { C -> False; _ -> True }) s
But that's ugly and we still need toChar. Further, although not really applicable here, there might not be a reasonable toChar :: V -> Char for every constructor of V.
Oh, forgot to mention one thing. You could have a toChar :: V -> Maybe Char and have a comprehension like [ y | Just y <- [ toChar x | x <- s, x /= C ] ] a.k.a. mapMaybe toChar . filter (/= C) and without Eq mapMaybe toChar . filter (\case { C -> False; _ -> True }) but we still need to write toChar separately and the comprehension still has Eq constraint. Of course we could inline the pattern match and so on but in the end it's all just ugly. Stick to what you have.
So in conclusion, the way you have now is pretty good: it avoids Eq constraint and it doesn't force us to write (possibly partial) toChar.
So to answer your question, no, you can't extend this very easily to multiple without effectively inlining your existing ‘pv’ function into the comprehension.
-- Mateusz K.
participants (4)
-
Brandon Allbery
-
Donn Cave
-
Mateusz Kowalczyk
-
Raphaël Mongeau