Why is there no notion of a one-tuple (e.g., a '([])' as opposed to a '[]') in Haskell?

I'm having difficulty in understanding the following behavior: In GHCi: Prelude> :type [] [] :: [a] but: Prelude> :type ([]) ([]) :: [a] I.e., the types of both the empty-list '[]' and the one-tuple containing the empty-list '[]' are '[a]' (a list of a generic type variable). According to "Chapter 2. Types and Functions" (see http://book.realworldhaskell.org/read/types-and-functions.html) of Real World Haskell (beta) (see http://book.realworldhaskell.org/beta/),
Haskell doesn't have a notion of a one-element tuple.
Why not? It seems that a tuple is similar to a list, except that the elements need not be all of the same type, and that a tuple, unlike a list, cannot be extended. Yet: Prelude> :type [] [] :: [a] and Prelude> :type [[]] [[]] :: [[a]] so the types of the empty-list '[]' and the one-element list containing the empty-list '[[]]' are different. Forgive me if I am missing something, but something about this asymmetry bothers me.... -- Benjamin L. Russell

Hi Benjamin, [] has the type [a] because there is no constraint on what the type of its elements could be, hence it is polymorphic. ([]) is actually the parenthesised expression for [], in the same way any expression e == (e). Haskell does have a unit type: Prelude> :t () () :: () I guess this is analogue of the empty tuple to the empty list. One element tuples are not allowed - they are themselves expressions. The unit type is like the Null construct in other languages. Kind regards, Chris. On Wed, 24 Sep 2008, Benjamin L.Russell wrote:
I'm having difficulty in understanding the following behavior:
In GHCi:
Prelude> :type [] [] :: [a]
but:
Prelude> :type ([]) ([]) :: [a]
I.e., the types of both the empty-list '[]' and the one-tuple containing the empty-list '[]' are '[a]' (a list of a generic type variable).
According to "Chapter 2. Types and Functions" (see http://book.realworldhaskell.org/read/types-and-functions.html) of Real World Haskell (beta) (see http://book.realworldhaskell.org/beta/),
Haskell doesn't have a notion of a one-element tuple.
Why not? It seems that a tuple is similar to a list, except that the elements need not be all of the same type, and that a tuple, unlike a list, cannot be extended. Yet:
Prelude> :type [] [] :: [a]
and
Prelude> :type [[]] [[]] :: [[a]]
so the types of the empty-list '[]' and the one-element list containing the empty-list '[[]]' are different.
Forgive me if I am missing something, but something about this asymmetry bothers me....
-- Benjamin L. Russell
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wed, 24 Sep 2008, Benjamin L.Russell wrote:
Haskell doesn't have a notion of a one-element tuple.
Why not?
Because that would've required clearing special syntactic space for it, and in most cases it's not semantically significant at all. The exception is when you put something strict in it.
It seems that a tuple is similar to a list, except that the elements need not be all of the same type, and that a tuple, unlike a list, cannot be extended. Yet:
Prelude> :type [] [] :: [a]
and
Prelude> :type [[]] [[]] :: [[a]]
so the types of the empty-list '[]' and the one-element list containing the empty-list '[[]]' are different.
Forgive me if I am missing something, but something about this asymmetry bothers me....
A one-element list will normally have a different type to the empty list because now we know what it's a list /of/ - the a in [a] has been substituted for [b] (or rather, a /new/ a) because we know we're looking at a list of lists of something. There are no one-tuples, so (x) is just x in parentheses and ([]) is just []. -- flippa@flippac.org Performance anxiety leads to premature optimisation

On Wed, Sep 24, 2008 at 09:08:49PM +0900, Benjamin L.Russell wrote:
I'm having difficulty in understanding the following behavior:
In GHCi:
Prelude> :type [] [] :: [a]
but:
Prelude> :type ([]) ([]) :: [a]
I.e., the types of both the empty-list '[]' and the one-tuple containing the empty-list '[]' are '[a]' (a list of a generic type variable).
According to "Chapter 2. Types and Functions" (see http://book.realworldhaskell.org/read/types-and-functions.html) of Real World Haskell (beta) (see http://book.realworldhaskell.org/beta/),
Haskell doesn't have a notion of a one-element tuple.
Why not? It seems that a tuple is similar to a list, except that the elements need not be all of the same type, and that a tuple, unlike a list, cannot be extended. Yet:
Note that it would be really annoying to have parentheses create a one-tuple. That would lead to such joyous fun as
1 + (2 + 3)
<interactive>:1:0: No instance for (Num (t)) arising from a use of `+' at <interactive>:1:0-8 Possible fix: add an instance declaration for (Num (t)) In the expression: 1 + (2 + 3) In the definition of `it': it = 1 + (2 + 3) (artist's conception). So some other syntax would be needed, but as Philippa points out, that would be a lot of syntactic heaviness for not much benefit. Python actually does have one-tuples: you create a one-tuple containing, say, the number 3 by writing: (3,) Ugly! In the end, there's no *theoretical* reason why Haskell doesn't have one-tuples: this is one of the few places in the language design where practical concerns won out over theoretical. -Brent

On 2008-09-24, Benjamin L.Russell
Haskell doesn't have a notion of a one-element tuple.
Why not?
In addition to the syntactic nightmare mentioned, or the possible loss of parenthesized expressions, it's just plain not necessary. Aside from strictness, a one-tuple is isomorphic to the element inside. We like category theory, so we ignore trivial isomorphisms. -- Aaron Denney -><-

G'day all.
Quoting "Benjamin L.Russell"
Haskell doesn't have a notion of a one-element tuple.
Why not?
As noted by others, there's no syntactic space for them. Perhaps more crucially, it's hard to see where such a thing would be useful. The 2-tuple (i.e. pair) is a categorical product, and can be used to carry around two things where you would normally only have space for one. The 0-tuple (i.e. void) is a categorical terminal object, and can be used to fill in space in a parametric data structure where no annotation is actually needed. One reason why they're provided in the Prelude is so that standard functions can do operations on them. It's hard to see where a standard function would use a generic 1-tuple. Generally speaking, if you need a type-checked 1-tuple, you almost certainly don't want a generic one. Cheers, Andrew Bromage

On 25/09/2008, at 11:27 AM, ajb@spamcop.net wrote:
Haskell doesn't have a notion of a one-element tuple.
Why not?
Perhaps more crucially, it's hard to see where such a thing would be useful.
IORef, and ML's ref types are sort of one element tuples. The ML ref type is more so, because you don't need a special monad to read and write its contents.. Ref types are useful because many different parts of your program can hold pointers to the outer constructor. By updating the constructor to hold a different value, you propagate this new value throughout your program in a single, constant time operation. Ref types can be very useful in practice. IORefs are used GHC's type inferencer to implement type substitution. They're also heavily used in interactive programs like frag[1] to propagate the current user input state throughout the program. Ben. [1] http://www.haskell.org/haskellwiki/Frag

G'day all.
Quoting Ben Lippmeier
Perhaps more crucially, it's hard to see where such a thing would be useful.
IORef, and ML's ref types are sort of one element tuples.
I used to do a fair bit of hash consing myself. I'm definitely sold on references. But they're not quite the same thing as 1-tuples. The fact that you need to go through a monad in Haskell shows why they are different. Cheers, Andrew Bromage

On Wed, 24 Sep 2008 21:27:37 -0400, ajb@spamcop.net wrote:
G'day all.
Quoting "Benjamin L.Russell"
: Haskell doesn't have a notion of a one-element tuple.
Why not?
As noted by others, there's no syntactic space for them.
Perhaps more crucially, it's hard to see where such a thing would be useful. The 2-tuple (i.e. pair) is a categorical product, and can be used to carry around two things where you would normally only have space for one. The 0-tuple (i.e. void) is a categorical terminal object, and can be used to fill in space in a parametric data structure where no annotation is actually needed.
One reason why they're provided in the Prelude is so that standard functions can do operations on them. It's hard to see where a standard function would use a generic 1-tuple.
Generally speaking, if you need a type-checked 1-tuple, you almost certainly don't want a generic one.
So, basically generic one-element tuples don't exist because they're not needed, and there is no elegant way to represent them syntactically. That makes sense. Nevertheless, I can't help feeling that Haskell could perhaps been made even more elegant if some alternative tuple notation not conflicting with parentheses had been used; e.g., '{}' (braces) (please forgive me if braces are already used for some other purpose of which I am not aware). Then, for example, we could have the following: {} (a unit, or void), {{}} (a one-tuple), {{{}}} (a one-tuple consisting of a one-tuple), {{{{}}}} (a one-tuple consisting of a one-tuple consisting of a one-tuple), ... We could then come up with an n-depth-ordering on tuples, as opposed to an ordering on n-tuples. While perhaps not immediately useful, this ordering would have an interesting structure, and perhaps lead to some kind of mathematics of n-depth-orderings, which could be even more interesting, and which could be expressed in Haskell. -- Benjamin L. Russell

How is a 1-tuple different from a value? If we think of tuple types as product types, then the 1-ary product is a simple type -- and 1-ary tuples of values are simple values. In Python, tuples really are like lists -- to the point of being mapable, iterable, &c. In Haskell, lists and tuples share very little. -- _jsn
participants (8)
-
Aaron Denney
-
ajb@spamcop.net
-
Ben Lippmeier
-
Benjamin L.Russell
-
Brent Yorgey
-
C.M.Brown
-
Jason Dusek
-
Philippa Cowderoy