
Fellow Haskellers, Much attention has been paid over the years to the regrettable omission of singleton tuples from Haskell. I am pleased to announce OneTuple, a humble implementation of the singleton tuple for Haskell. Now you can: * Wrap a single value of any type in a OneTuple ! * Pattern match to retrieve your value ! * Solve any of the software problems that cannot be solved without the singleton tuple ! * Enjoy instances for all the classes normal tuples have, plus more ! * Proclaim feature parity with Python ! Note: the singleton tuple does not support tuple syntax. Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version. Enjoy! Regards, John Dorsey

G'day all.
Quoting John Dorsey
Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version.
I hope it has a Monad instance. But more to the point: Can it send email? Cheers, Andrew Bromage

On 10/2/08, ajb@spamcop.net
G'day all.
Quoting John Dorsey
: Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version.
I hope it has a Monad instance.
You could always use this one-tuple instead and get Functor, Monad and MonadFix for free: http://hackage.haskell.org/packages/archive/mtl/1.1.0.1/doc/html/Control-Mon...

On Thu, Oct 2, 2008 at 1:17 AM, Simon Brenner
On 10/2/08, ajb@spamcop.net
wrote: G'day all.
Quoting John Dorsey
: Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version.
I hope it has a Monad instance.
You could always use this one-tuple instead and get Functor, Monad and MonadFix for free: http://hackage.haskell.org/packages/archive/mtl/1.1.0.1/doc/html/Control-Mon...
But that one is different: newtype Identity a = Identity { runIdentity :: a } data OneTuple a = OneTuple { only :: a } So OneTuple has one more value than Identity (Identity Int has Identity _|_ and Identity n for each n, whereas OneTuple Int has _|_, OneTuple _|_, and OneTuple n for each n) Luke

All, I'm bundling responses to save paper. ajb@spamcop.net wrote:
I hope it has a Monad instance.
Naturally!
But more to the point: Can it send email?
Can you give an example of a use case? Do the Haskell-98 standard tuples have a correspondence feature? I wasn't able to find one with Hoogle. Simon Brenner wrote:
You could always use this one-tuple instead and get Functor, Monad and MonadFix for free:
As Luke pointed out, that one seems to be too strict. It may simplify the strict implementation, though. The initial release did have Monad and Functor instances... I'll look into MonadFix (thanks!). Luke Palmer wrote:
Hmm, it looks like you forgot to write a Traversable instance.
Oops... I included the instance statement but retained the default, mutually recursive methods. Too bad GHC didn't warn me. (Pesky halting problem.) Your change is in 0.1.1 -- thanks! Benjamin L.Russell wrote:
Wonderful! I'm intrigued....
Thank you.
What is the syntax for the singleton tuple? [...] What is your solution?
Haskell has no such syntax, of course. '(x)' is no good due to ambiguity with parens' usual associative use. '(x,)' has been discussed, I think. It's ugly; it's inconsistent with other tuples, which don't share its final comma; it looks a bit like a tuple section, which could cause confusion. My solution was to use a normal Algebraic Data Type: data OneTuple a = OneTuple a I think the need for singleton tuples is rare enough that the syntactic inconsistency is tolerable. Jon Fairbairn suggests using unicode 0x27e8 and 0x27e0 in place of parentheses for tuples. I like the idea, especially as an alternate syntax for the same tuple types, permitting the singleton. minh thu writes:
I thought to this idea in another way : parenthesis could be used for s-expressions and [unicode 0x27e8 and 0x27e0] could be used for regular grouping. This would allow to switch in the same code between infix and s-expr (e.g. enabling SXML)...
I don't think I fully understand your proposal, although it sounds interesting. Regards, John Dorsey

On Thu, Oct 02, 2008 at 03:58:12PM -0400, John Dorsey wrote:
All,
I'm bundling responses to save paper.
ajb@spamcop.net wrote:
I hope it has a Monad instance.
Naturally!
But more to the point: Can it send email?
Can you give an example of a use case? Do the Haskell-98 standard tuples have a correspondence feature? I wasn't able to find one with Hoogle.
Pfft, that kind of thinking never stopped Emacs! :-)

2008/10/2 John Dorsey
All,
I'm bundling responses to save paper.
ajb@spamcop.net wrote:
I hope it has a Monad instance.
Naturally!
But more to the point: Can it send email?
Can you give an example of a use case? Do the Haskell-98 standard tuples have a correspondence feature? I wasn't able to find one with Hoogle.
Simon Brenner wrote:
You could always use this one-tuple instead and get Functor, Monad and MonadFix for free:
As Luke pointed out, that one seems to be too strict. It may simplify the strict implementation, though. The initial release did have Monad and Functor instances... I'll look into MonadFix (thanks!).
Luke Palmer wrote:
Hmm, it looks like you forgot to write a Traversable instance.
Oops... I included the instance statement but retained the default, mutually recursive methods. Too bad GHC didn't warn me. (Pesky halting problem.) Your change is in 0.1.1 -- thanks!
Benjamin L.Russell wrote:
Wonderful! I'm intrigued....
Thank you.
What is the syntax for the singleton tuple? [...] What is your solution?
Haskell has no such syntax, of course. '(x)' is no good due to ambiguity with parens' usual associative use. '(x,)' has been discussed, I think. It's ugly; it's inconsistent with other tuples, which don't share its final comma; it looks a bit like a tuple section, which could cause confusion.
My solution was to use a normal Algebraic Data Type: data OneTuple a = OneTuple a
I think the need for singleton tuples is rare enough that the syntactic inconsistency is tolerable.
Jon Fairbairn suggests using unicode 0x27e8 and 0x27e0 in place of parentheses for tuples. I like the idea, especially as an alternate syntax for the same tuple types, permitting the singleton.
minh thu writes:
I thought to this idea in another way : parenthesis could be used for s-expressions and [unicode 0x27e8 and 0x27e0] could be used for regular grouping. This would allow to switch in the same code between infix and s-expr (e.g. enabling SXML)...
I don't think I fully understand your proposal, although it sounds interesting.
(It's not related to your tuple) Here is an example, quite contrived: With angle bracket: f a b c d = a + (+ b ⟨c + d⟩) -- the + before the b is in prefix position is equivalent to Normal Haskell: f a b c d = a + (b + (c + d)) With angle brackets, parenthesis mean "this is an s-expr" and angle brackets mean "this is an standard (infix) expression". In the s-expr, there is no precedence rules while they are kept in the top level or in angle brackets. Hope it's clearer, Thu

Hmm, it looks like you forgot to write a Traversable instance. I don't believe:
sequenceA (OneTuple [1,2,3,4]) = _|_
is correct. Here is my contribution!
instance Traversable OneTuple where
sequenceA (OneTuple x) = fmap OneTuple x
Luke
On Thu, Oct 2, 2008 at 12:56 AM, John Dorsey
Fellow Haskellers,
Much attention has been paid over the years to the regrettable omission of singleton tuples from Haskell.
I am pleased to announce OneTuple, a humble implementation of the singleton tuple for Haskell. Now you can:
* Wrap a single value of any type in a OneTuple !
* Pattern match to retrieve your value !
* Solve any of the software problems that cannot be solved without the singleton tuple !
* Enjoy instances for all the classes normal tuples have, plus more !
* Proclaim feature parity with Python !
Note: the singleton tuple does not support tuple syntax.
Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version.
Enjoy!
Regards, John Dorsey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, 2 Oct 2008 02:56:08 -0400, John Dorsey
Fellow Haskellers,
Much attention has been paid over the years to the regrettable omission of singleton tuples from Haskell.
I am pleased to announce OneTuple, a humble implementation of the singleton tuple for Haskell.
Wonderful! I'm intrigued....
Note: the singleton tuple does not support tuple syntax.
What is the syntax for the singleton tuple? We have a dilemma: If we extend the singleton syntax to support non-singleton tuples, then we'll have at least two definitions of a tuple for each non-singleton tuple, which is syntactically inelegant; however, if we don't, then the singleton syntax will be different from the non-singleton syntax, which is also syntactically inelegant. What is your solution? -- Benjamin

Benjamin L.Russell
Note: the singleton tuple does not support tuple syntax.
What is the syntax for the singleton tuple? [...] the singleton syntax will be different from the non-singleton syntax, which is also syntactically inelegant.
What is your solution?
Replace () in tuple syntax with ⟨⟩ (unicode 0x27e8 and 0x27e0). I always wanted Haskell to be defined in terms of an idealised syntax together with a (at the time ASCII) machine representation that approximated it. As time went by, we could gradually have made the approximation approach the ideal. It would probably have been a mistake politically, though (people would have muttered about APL). Nowadays it might be more acceptable. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2008-04-26)

2008/10/2 Jon Fairbairn
Benjamin L.Russell
writes: Note: the singleton tuple does not support tuple syntax.
What is the syntax for the singleton tuple? [...] the singleton syntax will be different from the non-singleton syntax, which is also syntactically inelegant.
What is your solution?
Replace () in tuple syntax with ⟨⟩ (unicode 0x27e8 and 0x27e0).
I thought to this idea in another way : parenthesis could be used for s-expressions and ⟨⟩ (unicode 0x27e8 and 0x27e0) could be used for regular grouping. This would allow to switch in the same code between infix and s-expr (e.g. enabling SXML)... Cheers, Thu

On Thu, Oct 2, 2008 at 2:46 PM, Jason Dusek
John Dorsey
wrote: Now you can: * Solve any of the software problems that cannot be solved without the singleton tuple !
What would those be? I'm still trying to figure out how a singelton tuple is really distinct from a plain value.
Careful when making (or not making) this distinction. It could lead to infinite types such as, a = OneTuple a. Jason

On 2008 Oct 2, at 19:00, Jason Dagit wrote:
On Thu, Oct 2, 2008 at 2:46 PM, Jason Dusek
wrote: John Dorsey wrote: Now you can: * Solve any of the software problems that cannot be solved without the singleton tuple !
What would those be? I'm still trying to figure out how a singelton tuple is really distinct from a plain value.
Careful when making (or not making) this distinction. It could lead to infinite types such as, a = OneTuple a.
As for the difference, doesn't the tuple have an additional _|_ compared to a direct value? _|_, (_|_,), (value,). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Jason Dagit
Jason Dusek
wrote: John Dorsey
wrote: Now you can: * Solve any of the software problems that cannot be solved without the singleton tuple !
What would those be? I'm still trying to figure out how a singelton tuple is really distinct from a plain value.
Careful when making (or not making) this distinction. It could lead to infinite types such as, a = OneTuple a.
Perhaps I am lacking in imagination, but I still can't see the value of one tuples. -- _jsn

Let me pick one example. Let's make a class that can convert between
tuples and lists.
Of course there are restriction when this works, but it can still be useful.
class TupleList t l | t -> l where
tupleToList :: t -> l
listToTuple :: l -> t
instance TupleList () [a] where
tupleToList () = []
listToTuple [] = ()
-- XXX This doesn't work, and is just wrong.
--instance TupleList (a) [a] where
-- tupleToList (a) = [a]
-- listToTuple [a] = (a)
instance TupleList (a,a) [a] where
tupleToList (a1,a2) = [a1, a2]
listToTuple [a1,a2] = (a1, a2)
instance TupleList (a,a,a) [a] where
tupleToList (a1,a2,a3) = [a1, a2, a3]
listToTuple [a1,a2,a3] = (a1, a2, a3)
On Fri, Oct 3, 2008 at 8:17 AM, Jason Dusek
Jason Dagit
wrote: Perhaps I am lacking in imagination, but I still can't see the value of one tuples. -- _jsn

Lennart Augustsson
Let me pick one example. Let's make a class that can convert between tuples and lists.
-- XXX This doesn't work, and is just wrong. -- instance TupleList (a) [a] where -- tupleToList (a) = [a] -- listToTuple [a] = (a)
It's not clear to me what is so "wrong" about it. If the 1-ary tuple is the 1-ary product, it makes sense. -- _jsn

But (a) is not a lifted version of a, whereas (a,b) is a lifted
version of the a b product.
So it's not consistent, and thereby wrong.
-- Lennart
On Fri, Oct 3, 2008 at 6:07 PM, Jason Dusek
Lennart Augustsson
wrote: Let me pick one example. Let's make a class that can convert between tuples and lists.
-- XXX This doesn't work, and is just wrong. -- instance TupleList (a) [a] where -- tupleToList (a) = [a] -- listToTuple [a] = (a)
It's not clear to me what is so "wrong" about it. If the 1-ary tuple is the 1-ary product, it makes sense.
-- _jsn

Lennart Augustsson
But (a) is not a lifted version of a, whereas (a,b) is a lifted version of the a b product. So it's not consistent, and thereby wrong.
Well, we can't represent the unlifted product in Haskell, right? You have to use some constructor. So if we just say we are using tuples to represent unlifted products, what's so bad about that? At present, tupling doesn't lift values into anything, since we don't have generic operations on tuples. The last two messages in this thread suggests this has more to do with the internals of Haskell than they do with consistent semantics -- so I am perhaps missing the point. -- _jsn

On Fri, Oct 3, 2008 at 2:29 PM, Jason Dusek
Lennart Augustsson
wrote: But (a) is not a lifted version of a, whereas (a,b) is a lifted version of the a b product. So it's not consistent, and thereby wrong.
Well, we can't represent the unlifted product in Haskell, right? You have to use some constructor. So if we just say we are using tuples to represent unlifted products, what's so bad about that?
Unless I'm confused, unboxed tuples represent unlifted products. In a sense this is "[using] some constructor", but in a sense not, since an unboxed tuple constructor has no runtime representation.
The last two messages in this thread suggests this has more to do with the internals of Haskell than they do with consistent semantics -- so I am perhaps missing the point.
I think most Haskellers try their best to keep the first subservient to the second. Cheers, Tim -- Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt "If you don't understand the causes, it is impossible to come up with a solution." -- Joe Biden

On Fri, Oct 3, 2008 at 7:26 PM, Tim Chevalier
On Fri, Oct 3, 2008 at 2:29 PM, Jason Dusek
wrote: Lennart Augustsson
wrote: But (a) is not a lifted version of a, whereas (a,b) is a lifted version of the a b product. So it's not consistent, and thereby wrong.
Well, we can't represent the unlifted product in Haskell, right? You have to use some constructor. So if we just say we are using tuples to represent unlifted products, what's so bad about that?
Unless I'm confused, unboxed tuples represent unlifted products. In a sense this is "[using] some constructor", but in a sense not, since an unboxed tuple constructor has no runtime representation.
Well, unboxed tuples are not really lifted nor unlifed, since you can't even pass one to a function. I like to pretend tuples are unlifted. Here's how I do it: * Never use seq on tuples (or functions). I could make this precise by putting seq in a typeclass (like it used to be - like it should be), and not having instances for tuples. * Never do a strict pattern match on a tuple. I.e. instead of writing f (x,y) = ..., I will write f ~(x,y) =... everywhere. Then (_|_,_|_) might as well be _|_, we have no way to tell them apart. I like to pretend functions are unlifed the same way; i.e. const _|_ = _|_. There are apparently occasions where lazily matching on a tuple will introduce a space leak. I am not 1337 enough to recognize them yet. Luke

On Fri, Oct 3, 2008 at 7:24 PM, Luke Palmer
Well, unboxed tuples are not really lifted nor unlifed, since you can't even pass one to a function.
It's true that unboxed tuples are not first-class. But what I mean by "unlifted" is that the type (# Int, Int #), when interpreted as a set, does not contain _|_ as an element (and I'm purposely conflating the unlifted/liftedness distinction with the unboxed/boxness distinction here). Is that what you mean, or do you mean something else?
I like to pretend tuples are unlifted. Here's how I do it:
Sure. But the compiler won't check that assumption for you. I don't know whether that has anything to do with the original question, though :-) Cheers, Tim -- Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt "If you don't understand the causes, it is impossible to come up with a solution." -- Joe Biden

On Fri, Oct 3, 2008 at 8:32 PM, Tim Chevalier
On Fri, Oct 3, 2008 at 7:24 PM, Luke Palmer
wrote: Well, unboxed tuples are not really lifted nor unlifed, since you can't even pass one to a function.
It's true that unboxed tuples are not first-class. But what I mean by "unlifted" is that the type (# Int, Int #), when interpreted as a set, does not contain _|_ as an element (and I'm purposely conflating the unlifted/liftedness distinction with the unboxed/boxness distinction here). Is that what you mean, or do you mean something else?
Yeah kind of, because if it doesn't contain _|_ as an element, then it's not even a domain! :-)
I like to pretend tuples are unlifted. Here's how I do it:
Sure. But the compiler won't check that assumption for you. I don't know whether that has anything to do with the original question, though :-)
Nobody's questions are original. Luke

On Fri, Oct 3, 2008 at 3:17 AM, Jason Dusek
Perhaps I am lacking in imagination, but I still can't see the value of one tuples.
You can use them to defeat seq.
undefined `seq` x == undefined
OneTuple undefined `seq` x == x
That might be useful if a polymorphic function is using seq to force
evaluation, and you don't want it to. But I can't imagine that coming
up much in practice.
--
Dave Menendez

On Fri, 2008-10-03 at 15:38 -0400, David Menendez wrote:
On Fri, Oct 3, 2008 at 3:17 AM, Jason Dusek
wrote: Perhaps I am lacking in imagination, but I still can't see the value of one tuples.
You can use them to defeat seq.
undefined `seq` x == undefined OneTuple undefined `seq` x == x
That might be useful if a polymorphic function is using seq to force evaluation, and you don't want it to. But I can't imagine that coming up much in practice.
Think element strict polymorphic containers, e.g. data HeadStrictList a = Nil | Cons !a (HeadStrictList a) then type LazyList a = HeadStrictList (OneTuple a)

derek.a.elkins:
On Fri, 2008-10-03 at 15:38 -0400, David Menendez wrote:
On Fri, Oct 3, 2008 at 3:17 AM, Jason Dusek
wrote: Perhaps I am lacking in imagination, but I still can't see the value of one tuples.
You can use them to defeat seq.
undefined `seq` x == undefined OneTuple undefined `seq` x == x
That might be useful if a polymorphic function is using seq to force evaluation, and you don't want it to. But I can't imagine that coming up much in practice.
Think element strict polymorphic containers, e.g.
data HeadStrictList a = Nil | Cons !a (HeadStrictList a)
then
type LazyList a = HeadStrictList (OneTuple a)
Used in practice to prevent strict state components in list fusion leaking into user's lazy code, data L a = L a -- lazy / lifted newtype S a = S a -- strict / unlifted class Unlifted a where instance Unlifted (L a) where expose (L _) s = s instance Unlifted (S a) where expose (S a) s = seq a s data Stream a = forall s. Unlifted s => Stream !(s -> Step a s) -- ^ a stepper function !s -- ^ an initial state So we can then ensure stream :: [a] -> Stream a stream xs0 = Stream next (L xs0) where next (L []) = Done next (L (x:xs)) = Yield x (L xs) Has the appropriate strictness properties. -- Don

On Thu, 2 Oct 2008 14:46:32 -0700, "Jason Dusek"
John Dorsey
wrote: Now you can: * Solve any of the software problems that cannot be solved without the singleton tuple !
What would those be? I'm still trying to figure out how a singelton tuple is really distinct from a plain value.
Actually, part of my original motivation for suggesting a singleton tuple had to do with in using it as a tool for modeling complete partial orders (a.k.a. "cpos") (see http://en.wikipedia.org/wiki/Complete_partial_order), such as those that appear in a lattice (see http://en.wikipedia.org/wiki/Lattice_(order)). A lattice is a partially ordered set in which every pair of elements has a unique supremum (see http://en.wikipedia.org/wiki/Supremum) and infimum (see http://en.wikipedia.org/wiki/Infimum). When I was in college, one of the courses that I took was on domain theory (see http://en.wikipedia.org/wiki/Domain_theory), where we used complete partial orders to model (partial) results of a computation, where elements higher in the order extended the information of the elements below them in a consistent way. _|_ (bottom) represented an undefined result, and, if present in a cpo, was a least element for that cpo. In a lattice, unlike in a list, since every pair of elements has a unique supremum and infimum, it is possible to have an ordering where a pair of elements X1, Y1 < Z1 for some element Z1, and X1, Y2 < Z2 for some other elements Y2, Z2, but neither Z1 < Z2 nor Z2 < Z1. This kind of ordering cannot be represented in a list in which every element is a number. My idea was that it may be possible to use nesting of tuples to represent this kind of ordering if we, say, allow nesting an element in a tuple to distinguish that element from the same element not nested in a tuple, and to define elements or tuples X to have a lower ordering than either the same elements or tuples X with more nesting (e.g., X < (X)), or less than elements containing either those elements or containing tuples containing those elements (e.g., X < (X) and X < ((X), (Y)) (in the above-mentioned example) (() as _|_ being a unique least element). E.g. (in the above-mentioned example), let: X1 = (X) Y1 = (Y) Y2 = ((Y)) Then, in order to define Z1 and Z2, since X1 < Z1, Y1 < Z1 i.e., (X) < Z1, (Y) < Z1 and X1 < Z1, Y2 < Z2 i.e., (X) < Z1, ((Y)) < Z2 just define: Z1 = ((X), (Y)) Z2 = ((X), ((Y))) Then: X1 < Z1 i.e., (X) < ((X), (Y)) and Y1 < Z1 i.e., (Y) < ((X), (Y)) and X1 < Z2 i.e., (X) < ((X), ((Y))) Y2 < Z2 i.e., ((Y)) < ((X), ((Y))) but not: Z1 < Z2 i.e., not: ((X), (Y)) < ((X), ((Y))) (since they cannot be compared) and not: Z2 < Z1 i.e., not: ((X), ((Y))) < ((X), (Y)) (again, since they cannot be compared) Forgive me if this makes little sense, but I just thought that being able to define, say, (X) = X1 < ((X)) = X2 < (((X))) = X3 < .. < (..(^nX)..)^n = Xn would be useful in this kind of ordering. Then, X is not the same as (X), because X = X0, (X) = X1, ..., (..(^nX)..)^n = Xn, and in the context of this example, X < (X) < ... < (..(^nX)..)^n. Having a singleton tuple might then allow the representation of lattices using tuples, in which _|_ (bottom) = () is a unique least element, and for each element X in the lattice, X < (X) and X < each tuple containing X. Without a singleton tuple, we cannot define X < (X), because then X = (X). Does this sound plausible? -- Benjamin L. Russell

Actually, on second thought, there might be one problem with using
nested tuples in cpos in Haskell: Each tuple would have a different
type.
I.e., if we let
X /= (X) /= ... /= (..(^nX)..)^n
then
:type X
would yield a different result from
:type (X)
which would yield a different result from
:type ((X))
which would yield a different result from
...
which would yield a different result from
:type (..(^nX)..)
(using my notation here).
It might then be difficult to order the tuples of different
nesting....
I may need to think of a way around this issue....
-- Benjamin L. Russell
--- On Fri, 10/3/08, Benjamin L. Russell
From: Benjamin L. Russell
Subject: Re: Announcing OneTuple-0.1.0 To: Date: Friday, October 3, 2008, 3:10 PM On Thu, 2 Oct 2008 14:46:32 -0700, "Jason Dusek" wrote: John Dorsey
wrote: Now you can: * Solve any of the software problems that cannot be solved without the singleton tuple !
What would those be? I'm still trying to figure out how a singelton tuple is really distinct from a plain value.
Actually, part of my original motivation for suggesting a singleton tuple had to do with in using it as a tool for modeling complete partial orders (a.k.a. "cpos") (see http://en.wikipedia.org/wiki/Complete_partial_order), such as those that appear in a lattice (see http://en.wikipedia.org/wiki/Lattice_(order)). A lattice is a partially ordered set in which every pair of elements has a unique supremum (see http://en.wikipedia.org/wiki/Supremum) and infimum (see http://en.wikipedia.org/wiki/Infimum).
When I was in college, one of the courses that I took was on domain theory (see http://en.wikipedia.org/wiki/Domain_theory), where we used complete partial orders to model (partial) results of a computation, where elements higher in the order extended the information of the elements below them in a consistent way. _|_ (bottom) represented an undefined result, and, if present in a cpo, was a least element for that cpo.
In a lattice, unlike in a list, since every pair of elements has a unique supremum and infimum, it is possible to have an ordering where a pair of elements X1, Y1 < Z1 for some element Z1, and X1, Y2 < Z2 for some other elements Y2, Z2, but neither Z1 < Z2 nor Z2 < Z1. This kind of ordering cannot be represented in a list in which every element is a number.
My idea was that it may be possible to use nesting of tuples to represent this kind of ordering if we, say, allow nesting an element in a tuple to distinguish that element from the same element not nested in a tuple, and to define elements or tuples X to have a lower ordering than either the same elements or tuples X with more nesting (e.g., X < (X)), or less than elements containing either those elements or containing tuples containing those elements (e.g., X < (X) and X < ((X), (Y)) (in the above-mentioned example) (() as _|_ being a unique least element).
E.g. (in the above-mentioned example), let:
X1 = (X) Y1 = (Y) Y2 = ((Y))
Then, in order to define Z1 and Z2, since
X1 < Z1, Y1 < Z1 i.e., (X) < Z1, (Y) < Z1
and
X1 < Z1, Y2 < Z2 i.e., (X) < Z1, ((Y)) < Z2
just define:
Z1 = ((X), (Y)) Z2 = ((X), ((Y)))
Then:
X1 < Z1 i.e., (X) < ((X), (Y))
and
Y1 < Z1 i.e., (Y) < ((X), (Y))
and
X1 < Z2 i.e., (X) < ((X), ((Y)))
Y2 < Z2 i.e., ((Y)) < ((X), ((Y)))
but not: Z1 < Z2 i.e., not: ((X), (Y)) < ((X), ((Y))) (since they cannot be compared)
and not: Z2 < Z1 i.e., not: ((X), ((Y))) < ((X), (Y)) (again, since they cannot be compared)
Forgive me if this makes little sense, but I just thought that being able to define, say, (X) = X1 < ((X)) = X2 < (((X))) = X3 < .. < (..(^nX)..)^n = Xn
would be useful in this kind of ordering.
Then, X is not the same as (X), because X = X0, (X) = X1, ..., (..(^nX)..)^n = Xn, and in the context of this example, X < (X) < ... < (..(^nX)..)^n.
Having a singleton tuple might then allow the representation of lattices using tuples, in which _|_ (bottom) = () is a unique least element, and for each element X in the lattice, X < (X) and X < each tuple containing X.
Without a singleton tuple, we cannot define X < (X), because then X = (X).
Does this sound plausible?
-- Benjamin L. Russell

Just FYI, at Credit Suisse I wrote a 1-tuple type a few years ago. It
was the only way to get a consistent way of dealing with certain
things.
But I called it One.
I think the OneTuple should be in the base library, I mean, ask an 8
year old what number is missing in this sequence 0,2,3,4,5,6,7,8,9,...
-- Lennart
On Thu, Oct 2, 2008 at 7:56 AM, John Dorsey
Fellow Haskellers,
Much attention has been paid over the years to the regrettable omission of singleton tuples from Haskell.
I am pleased to announce OneTuple, a humble implementation of the singleton tuple for Haskell. Now you can:
* Wrap a single value of any type in a OneTuple !
* Pattern match to retrieve your value !
* Solve any of the software problems that cannot be solved without the singleton tuple !
* Enjoy instances for all the classes normal tuples have, plus more !
* Proclaim feature parity with Python !
Note: the singleton tuple does not support tuple syntax.
Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version.
Enjoy!
Regards, John Dorsey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Quoting Lennart Augustsson
: But I called it One.
I did a similar one for Yhc, and I think I called it Box. My guess was that boxing/unboxing wasn't an overloaded enough term :-) Thanks Neil ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================
participants (17)
-
ajb@spamcop.net
-
Benjamin L.Russell
-
Brandon S. Allbery KF8NH
-
David Menendez
-
Derek Elkins
-
Don Stewart
-
Jason Dagit
-
Jason Dusek
-
John Dorsey
-
John Goerzen
-
Jon Fairbairn
-
Lennart Augustsson
-
Luke Palmer
-
minh thu
-
Mitchell, Neil
-
Simon Brenner
-
Tim Chevalier