Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread ajb

G'day all.

I asked:


But more to the point: Can it send email?


Quoting John Dorsey [EMAIL PROTECTED]:


Can you give an example of a use case?


I don't need one.  It's not maximally flexible until it can send email.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread ajb

G'day all.

Quoting Lennart Augustsson [EMAIL PROTECTED]:


But I called it One.


That's a _terrible_ name.  One, surely is (), just as Zero is Void.

While I'm at it, I really don't like the lexical syntax of comments.
Someone should fix that.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Jason Dusek
Jason Dagit [EMAIL PROTECTED] wrote:
 Jason Dusek [EMAIL PROTECTED] wrote:
  John Dorsey [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Mitchell, Neil

 Quoting Lennart Augustsson [EMAIL PROTECTED]:
 
  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
==

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Lennart Augustsson
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 [EMAIL PROTECTED] wrote:
 Jason Dagit [EMAIL PROTECTED] wrote:
  Perhaps I am lacking in imagination, but I still can't see the
  value of one tuples.

 --
 _jsn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Jason Dusek
Lennart Augustsson [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread David Menendez
On Fri, Oct 3, 2008 at 3:17 AM, Jason Dusek [EMAIL PROTECTED] 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.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread 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.

  -- Lennart

On Fri, Oct 3, 2008 at 6:07 PM, Jason Dusek [EMAIL PROTECTED] wrote:
 Lennart Augustsson [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Derek Elkins
On Fri, 2008-10-03 at 15:38 -0400, David Menendez wrote:
 On Fri, Oct 3, 2008 at 3:17 AM, Jason Dusek [EMAIL PROTECTED] 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)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Don Stewart
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 [EMAIL PROTECTED] 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,

dataL 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Jason Dusek
Lennart Augustsson [EMAIL PROTECTED] 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?

  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Tim Chevalier
On Fri, Oct 3, 2008 at 2:29 PM, Jason Dusek [EMAIL PROTECTED] wrote:
 Lennart Augustsson [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Luke Palmer
On Fri, Oct 3, 2008 at 7:26 PM, Tim Chevalier [EMAIL PROTECTED] wrote:
 On Fri, Oct 3, 2008 at 2:29 PM, Jason Dusek [EMAIL PROTECTED] wrote:
 Lennart Augustsson [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Tim Chevalier
On Fri, Oct 3, 2008 at 7:24 PM, Luke Palmer [EMAIL PROTECTED] 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?

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread Luke Palmer
On Fri, Oct 3, 2008 at 8:32 PM, Tim Chevalier [EMAIL PROTECTED] wrote:
 On Fri, Oct 3, 2008 at 7:24 PM, Luke Palmer [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread ajb

G'day all.

Quoting John Dorsey [EMAIL PROTECTED]:


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Simon Brenner
On 10/2/08, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 G'day all.

  Quoting John Dorsey [EMAIL PROTECTED]:


  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-Monad-Identity.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Luke Palmer
On Thu, Oct 2, 2008 at 1:17 AM, Simon Brenner [EMAIL PROTECTED] wrote:
 On 10/2/08, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 G'day all.

  Quoting John Dorsey [EMAIL PROTECTED]:


  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-Monad-Identity.html

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Luke Palmer
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 [EMAIL PROTECTED] wrote:
 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread John Dorsey
All,

I'm bundling responses to save paper.

[EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread John Goerzen

On Thu, Oct 02, 2008 at 03:58:12PM -0400, John Dorsey wrote:
 All,
 
 I'm bundling responses to save paper.
 
 [EMAIL PROTECTED] 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! :-)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread minh thu
2008/10/2 John Dorsey [EMAIL PROTECTED]:
 All,

 I'm bundling responses to save paper.

 [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Jason Dusek
John Dorsey [EMAIL PROTECTED] 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.

--
_jsn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Jason Dagit
On Thu, Oct 2, 2008 at 2:46 PM, Jason Dusek [EMAIL PROTECTED] wrote:

 John Dorsey [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Lennart Augustsson
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 [EMAIL PROTECTED] wrote:
 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread Brandon S. Allbery KF8NH

On 2008 Oct 2, at 19:00, Jason Dagit wrote:
On Thu, Oct 2, 2008 at 2:46 PM, Jason Dusek [EMAIL PROTECTED]  
wrote:

John Dorsey [EMAIL PROTECTED] 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] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe