[Haskell-cafe] MultiCase alternative
Baa
aquagnu at gmail.com
Thu Jun 15 14:58:58 UTC 2017
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.
More information about the Haskell-Cafe
mailing list