
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