
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

We could potentially have this. It reminds me of Agda's record https://agda.readthedocs.io/en/v2.6.2.1/language/record-types.html#construct... syntax, where you can construct any record (which is like your tuple) with the keyword `record`. Is it worth having yet another feature in the language? I'm not sure, myself. Richard
On Jan 13, 2022, at 5:12 PM, Daneel Yaitskov
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.

I'm not sure I like the idea of Haskell trying to guess a constructor
to use from a tuple. What happens if multiple constructors could
match, for one?
On Thu, Jan 13, 2022 at 6:17 PM Richard Eisenberg
We could potentially have this. It reminds me of Agda's record syntax, where you can construct any record (which is like your tuple) with the keyword `record`.
Is it worth having yet another feature in the language? I'm not sure, myself.
Richard
On Jan 13, 2022, at 5:12 PM, Daneel Yaitskov
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.
_______________________________________________ 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.
-- brandon s allbery kf8nh allbery.b@gmail.com

`(,) :: forall a b c. (IsPair c, Fst c ~ a, Snd c ~ b)=> a → b → c`
Might be nice syntax for `data StrictPair a b = StrictPair !a !b`.
—
Sent from my phone with K-9 Mail.
On 13 January 2022 23:19:29 UTC, Brandon Allbery
I'm not sure I like the idea of Haskell trying to guess a constructor to use from a tuple. What happens if multiple constructors could match, for one?
On Thu, Jan 13, 2022 at 6:17 PM Richard Eisenberg
wrote: We could potentially have this. It reminds me of Agda's record syntax, where you can construct any record (which is like your tuple) with the keyword `record`.
Is it worth having yet another feature in the language? I'm not sure, myself.
Richard
On Jan 13, 2022, at 5:12 PM, Daneel Yaitskov
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.
_______________________________________________ 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.
-- brandon s allbery kf8nh allbery.b@gmail.com _______________________________________________ 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.

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
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

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.

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
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.

If you want "completeness" for "overloaded things", I think you might be
interested in this - https://github.com/phadej/overloaded
Not sure if it has OverloadedTuples, but it's in the same spirit, and could
probably be extended to have them.
On Mon, Jan 17, 2022 at 3:09 PM Carter Schonwald
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
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.
_______________________________________________ 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.
participants (8)
-
Brandon Allbery
-
Carter Schonwald
-
Daneel Yaitskov
-
Georgi Lyubenov
-
Jeffrey Brown
-
Keith
-
Richard Eisenberg
-
Viktor Dukhovni