<div dir="ltr">The main thing Baldur had asked me about was if it makes sense to talk about patterns that are parameterized by expressions in places.<div><br></div><div>I agree that the thought is very poorly fleshed out, but as a motivation, in some sense the previous form of view patterns already do this.</div>
<div><div><br></div><div>Consider (->), which takes in an expression to apply on the left and a pattern for what to match against the result of it on the right.</div><div><br></div></div><div>The question then becomes can we allow this for arbitrary patterns?</div>
<div><br></div><div>There are a number of use cases for these. For example, </div><div><br></div><div>A pattern to match a regular expression might look like</div><div><br></div><div>Foo (x :~= "ab*")</div><div>
<br></div><div><div>where you want "ab*" to be passed as a parameter to the code for the pattern synonym (:~=), not be something it is binding.<br></div></div><div><br></div><div>This then speaks to needing some notion of mode for the different parameters.</div>
<div><br></div><div>One of the reasons I'm under-excited about pattern synonyms is we already built all the machinery for working with prisms in lens to generalize them. =)<br></div><div><br></div><div>In lens we have a combinator 'preview :: Prism' s a -> s -> Maybe a'.</div>
<div><br></div><div>As a straw man proposal:</div><div><br></div><div>It'd be nice to be able to do something like</div><div><br></div><div>pattern (Match p a) <- (preview p -> Just a)</div><div><br></div><div>and have it take the arguments that go to the left hand side of the -> as expressions, not patterns so that that can compile.</div>
<div><br></div><div><div>Now, I'm somewhat dubious that it worth the pain to embellish the pattern language with something this complicated, but in some sense we already have a lot of the machinery to support it. e.g. IIRC we parse patterns first as expressions then convert them.<br>
</div><div><br></div></div><div>-Edward</div></div><div class="gmail_extra"><br><br><div class="gmail_quote">On Mon, Jun 23, 2014 at 4:39 AM, Simon Peyton Jones <span dir="ltr"><<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>></span> wrote:<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Baldur<br>
<br>
(My name is Simon, not Peyton, incidentally.  "Peyton Jones" is my last name.)<br>
<br>
I'm glad you are enjoying pattern synonyms. Thanks for identifying #9226, which I guess is you.<br>
<br>
I honestly don't understand your pattern family proposal.  Would you like to write a wiki page somewhere describing the<br>
  syntax<br>
  typing (static semantics)<br>
  desugaring (dynamic semantics)<br>
as clearly and precisely as you can, independent of prisms, and using the simplest possible examples to illustrate.  By all means say that prisms are a more advanced application, and give examples to show how.  But in general to specify a language feature you need a lot more than a couple of examples!<br>

<br>
Then you can ask GHC users what they think.<br>
<br>
I have to say that I'm cautious about adding further features to pattern synonyms until we've gotten more user experience with what we have.  (Do you think the explicitly bidirectional stuff on the wiki page is important?  To me that seems like the first thing a user might stumble over.)<br>

<br>
Incidentally, I'd really like to replace view patterns with <a href="https://ghc.haskell.org/trac/ghc/wiki/ViewPatternsAlternative" target="_blank">https://ghc.haskell.org/trac/ghc/wiki/ViewPatternsAlternative</a>, another thing that is awaiting cycles.<br>

<br>
Copying ghc-devs for interest<br>
<br>
Thanks<br>
<br>
Simon<br>
<br>
<br>
<br>
| -----Original Message-----<br>
| From: Baldur Blöndal [mailto:<a href="mailto:baldurpet@gmail.com">baldurpet@gmail.com</a>]<br>
| Sent: 18 June 2014 04:31<br>
| To: Simon Peyton Jones; <a href="mailto:gergo@erdi.hu">gergo@erdi.hu</a><br>
| Subject: New GHC feature proposal: Pattern families<br>
|<br>
| Hello Peyton and Gergo,<br>
|<br>
| I'm a master's student at Chalmers, a minor GHC contributor and have<br>
| written about the pattern synonyms extension<br>
| (<a href="https://www.fpcomplete.com/user/icelandj/Pattern%20synonyms" target="_blank">https://www.fpcomplete.com/user/icelandj/Pattern%20synonyms</a>) and<br>
| included is a proposal for an extension I call “pattern families”<br>
| allowing users to create patterns parameterized by an expression. I feel<br>
| like patterns don't get nearly as much attention as the type system and<br>
| this is my attempt to balance things out :)<br>
|<br>
| I discussed the proposal with Edward Kmett who suggested an example with<br>
| prisms and that I contact you two for comments. The syntax is still in<br>
| flux.<br>
|<br>
| Some motivating examples for your consideration.<br>
|<br>
|     PRISM PATTERNS<br>
|<br>
| Edward suggested a pattern to match a prism which would look like this:<br>
| <edwardk> an example where you want it is if you want to use a pattern<br>
| synonym to match a prism <edwardk> foo (Match _Left a) = ...<br>
| [...]<br>
| <edwardk> the example of a single pattern that can match every prism<br>
| would be a nice example<br>
|<br>
| which would be quite easy to implement:<br>
|<br>
| | pattern Match prism a ← ((^? prism) → Just a)<br>
| |<br>
| | bar :: Either c (Either a b) → a<br>
| | bar (Match (_Right._Left) a) = a<br>
| | bar _ = error "Not a Right (Left ...)"<br>
|<br>
| This can be used for any prism:<br>
| | jsonBlob = "[{\"someObject\": {\"version\": [1,0,3]}}]"<br>
| |<br>
| | foo (Match (nth 0) (Match (key "someObject") (Match (key "version")<br>
| (Match (nth 1) a)))) = a<br>
| | ghci> foo jsonBlob<br>
| | Number 0.0<br>
|<br>
| and defining more specilized patterns we can make it terser:<br>
| | pattern Get i a ← ((^? nth i) → Just a) pattern Key str a ← ((^? key<br>
| | str) → Just a)<br>
| |<br>
| | baz (Get 0 (Key "someObject" (Key "version" (Get 1 a)))) = a baz (0<br>
| | `Get` "someObject" `Key` "version" `Key` 1 `Get` a) = a baz (a :→<br>
| | "someObject" :⇒ "version" :⇒ 1 :→ a) = a<br>
| where<br>
| | pattern i   :→ a ← Get i a<br>
| | pattern str :⇒ a ← Key str a<br>
|<br>
| So this is excellent for pattern matching on any sort of nested<br>
| structure: records, JSON, XML, HTML, ASTs, … Since this also supports<br>
| pattern matching on any value that satisfies a predicate.<br>
|<br>
|     N+K PATTERNS<br>
| Generalizing n+k patterns: We create a pattern family indexed by its<br>
| first argument:<br>
|<br>
| | pattern (a :+) :: Num a ⇒ a → a<br>
| |               k :+ n ← (unSucc k → Just n) -- [1] unSucc defined below<br>
|<br>
| where (a :+) indicates that 'k' is an index of the pattern family<br>
| allowing it to be supplied to the view pattern.<br>
| The pattern can be used as follows:<br>
| | fact 0          = 1<br>
| | fact m@(1 :+ n) = m * fact n<br>
|<br>
|     PATTERN MATCHING REGULAR EXPRESSIONS The pattern (:=~) is inspired<br>
| by the operator (=~) from Text.Regex.Posix.Wrap (regex-posix), note that<br>
| its second argument is the index here:<br>
| | pattern (:=~ String) :: RegexContext Regex a c ⇒ a → c<br>
| |               n :=~ pattern ← ((=~ pattern) → n)<br>
|<br>
| Used as:<br>
| | vowels :: RegexContext Regex src tgt ⇒ src → tgt vowels (n :=~<br>
| | "[aeiou]") = n<br>
| |<br>
| | ghci> vowels "honorificabilitudinitatibus" ∷ Int<br>
| | 13<br>
|<br>
| where you can of course pattern match on the resulting value:<br>
|<br>
| | has5Vowels :: String → Int<br>
| | has5Vowels (5 :=~ "[aeiou]") = True<br>
| | has5Voewls _                         = False<br>
|<br>
|     TYPE INFERENCE<br>
| Here is an example of a snippet inferring the type of an if expression:<br>
|<br>
| | infer Γ (If cond t e) =<br>
| |   case (infer Γ cond, infer Γ t, infer Γ e) of<br>
| |     (Just TBool, Just τ₁, Just τ₂)<br>
| |       | τ₁ == τ₂ = Just t₁<br>
|<br>
| Here is how it might look with pattern families:<br>
|<br>
| | infer Γ (If (Infer Γ TBool) (Infer Γ τ₁) (Infer Γ τ₂))<br>
| |   | τ₁ == τ₂ = Just τ₁<br>
|<br>
| (or even nicer if we use (:⇑) = Infer)<br>
| | infer Γ (If (Γ :⇑ TBool) (Γ :⇑ τ₁) (Γ :⇑ τ₂)) …<br>
|<br>
|     IMPLEMENTATION<br>
| From what I can see this is a relatively straight-forward translation<br>
| into view patterns where a variable bound by a view pattern is an<br>
| “index” to the pattern family and unbound variables are regular<br>
| patterns. In the examples above I use special syntax for the index where<br>
| the type is included but even without any annotation it can be inferred<br>
| from context.<br>
|<br>
| If the proposal is fine by you I offer to do the implementation work,<br>
| all feedback welcome!<br>
|<br>
| Best regards,<br>
| Baldur Blöndal<br>
|<br>
|     APPENDIX<br>
| | unSucc :: Int → Int → Maybe Int<br>
| | unSucc k n<br>
| |     | n - k < 0   = Nothing<br>
| |     | otherwise = Just (n - k)<br>
| |<br>
_______________________________________________<br>
ghc-devs mailing list<br>
<a href="mailto:ghc-devs@haskell.org">ghc-devs@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/ghc-devs" target="_blank">http://www.haskell.org/mailman/listinfo/ghc-devs</a><br>
</blockquote></div><br></div>