MultiCase alternative

Hello, Everyone! As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like: case x of A a -> .. B b -> .. C c -> --same-- D c -> --same-- and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions. Something like "(C|D) c -> ..." === Best regards, Paul

case x of A a -> .. B b -> .. C c -> f c D d -> f d where f cd = ... On 15 Jun 2017, at 15:11, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On 2017-06-15 16:11, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Create a function. Regards,

Hmm, seems there is a way: {-# LANGUAGE ViewPatterns #-} isCD (C c) = c isCD (D c) = c case x of A a -> .. B b -> .. (isCD -> x) -> ..process-x..
On 2017-06-15 16:11, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Create a function.
Regards,
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Paul,
I'm nit experienced in Haskell, so I don't have a solution. But the
following keywords spring to mind:
Ignore the syntactic sugar and see if any of the alternative syntaxes are
more flexible
https://wiki.haskell.org/Case
Create a DSL.
Greetings,
Bram
On Thu, 15 Jun 2017, 16:13 Baa,
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Paul, This looks like the or-patterns proposal: https://github.com/ghc-proposals/ghc-proposals/pull/43 I'm not sure what you call MultiCase though. Is the above what you were refering to? Here are some alternatives with current Haskell, the first one is to be preferred: - Factor out the alternatives in a function. ... case x of ... C c -> f c D c -> f c where f c = ... - If your C and D constructors have similar enough meanings, you might want to fuse them into a single constructor with a separate tag: data T = A TA | B TB | CD CorD TC data CorD = C | D so that you can write case x of ... CD _ c -> ... - With pattern synonyms + view patterns, although it takes some effort to set up and confuses the exhaustiveness checker. matchCorD :: T -> Maybe C matchCorD (C c) = Just c matchCorD (D c) = Just c matchCorD _ = Nothing pattern CD :: C -> T pattern CD c <- (matchCorD -> Just c) you can now write case x of ... CD c -> ... Li-yao On 06/15/2017 10:11 AM, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hello, Li-yao! I mean this: https://wiki.haskell.org/MultiCase
Hi Paul,
This looks like the or-patterns proposal:
https://github.com/ghc-proposals/ghc-proposals/pull/43
I'm not sure what you call MultiCase though. Is the above what you were refering to?
Here are some alternatives with current Haskell, the first one is to be preferred:
- Factor out the alternatives in a function.
... case x of ... C c -> f c D c -> f c where f c = ...
- If your C and D constructors have similar enough meanings, you might want to fuse them into a single constructor with a separate tag:
data T = A TA | B TB | CD CorD TC data CorD = C | D
so that you can write
case x of ... CD _ c -> ...
- With pattern synonyms + view patterns, although it takes some effort to set up and confuses the exhaustiveness checker.
matchCorD :: T -> Maybe C matchCorD (C c) = Just c matchCorD (D c) = Just c matchCorD _ = Nothing
pattern CD :: C -> T pattern CD c <- (matchCorD -> Just c)
you can now write
case x of ... CD c -> ...
Li-yao
On 06/15/2017 10:11 AM, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hello, Li-yao! I mean this: https://wiki.haskell.org/MultiCase
Hi Paul,
This looks like the or-patterns proposal:
You can see on github that it's just "dormant". But the examples in this thread made me have an interesting, even more general idea: we have functions on term-level and type-level – why not on pattern-level? Here's a very rough draft of what I imagine: {-# LANGUAGE PatternFamilies, PatternKinds #-} data Dt a = A a | B a | C a | D a deriving ( Show ) pattern (∥) ∷ (Pattern a → T) → (Pattern a → T) → (T → U) → (a → U) pattern (a ∥ _) f = f a pattern (_ ∥ b) f = f b infixl 2 pattern ∥ foo ∷ (Show a) ⇒ Dt a → String foo (A a) = … foo (B b) = … foo (C c ∥ D d) = … No, I don't think that's worth drawing up a proposal yet. I just want to document the idea. Maybe it can inspire someone who's building their own language or something. Cheers, MarLinn

There is another elementary alternative. If you need to treat C and D the same in just one place, you don't really have a problem. If you need to treat them the same in several places, do this: data T a b c = A a | B b | C c | D c -- existing type data Which a b c = A' a | B' b | CD Bool c which :: T a b c -> Which a b c which (A a) = A' a which (B b) = B' b which (C c) = CD False c which (D c) = CD True c then case which $ x of A' a -> B' b -> CD _ c -> ... If you want to merge the C and D cases often, I like this approach, otherwise the C c -> f c D c -> f c where f c = ... approach is better.

Hello, Richard. As a result I did with "...where f c = ..." :) A way with "which" is interesting but duplicates unique constructors (A -> A', B -> B'). Interesting, is F# can solve this problem with active pattern? Pattern matching in Haskell does not seem enought flexible, for example, if I have `data D = D a b c d`, how can I match it without placeholders for `D` args? Something like `D...`? I need to write `D _ _ _ _` if I want to match without to bind args, right? I want to say, that may be (I'm not sure, I'm newbie in Haskell) active patterns can solve this and many other problems, may be active-pattern + reflection. For last example, I create pattern `IsD` in place where `D` is defined and use it - to be more independent on D args (D can be record and I can use getters/lens only to access its args, so I need a way to be similar independent from its args in pattern-matching too). But again, I'm not sure about right approaches - I'm newbie yet. === Best regards, Paul
There is another elementary alternative. If you need to treat C and D the same in just one place, you don't really have a problem. If you need to treat them the same in several places, do this:
data T a b c = A a | B b | C c | D c -- existing type
data Which a b c = A' a | B' b | CD Bool c
which :: T a b c -> Which a b c which (A a) = A' a which (B b) = B' b which (C c) = CD False c which (D c) = CD True c
then case which $ x of A' a -> B' b -> CD _ c -> ...
If you want to merge the C and D cases often, I like this approach, otherwise the C c -> f c D c -> f c where f c = ... approach is better.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

You can record match like so "x@D{}" but then you'll need someway to access
the contents of "x" (if you're interested in the contents, that is).
On Fri, Jun 16, 2017 at 3:43 PM, Baa
Hello, Richard.
As a result I did with "...where f c = ..." :) A way with "which" is interesting but duplicates unique constructors (A -> A', B -> B').
Interesting, is F# can solve this problem with active pattern?
Pattern matching in Haskell does not seem enought flexible, for example, if I have `data D = D a b c d`, how can I match it without placeholders for `D` args? Something like `D...`? I need to write `D _ _ _ _` if I want to match without to bind args, right?
I want to say, that may be (I'm not sure, I'm newbie in Haskell) active patterns can solve this and many other problems, may be active-pattern + reflection. For last example, I create pattern `IsD` in place where `D` is defined and use it - to be more independent on D args (D can be record and I can use getters/lens only to access its args, so I need a way to be similar independent from its args in pattern-matching too).
But again, I'm not sure about right approaches - I'm newbie yet.
=== Best regards, Paul
There is another elementary alternative. If you need to treat C and D the same in just one place, you don't really have a problem. If you need to treat them the same in several places, do this:
data T a b c = A a | B b | C c | D c -- existing type
data Which a b c = A' a | B' b | CD Bool c
which :: T a b c -> Which a b c which (A a) = A' a which (B b) = B' b which (C c) = CD False c which (D c) = CD True c
then case which $ x of A' a -> B' b -> CD _ c -> ...
If you want to merge the C and D cases often, I like this approach, otherwise the C c -> f c D c -> f c where f c = ... approach is better.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi cafe, Here's another solution using lens (and prisms): ``` {-# LANGUAGE PatternSynonyms, RankNTypes, TemplateHaskell, ViewPatterns #-} module Main where import Control.Lens data F = C Int | D Int | E String Int | F Int | G String deriving (Read, Show, Eq, Ord) makePrisms ''F match = flip (^?) main :: IO () main = case C 2 of (match (_C <|?> _D <|?> _E._2 <|?> _F) -> Just i) -> print i G s -> putStrLn s infixl 8 <|?> (<|?>) :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b (<|?>) = failing ```
2017/06/16 14:55、Clinton Mead
のメール: You can record match like so "x@D{}" but then you'll need someway to access the contents of "x" (if you're interested in the contents, that is).
On Fri, Jun 16, 2017 at 3:43 PM, Baa
wrote: Hello, Richard. As a result I did with "...where f c = ..." :) A way with "which" is interesting but duplicates unique constructors (A -> A', B -> B').
Interesting, is F# can solve this problem with active pattern?
Pattern matching in Haskell does not seem enought flexible, for example, if I have `data D = D a b c d`, how can I match it without placeholders for `D` args? Something like `D...`? I need to write `D _ _ _ _` if I want to match without to bind args, right?
I want to say, that may be (I'm not sure, I'm newbie in Haskell) active patterns can solve this and many other problems, may be active-pattern + reflection. For last example, I create pattern `IsD` in place where `D` is defined and use it - to be more independent on D args (D can be record and I can use getters/lens only to access its args, so I need a way to be similar independent from its args in pattern-matching too).
But again, I'm not sure about right approaches - I'm newbie yet.
=== Best regards, Paul
There is another elementary alternative. If you need to treat C and D the same in just one place, you don't really have a problem. If you need to treat them the same in several places, do this:
data T a b c = A a | B b | C c | D c -- existing type
data Which a b c = A' a | B' b | CD Bool c
which :: T a b c -> Which a b c which (A a) = A' a which (B b) = B' b which (C c) = CD False c which (D c) = CD True c
then case which $ x of A' a -> B' b -> CD _ c -> ...
If you want to merge the C and D cases often, I like this approach, otherwise the C c -> f c D c -> f c where f c = ... approach is better.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
----- 石井 大海 --------------------------- konn.jinro@gmail.com 筑波大学数理物質科学研究科 数学専攻 博士後期課程二年 ----------------------------------------------

Hello, Richard.
As a result I did with "...where f c = ..." :) A way with "which" is interesting but duplicates unique constructors (A -> A', B -> B').
Yes, but if you *often* want to group constructors together, it's still a good idea. The alternative, which has already been suggested, is to group them together in the original type, but you might want to classify the alternatives in more than one way.
Interesting, is F# can solve this problem with active pattern?
Probably. See https://docs.microsoft.com/en-us/dotnet/fsharp/language-reference/active-pat... for details of active patterns in F#. The syntax is seriously twisted. You *can* associate data with the partitions, but it's really not obvious. If you want to classify something more than 7 ways F# is unhelpful. F# active patterns are not entirely unlike view patterns https://ghc.haskell.org/trac/ghc/wiki/ViewPatterns only stranger.
Pattern matching in Haskell does not seem enought flexible, for example, if I have `data D = D a b c d`, how can I match it without placeholders for `D` args? Something like `D...`? I need to write `D _ _ _ _` if I want to match without to bind args, right?
Yes, but (a) in all seriousness, that's not much of a problem, surely and (b) there is an alternative. If you write instead data D a b c d = D { f1 :: a, f2 :: b, f3 :: c, f4 :: d } then you can abbreviate patterns like this: f (D{}) = () g (D{f1 = x}) = x If you have enough fields for counting the placeholders to be a problem then you have enough fields that you really *ought* to be naming them anyway. The problem with making pattern matching overly flexible is that people have to read and understand this stuff. It's a bit like regular expressions: POSIX regular expressions can be implemented to take linear time (by simulating an NDFA), but they are a bit limited, whereas Perl regular expressions are very expressive indeed, but they can all too easily take exponential time, and it isn't easy for John and Jane Doe programmers to tell when that is going to happen. Generally speaking, before proposing language changes, it's always a good idea to see if you can solve your problem by factoring out common stuff into a new function (or type, or typeclass) first.

On Fri, Jun 16, 2017 at 2:21 AM,
If you write instead
data D a b c d = D { f1 :: a, f2 :: b, f3 :: c, f4 :: d }
then you can abbreviate patterns like this:
f (D{}) = ()
As a special case, you can use the no-fields record pattern Cons {} with *any* constructor, regardless of whether it was defined with record syntax or whether it has parameters. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Fri, Jun 16, 2017 at 2:21 AM,
wrote: If you write instead
data D a b c d = D { f1 :: a, f2 :: b, f3 :: c, f4 :: d }
then you can abbreviate patterns like this:
f (D{}) = ()
As a special case, you can use the no-fields record pattern Cons {} with *any* constructor, regardless of whether it was defined with record syntax or whether it has parameters.
Aha, I checked it, good.

Interesting, is F# can solve this problem with active pattern?
Probably. See https://docs.microsoft.com/en-us/dotnet/fsharp/language-reference/active-pat... for details of active patterns in F#. The syntax is seriously twisted. You *can* associate data with the partitions, but it's really not obvious. If you want to classify something more than 7 ways F# is unhelpful. F# active patterns are not entirely unlike view patterns https://ghc.haskell.org/trac/ghc/wiki/ViewPatterns only stranger.
view patterns are "active" too, sure while they are callable :) Unfortunately I am not so familiar with both to compare them in detail. Are they equal in capacity/in general or only partially? I mean, can Haskell view patterns cover all possibilities of Active Patterns of F#?
Pattern matching in Haskell does not seem enought flexible, for example, if I have `data D = D a b c d`, how can I match it without placeholders for `D` args? Something like `D...`? I need to write `D _ _ _ _` if I want to match without to bind args, right?
Yes, but (a) in all seriousness, that's not much of a problem, surely and (b) there is an alternative. If you write instead
data D a b c d = D { f1 :: a, f2 :: b, f3 :: c, f4 :: d }
then you can abbreviate patterns like this:
f (D{}) = ()
g (D{f1 = x}) = x
If you have enough fields for counting the placeholders to be a problem then you have enough fields that you really *ought* to be naming them anyway.
That it is, good! Thanks for this hint!
The problem with making pattern matching overly flexible is that people have to read and understand this stuff. It's a bit like regular expressions: POSIX regular expressions can be implemented to take linear time (by simulating an NDFA), but they are a bit limited, whereas Perl regular expressions are very expressive indeed, but they can all too easily take exponential time, and it isn't easy for John and Jane Doe programmers to tell when that is going to happen.
Sure, true.
Generally speaking, before proposing language changes, it's always a good idea to see if you can solve your problem by factoring out common stuff into a new function (or type, or typeclass) first.
Sure, but there is another point of view here. Alternative is to have flexible but elegant syntax embedded in language, instead of many-many extensions for any possibility - they "fragment" language. But of course this is controversial and ambiguous :-) === Best regards, Paul

On Fri, Jun 16, 2017 at 6:12 AM, Baa
Sure, but there is another point of view here. Alternative is to have flexible but elegant syntax embedded in language, instead of many-many extensions for any possibility - they "fragment" language. But of course this is controversial and ambiguous :-)
The active patterns of F# that you mentioned can be seen as a counterargument :) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 16/06/2017, at 10:15 PM, Brandon Allbery
wrote: On Fri, Jun 16, 2017 at 6:12 AM, Baa
wrote: Sure, but there is another point of view here. Alternative is to have flexible but elegant syntax embedded in language, instead of many-many extensions for any possibility - they "fragment" language. But of course this is controversial and ambiguous :-) The active patterns of F# that you mentioned can be seen as a counterargument
There's an interesting irony here. I'm reading the paper "Extensible Pattern Matching via a Lightweight Language Extension" by Syme, Neverov, and Margetson. The authors propose active patterns as a way of allowing functional code to work with objects using pattern matching. The irony is that doing this clearly violates the Object-Oriented Programming principle "Tell, Don't Ask". That is, according to the OOP gurus, if you have some sort of if or case that classifies an object in some way, you are doing it wrong. That variant- dependent behaviour belongs in the object. I'm agnostic about most OO dogma, so don't take this as my claim.

"Baa"
view patterns are "active" too, sure while they are callable :) Unfortunately I am not so familiar with both to compare them in detail. Are they equal in capacity/in general or only partially? I mean, can Haskell view patterns cover all possibilities of Active Patterns of F#?
I'm not sure. The idea of something like views has been around for a while. For all I know, F# might have got there first. There were quite a few proposals before all the warts got frozen off and we were blessed with the present deceptively simple scheme. I have a bit of trouble trying to make sense of some of Microsoft's F# documentation, though. Let's compare them! Do you use an ordinary function definition or some weird syntax? Haskell: you use an ordinary function that can be used like an ordinary function AND can be used in (view -> pattern) form F# : weird syntax, not usable as an ordinary function. Is the classification result an ordinary data type that can be used by multiple views, or does each user-defined classifier have to have a different result type? Haskell: it's an ordinary type. F# : if I've understood correctly, no, each active pattern defines its own union type (with parts of the definition scattered). Is it obvious to a human reader when we're doing a plain old "what constructor is this" match and when something fancy is happening? Haskell: yes, with pretty minimal overhead. F# : no, by design. Can the two approaches do the same things? Based on my present wholly inadequate understanding of F# active patterns, Haskell view patterns can do everything they do, but not the other way around. But I must stress that I regard my understanding of F# active patterns as inadequate. Let's take the ABCD example. data ABCD a b c = A a | B b | C c | D c data ABC a b c = A' A | B' b | C c Bool abc :: ABCD a b c -> ABC a b c abc (A a) = A' a abc (B b) = B' b abc (C c) = C' c False abc (D c) = C' c True f (abc -> A' a) = ... f (abc -> B' b) = ... f (abc -> C' c _) = ... This will be compiled as if it read f x = case abc x of {A' a -> ... ; B' b -> ... ; C' c _ -> ...} You define an ordinary type, you define an ordinary function, and you call that ordinary function inside patterns. type abcd<'a,'b,'c> = A of 'a | B of 'b | C of 'c | D of 'c;; let (|A1|B1|C1|) x = match x with | A a -> A1(a) | B b -> B1(b) | C c -> C1(c,false) | D c -> C1(c,true);; let f x = match x with | A1 a -> 1 | B1 b -> 2 | C1 (c,_) -> 3;; This F# code has been tested in fsi 4.1. You define an anonymous ADT with the constructors on one side of the = and their arguments on the other, you define an anonymous function, which is basically the same as the view function, and you call the anonymous function inside pattern matching.
Generally speaking, before proposing language changes, it's always a good idea to see if you can solve your problem by factoring out common stuff into a new function (or type, or typeclass) first.
Sure, but there is another point of view here. Alternative is to have flexible but elegant syntax embedded in language, instead of many-many extensions for any possibility - they "fragment" language. But of course this is controversial and ambiguous :-)
I agree 100%. That's why I prefer Haskell to F#. View patterns are indeed flexible but elegant. However, in this particular example, they are not actually needed. <quote> SML/NJ has also extended the syntax of patterns to allow ``or-patterns.'' The basic syntax is: (apat1 | ... | apatn) where the apati are atomic patterns. The other restriction is that the variables bound in each apati must be the same, and have the same type. </quote> The MLton compiler also (optionally) supports this. There has been a certain amount of pressure in the Erlang community to add a similar feature to Erlang. In fact, respected Erlang people have claimed to see a lot of repeated cases that OR patterns would avoid. Sometimes pain is Nature's way of telling you you're doing it wrong. If you find two cases in a data type being handled the same way in one place, is this a rare thing, or are they handled very similarly in many places? If so, why are they TWO cases instead of one with a subcase? There's a big problem with F# active patterns, which is shared by view patterns to a lesser degree. That is that a call to an active or view pattern may do arbitrary amounts of work, whereas (after forcing such evaluation as may be needed) ordinary pattern matching does an amount of work proportional to the size of the pattern. In Haskell, view pattern match syntax at least warns you that you *might* have a problem. What evil lurks in the heart of OR-patterns? Let Pi be the pattern (i,_) | (_,i) f P1 ... Pn (0,0) = True f _ ... _ _ = False g = f (1,1) (2,2) ... (n,n) (1,1) What stops this taking time exponential in n to decide which clause to use? And you certainly don't want the compiler to process this by expanding the alternatives out. (So far it has taken 3 minutes on a fast machine to not finish compiling these 3 lines of code... I fear the worst.) I have reluctantly come to the conclusion that OR-patterns fill a much-needed gap.

What evil lurks in the heart of OR-patterns?
Let Pi be the pattern (i,_) | (_,i) In SML,
fun f P1 ... Pn (0,0) = true | f _ ... _ _ = false fun g () = f (1,1) (2,2) ... (n,n) (1,1)
(So far it has taken 3 minutes on a fast machine to not finish compiling these 3 lines of code... I fear the worst.)
I killed it after 24 minutes on a 3.2 GHz machine. In Haskell, ok n (x,y) = x == n || y == n f (ok 1 -> True) ... (ok n -> True) (0,0) = true f _ _ _ = false g () = f (1,1) (2,2) ... (n,n) (1,1) compiled and ran in a flash. (Yes, I know that the Haskell version is "committed choice" and the SML/NJ version is "backtracking search", but that's the point: the *syntax* of OR-patterns may be simple but sorting out the *semantics* is not.)

Sometimes pain is Nature's way of telling you you're doing it wrong.
This. This not only goes for or-patterns, but also for the pain that leads you to use View Patterns. They are an interesting concept, and the indirection makes it more "fun" to think about. We like flexing our minds that little bit sometimes. But they are also easily abused to hide shortcomings of the underlying model instead of fixing them. And in the real world, that's often what they end up being used for. Almost all code I have seen that actually used View Patterns got more readable by refactoring. Don't get me wrong: I'm not saying they should never be used. But I've fallen into the trap of overusing this pattern myself, and almost always I regretted it and/or refactored. Of all the code I've seen there has maybe been a handful of instances where View Patterns actually contributed in a positive way. Call me a hypocrite after I brought up the ridiculous concept of "pattern-level functions" earlier in this thread, but that's the difference between theory and practice I suppose. Cheers, MarLinn

Let's take the ABCD example. data ABCD a b c = A a | B b | C c | D c data ABC a b c = A' A | B' b | C c Bool
You mean data ABC a b c = A' a | B' b | C' c Bool It is very pleasant when a person has such a wide horizon: you compared F#, SML, Erlang and Haskell, IMHO modern FP developer should have basic knowledge about these languages/cultures and to know about their trends/current researches. Example with SML 'OR'-pattern, am I right that this terrible compile time is due search on all permutations of patterns (func arguments)? But what is not obvious to me is what is compiler try to match: P1 P2 ... Pn (0,0) => True _ _ ... _ _ => False (1,1) (2,2) ... (n,n) (1,1) => False is not enought to do depth-first search and to go from P1 to last (0,0)? Or is it try to find all matches, not only one, first successful? May be I miss what is 'Pn', how it's defined. Your example with the introduction of a 'ABC' has good understandable semantic, if they can be united, there is a reason to combine them in new type, semantically it makes sense. And view pattern in your example "unwraps" underlying datatype value to be matched and bound. Good explanation, thanks for it! And from SML example I can understand that obvious solution to the forehead of "OR"-pattern matching can be problematic in practice... === Thanks again, best regards, Paul

Exactly! "C c | D d" looks super!
Hello, Li-yao! I mean this: https://wiki.haskell.org/MultiCase
Hi Paul,
This looks like the or-patterns proposal:
You can see on github that it's just "dormant". But the examples in this thread made me have an interesting, even more general idea: we have functions on term-level and type-level – why not on pattern-level?
Here's a very rough draft of what I imagine:
{-# LANGUAGE PatternFamilies, PatternKinds #-}
data Dt a = A a | B a | C a | D a deriving ( Show )
pattern (∥) ∷ (Pattern a → T) → (Pattern a → T) → (T → U) → (a → U) pattern (a ∥ _) f = f a pattern (_ ∥ b) f = f b
infixl 2 pattern ∥
foo ∷ (Show a) ⇒ Dt a → String foo (A a) = … foo (B b) = … foo (C c ∥ D d) = …
No, I don't think that's worth drawing up a proposal yet. I just want to document the idea. Maybe it can inspire someone who's building their own language or something.
Cheers, MarLinn
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi, You can combine ViewPatterns and PatternSynonyms to obtain this desired effect: {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE PatternSynonyms #-} data X a b c = A a | B b | C c | D c deriving (Show) cOrD :: X a b c -> Maybe c cOrD (A _) = Nothing cOrD (B _) = Nothing cOrD (C c) = Just c cOrD (D c) = Just c pattern CorD :: c -> X a b c pattern CorD c <- (cOrD -> Just c) main :: IO () main = do let -- x = A "An a" :: X String String String -- x = B "A b" :: X String String String x = C "A c" :: X String String String --x = D "A d" :: X String String String case x of A a -> putStrLn ("A:" ++ show a) B b -> putStrLn ("B:" ++ show b) CorD c -> putStrLn ("CorD:" ++ show c) Note that you lose completeness checking: Test.hs:30:4: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: (C _) (D _) Cheers, Sylvain On 15/06/2017 16:11, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hmm, Sylvain, this is more interesting than my variant. Thank you a lot!
Hi,
You can combine ViewPatterns and PatternSynonyms to obtain this desired effect:
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE PatternSynonyms #-}
data X a b c = A a | B b | C c | D c deriving (Show)
cOrD :: X a b c -> Maybe c cOrD (A _) = Nothing cOrD (B _) = Nothing cOrD (C c) = Just c cOrD (D c) = Just c
pattern CorD :: c -> X a b c pattern CorD c <- (cOrD -> Just c)
main :: IO () main = do let -- x = A "An a" :: X String String String -- x = B "A b" :: X String String String x = C "A c" :: X String String String --x = D "A d" :: X String String String
case x of A a -> putStrLn ("A:" ++ show a) B b -> putStrLn ("B:" ++ show b) CorD c -> putStrLn ("CorD:" ++ show c)
Note that you lose completeness checking:
Test.hs:30:4: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: (C _) (D _)
Cheers, Sylvain
On 15/06/2017 16:11, Baa wrote:
Hello, Everyone!
As I understand "MultiCase" proposal was not approved, so my question is: is there alternatives to multi-case? I have code like:
case x of A a -> .. B b -> .. C c -> --same-- D c -> --same--
and I want to merge code of "C c" with "D c" branch. Anywhere, in general: is any alternatives to make "OR"s in patterns? I don't see how to do it with pattern guards, pattern synonyms, views extensions and don't see another related extensions.
Something like "(C|D) c -> ..."
=== Best regards, Paul _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (12)
-
Baa
-
Bardur Arantsson
-
Bram Neijt
-
Brandon Allbery
-
Clinton Mead
-
Hiromi ISHII
-
Li-yao Xia
-
Malcolm Wallace
-
MarLinn
-
ok@cs.otago.ac.nz
-
Richard A. O'Keefe
-
Sylvain Henry