
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 筑波大学数理物質科学研究科 数学専攻 博士後期課程二年 ----------------------------------------------