[Haskell-cafe] why OverloadedTuples extension is missing?

Jeffrey Brown jeffbrown.the at gmail.com
Fri Jan 14 00:50:02 UTC 2022


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

`f` is almost what you wanted. `g` will in many situations be terser.

On Thu, Jan 13, 2022 at 5:12 PM Daneel Yaitskov <dyaitskov at gmail.com> wrote:

> Cafe,
>
> There is a group of GHC extensions and complementary classes
> to make writing Haskell code a bit sweeter such as:
>  - {} - Num (fromIntegral)
>  - OverloadedStrings - IsString
>  - OverloadedLists - IsList
>
> So I have an inductive question - why there is no OverloadedTuples?
> I haven't found a discussion thread about this topic.
>
> I could imagine following tuple syntax interpretation:
>
> {-# LANGUAGE OverloadedTuples #-}
>
> data Foo = FooA Int String | FooB String Foo deriving (Show, Eq, IsTuple)
>
> mkFoo :: Foo
> mkFoo = (1, "hello")
>
> mkFoo2 :: Foo
> mkFoo = ("abc", (1, "hello"))
>
> Sometimes expected type name is known without data constructor.
> So such expression is more concise.
>
>
>
> --
>
> Best regards,
> Daniil Iaitskov
>
>
>
> _______________________________________________
> 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.



-- 
Jeff Brown | Jeffrey Benjamin Brown
LinkedIn <https://www.linkedin.com/in/jeffreybenjaminbrown>   |   Github
<https://github.com/jeffreybenjaminbrown>   |   Twitter
<https://twitter.com/carelogic>  |  Facebook
<https://www.facebook.com/mejeff.younotjeff>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20220113/eaefbcaf/attachment.html>


More information about the Haskell-Cafe mailing list