[Haskell-cafe] MultiCase alternative

Baa aquagnu at gmail.com
Fri Jun 16 05:27:09 UTC 2017


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:
> >>
> >> https://github.com/ghc-proposals/ghc-proposals/pull/43
> >>
> >>  
> 
> 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.


More information about the Haskell-Cafe mailing list