
`(,) :: 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.