[Haskell-cafe] why OverloadedTuples extension is missing?
Carter Schonwald
carter.schonwald at gmail.com
Mon Jan 17 13:08:15 UTC 2022
In some respects, there’s another path: further generalizing overloaded
lists with the right machinery for list syntax to support hlists and sized
lists!
I prototyped out a possible type class for this that predates pattern
synonyms and I believe it could be made even nicer with pattern synonyms
https://github.com/cartazio/HetList/blob/master/HetList.hs
Here’s the example code above!
On Thu, Jan 13, 2022 at 8:06 PM Viktor Dukhovni <ietf-dane at dukhovni.org>
wrote:
> On Thu, Jan 13, 2022 at 07:50:02PM -0500, Jeffrey Brown wrote:
> > You can get very close -- specifically, to within two extra characters --
> > to the brevity you're imagining without introducing any new extensions:
> >
> > data Foo = Foo Int Int
> > deriving (Show)
> >
> > f :: (Int, Int) -> Foo
> > f = uncurry Foo
> >
> > g :: Int -> Int -> Foo
> > g = Foo
>
> {-# LANGUAGE PatternSynonyms #-}
>
> pattern F :: Int -> Int -> Foo
> pattern F f s = Foo f s
>
> Which abbreviates a frequently used constructor, and works in pattern
> matches too.
>
> λ> case F 4 "2" of { F x y -> show x ++ y }
> "42"
>
> But the original question is really about logical completeness of
> overloading primitives, not about work-arounds, so bottom line I too
> don't think that overloading tuples is justified, since this breaks
> extensibility if constructor type signatures later become ambiguous, I
> don't think the idea has sufficient merit.
>
> --
> Viktor.
> _______________________________________________
> 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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20220117/fc2b2269/attachment.html>
More information about the Haskell-Cafe
mailing list