Pattern synonym type flexibility

David Feuer david.feuer at gmail.com
Wed Apr 20 21:17:26 UTC 2016


Think about it this way. The matching aspect of a pattern synonym is
basically about defining a function to a somewhat weird type, except of
course optimized and maybe a bit more general.

data HList :: [*] -> * where
  HNil :: HList '[]
  HCons :: a -> HList as -> HList (a ': as)

data PatternResult :: ([*] -> Constraint) -> * where
  PatternResult :: provides ts => HList ts -> PatternResult provides

type Matcher requires provides = forall x . requires x => x ->
PatternResult provides

The smart constructor side of a pattern synonym is much, much simpler! It's
just a regular old Haskell value! The only special bit is that it's
treated, syntactically, as a constructor. There's simply nothing else worth
saying about it, so the less said the better.
On Apr 20, 2016 1:48 PM, "David Feuer" <david.feuer at gmail.com> wrote:

> I don't know what that means. There's no way to enforce duality at the
> term level. Enforcing it at the type level prevents me from doing what I
> want and serves no apparent purpose. Remember that pattern synonyms are all
> about providing nice syntax, not adding essential expressiveness.
> On Apr 20, 2016 1:41 PM, "Carter Schonwald" <carter.schonwald at gmail.com>
> wrote:
>
> Shouldn't the design simply be both directions are the dual of the other,
> and pure in some sense ?
>
>
> On Wednesday, April 20, 2016, David Feuer <david.feuer at gmail.com> wrote:
>
>> To some degree, it probably could be. But I believe that imposing any
>> substantial relationship between the smart constructor and the pattern
>> synonym is likely to fall squarely into the category of things that are
>> subtle, hard, and almost completely useless. In the arrangement I
>> suggested, people would be free to do some things that "don't make sense",
>> and that doesn't bother me in the least.
>> On Apr 20, 2016 1:27 PM, "Carter Schonwald" <carter.schonwald at gmail.com>
>> wrote:
>>
>>> Would that duality be related to the given vs wanted constraints ?
>>>
>>> On Wednesday, April 20, 2016, David Feuer <david.feuer at gmail.com> wrote:
>>>
>>>> As far as I can tell from the 7.10 documentation, it's impossible to
>>>> make a bidirectional pattern synonym used as a constructor have a
>>>> different type signature than when used as a pattern. Has this been
>>>> improved in 8.0? I really want something like
>>>>
>>>> class FastCons x xs | xs -> x where
>>>>   fcons :: x -> xs -> xs
>>>> class FastViewL x xs | xs -> x where
>>>>   fviewl :: xs -> ViewL x xs
>>>>
>>>> pattern x :<| xs <- (fviewl -> ConsL x xs) where
>>>>   x :<| xs = fcons x xs
>>>>
>>>> This would allow users to learn just *one* name, :<|, that they can
>>>> use for sequences that are consable or viewable even if they may not
>>>> be the other.
>>>>
>>>> If this is not yet possible, then I think the most intuitive approach
>>>> is to sever the notions of "pattern synonym" and "smart constructor".
>>>> So I'd write
>>>>
>>>> pattern x :<| xs <- (fviewl -> ConsL x xs)
>>>> constructor (:<|) = fcons
>>>>
>>>> The current syntax could easily be desugared to produce *both* a
>>>> pattern synonym and a smart constructor in the bidirectional case.
>>>> _______________________________________________
>>>> ghc-devs mailing list
>>>> ghc-devs at haskell.org
>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>>
>>>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20160420/79c91d0f/attachment-0001.html>


More information about the ghc-devs mailing list