Best way to return Bool based on a successful pattern match?

Hi Cafe, Every now and then I'm in a need to check if a value satisfies pattern with a Bool result. So far I know several ways to do this: 1. Use lens: `has _Left` 2. Make a function: `isLeft (Left _) = True; isLeft _ = False` 3. (When you need a lambda) Use LambdaCase: `\case Left _ -> True; _ -> False` Usually I go for (1) because I use lens extensively anyway, but for one-time usage all the extra machinery seems too much. I don't like (2) when I don't have a library defining that for me, and also (3) -- they seem inelegant. Is there any syntactic trick that I'm missing that makes it look nicer? -- Nikolay.

Looking at the instances defined for Bool and Either, I don't think there's a higher level way of doing it. But even if there's one, it'll probably be more obscure than isLeft, which is in base since 4.7.0.0.

Yes, for standard data types like Either or Maybe the best way is to use library-defined functions -- I was more interested in a way to check for any given pattern, which would look nicer than a custom defined function or a LambdaCase. An example use case: partition (\case MyPat -> True; _ -> False) Anyway using lens for this is already very readable and concise, albeit needs makePrisms/Lens and stuff. On 07/13/2015 03:02 PM, Nikita Karetnikov wrote:
Looking at the instances defined for Bool and Either, I don't think there's a higher level way of doing it. But even if there's one, it'll probably be more obscure than isLeft, which is in base since 4.7.0.0.
-- Nikolay.

Perhaps this is of interest to you,
http://hackage.haskell.org/package/generic-maybe
HTH,
Adam
On Mon, Jul 13, 2015 at 3:04 PM, Nikolay Amiantov
Yes, for standard data types like Either or Maybe the best way is to use library-defined functions -- I was more interested in a way to check for any given pattern, which would look nicer than a custom defined function or a LambdaCase. An example use case:
partition (\case MyPat -> True; _ -> False)
Anyway using lens for this is already very readable and concise, albeit needs makePrisms/Lens and stuff.
On 07/13/2015 03:02 PM, Nikita Karetnikov wrote:
Looking at the instances defined for Bool and Either, I don't think there's a higher level way of doing it. But even if there's one, it'll probably be more obscure than isLeft, which is in base since 4.7.0.0.
-- Nikolay. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

A nice idea! It can be helpful in some cases, although usually I have more complex patterns, for example "get all DataDefinitions from a list of TopLevelDefinitions parsed from a .hs file" or "filter all KeyPresses directed to a particular window from an Event stream". On 07/13/2015 04:24 PM, Adam Bergmark wrote:
Perhaps this is of interest to you, http://hackage.haskell.org/package/generic-maybe
HTH, Adam
-- Nikolay.

You can write a generic 'is constructor' function using GHC Generics,
if you want:
{-# LANGUAGE
DeriveGeneric
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, MultiParamTypeClasses
, UndecidableInstances
#-}
import GHC.Generics
import Generics.Deriving.ConNames
class SameType a b | b -> a where
saturate :: b -> a
instance SameType a a where
saturate = id
instance SameType a b => SameType a (c -> b) where
saturate f = saturate (f undefined)
is :: (ConNames (Rep a), Generic a, SameType a b) => b -> a -> Bool
is ctor val = conNameOf val == conNameOf (saturate ctor)
Now you can do things like:
data Foo = A | B Int
deriving (Show, Generic)
*Main> is A A
True
*Main> is A (B 1)
False
*Main> is B A
False
*Main> is B (B 2)
True
Erik
On Mon, Jul 13, 2015 at 3:40 PM, Nikolay Amiantov
A nice idea! It can be helpful in some cases, although usually I have more complex patterns, for example "get all DataDefinitions from a list of TopLevelDefinitions parsed from a .hs file" or "filter all KeyPresses directed to a particular window from an Event stream".
On 07/13/2015 04:24 PM, Adam Bergmark wrote:
Perhaps this is of interest to you, http://hackage.haskell.org/package/generic-maybe
HTH, Adam
-- Nikolay. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Very interesting trick, thanks, it feels closer to what I've imagined! Meanwhile I've played with quasi-quoters and TH a bit for the sake of experiment. As a result I got this: https://github.com/abbradar/isit/blob/master/src/Language/Haskell/IsIt.hs It allows one to do very nice-looking checks, like: λ filter [is|Left (Just 4)|] [Right "test", Left (Just 4), Left Nothing] [Left (Just 4)] λ let x = 4 λ filter [is|Left (Just x)|] [Right "test", Left (Just 4), Left Nothing] [Left (Just 4)] λ :t [is|Just _|] [is|Just _|] :: Maybe t -> Bool I doubt anyone including me would actually use this though -- it depends on haskell-src-{exts,meta} which you probably don't want as yet more dependencies for your project to do such a trivial task. On 07/13/2015 05:06 PM, Erik Hesselink wrote:
You can write a generic 'is constructor' function using GHC Generics, if you want:
{-# LANGUAGE DeriveGeneric , FlexibleContexts , FlexibleInstances , FunctionalDependencies , MultiParamTypeClasses , UndecidableInstances #-}
import GHC.Generics import Generics.Deriving.ConNames
class SameType a b | b -> a where saturate :: b -> a
instance SameType a a where saturate = id
instance SameType a b => SameType a (c -> b) where saturate f = saturate (f undefined)
is :: (ConNames (Rep a), Generic a, SameType a b) => b -> a -> Bool is ctor val = conNameOf val == conNameOf (saturate ctor)
Now you can do things like:
data Foo = A | B Int deriving (Show, Generic)
*Main> is A A True *Main> is A (B 1) False *Main> is B A False *Main> is B (B 2) True
Erik -- Nikolay.

For this specific use case, you can also consider list comprehensions:
[ x | x@(DataDefinition _) <- tlds ]
I personally greatly prefer this over something like ‘filter’ + an ugly
lambda, especially if you can use the list comprehension for the rest of
your processing as well.
On Mon, 13 Jul 2015 16:40:33 +0300, Nikolay Amiantov
A nice idea! It can be helpful in some cases, although usually I have more complex patterns, for example "get all DataDefinitions from a list of TopLevelDefinitions parsed from a .hs file" or "filter all KeyPresses directed to a particular window from an Event stream".

I forgot to mention: The same can be extended to any monad with a good
‘fail’ definition, including many types of streams/parsers/whatever.
On Mon, 13 Jul 2015 19:03:02 +0200, Niklas Haas
For this specific use case, you can also consider list comprehensions:
[ x | x@(DataDefinition _) <- tlds ]
I personally greatly prefer this over something like ‘filter’ + an ugly lambda, especially if you can use the list comprehension for the rest of your processing as well.
On Mon, 13 Jul 2015 16:40:33 +0300, Nikolay Amiantov
wrote: A nice idea! It can be helpful in some cases, although usually I have more complex patterns, for example "get all DataDefinitions from a list of TopLevelDefinitions parsed from a .hs file" or "filter all KeyPresses directed to a particular window from an Event stream".

Ouch, I feel deeply ashamed for not thinking of that from the beginning! While not being a general solution "Pattern a -> a -> Bool" this covers almost all my use cases (with rest of processing, too) while requiring no extensions, no dependencies and overall being readable and "boring" in Sven's sense (at least I feel so -- comprehensions are being taught in every Haskell tutorial under the sun and are pretty self-describing). It remains a question of whether it's equally readable in monadic case ("huh? list comprehension? but... this is a Maybe/an Event!"), but in most my GUI/event-processing code I use lens anyway to cope with deep hierarchies of records describing events, so it's not much of a problem there. Thanks! On 07/13/2015 08:03 PM, Niklas Haas wrote:
For this specific use case, you can also consider list comprehensions:
[ x | x@(DataDefinition _) <- tlds ]
I personally greatly prefer this over something like ‘filter’ + an ugly lambda, especially if you can use the list comprehension for the rest of your processing as well. -- Nikolay.

Concerning monad patterns, I was thinking of expressions like these:
do SomeEvent a <- streamOfEvents
...
Depending on the stream monad involved (including []), this can have the
desired semantics.
On Mon, 13 Jul 2015 21:01:54 +0300, Nikolay Amiantov
Ouch, I feel deeply ashamed for not thinking of that from the beginning! While not being a general solution "Pattern a -> a -> Bool" this covers almost all my use cases (with rest of processing, too) while requiring no extensions, no dependencies and overall being readable and "boring" in Sven's sense (at least I feel so -- comprehensions are being taught in every Haskell tutorial under the sun and are pretty self-describing). It remains a question of whether it's equally readable in monadic case ("huh? list comprehension? but... this is a Maybe/an Event!"), but in most my GUI/event-processing code I use lens anyway to cope with deep hierarchies of records describing events, so it's not much of a problem there. Thanks!
On 07/13/2015 08:03 PM, Niklas Haas wrote:
For this specific use case, you can also consider list comprehensions:
[ x | x@(DataDefinition _) <- tlds ]
I personally greatly prefer this over something like ‘filter’ + an ugly lambda, especially if you can use the list comprehension for the rest of your processing as well. -- Nikolay.

Hm, right, that's better. On 07/13/2015 09:10 PM, Niklas Haas wrote:
Concerning monad patterns, I was thinking of expressions like these:
do SomeEvent a <- streamOfEvents ...
Depending on the stream monad involved (including []), this can have the desired semantics.
-- Nikolay.

2015-07-13 13:45 GMT+02:00 Nikolay Amiantov
[...] 1. Use lens: `has _Left` 2. Make a function: `isLeft (Left _) = True; isLeft _ = False` 3. (When you need a lambda) Use LambdaCase: `\case Left _ -> True; _ -> False` [...]
http://www.extremeprogramming.org/rules/simple.html ;-) So IMHO a simple, old-skool '\x -> case x of Left _ -> True; _ -> False' (probably item 2.5 in the list above) is by far the "best" way: It doesn't use any kind of extension, it doesn't pull in a dozen of packages for a trivial task, and is readable by anyone. My personal experience is that things which look very clever and advanced (like using meta/reflection facilities) only increase the WTF factor in the long run. Those facilities have their uses, but they come with a heavy cost which must be justified somehow. Boring code is good code! :-D

http://www.extremeprogramming.org/rules/simple.html ;-) So IMHO a simple, old-skool '\x -> case x of Left _ -> True; _ -> False' (probably item 2.5 in the list above) is by far the "best" way: It doesn't use any kind of extension, it doesn't pull in a dozen of packages for a trivial task, and is readable by anyone. My personal experience is that things which look very clever and advanced (like using meta/reflection facilities) only increase the WTF factor in the long run. Those facilities have their uses, but they come with a heavy cost which must be justified somehow. Boring code is good code! :-D
+1 for readability That's the problem with Haskell. You can do things in so many beautiful and wondrous ways that you tend to get lost very easily.
participants (7)
-
Adam Bergmark
-
Erik Hesselink
-
Nikita Karetnikov
-
Niklas Haas
-
Nikolay Amiantov
-
Silvio Frischknecht
-
Sven Panne