[Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Johan Tibell
I have a rope data type with the invariant that one of its data constructors can never appear as a leaf. module Data.Rope where import Data.Word (Word8) data Rope = Empty | Leaf | Node !Rope !Rope index :: Rope - Int - Word8 index Empty _ = error empty index Leaf _

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread David Benbennick
On 10/9/07, Johan Tibell [EMAIL PROTECTED] wrote: data Rope = Empty | Leaf | Node !Rope !Rope The point is that Empty can only appear at the top by construction How about indicating this in your data type? I.e., data Rope = Empty | NonEmptyRope data NonEmptyRope = Leaf

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Johan Tibell
On 10/9/07, David Benbennick [EMAIL PROTECTED] wrote: On 10/9/07, Johan Tibell [EMAIL PROTECTED] wrote: data Rope = Empty | Leaf | Node !Rope !Rope The point is that Empty can only appear at the top by construction How about indicating this in your data type?

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Thomas Schilling
On Tue, 2007-10-09 at 17:40 +0200, Johan Tibell wrote: On 10/9/07, David Benbennick [EMAIL PROTECTED] wrote: On 10/9/07, Johan Tibell [EMAIL PROTECTED] wrote: data Rope = Empty | Leaf | Node !Rope !Rope The point is that Empty can only appear at the top by

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Roberto Zunino
A GADT version seems to generate OK code: data Top data NTop data Rope t where Empty :: Rope Top Leaf :: Rope NTop Node :: !(Rope NTop) - !(Rope NTop) - Rope NTop index :: Rope t - Int - Word8 index Empty _ = error empty index Leaf _ = error leaf index (Node l r) n = index' l n

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Bryan O'Sullivan
Johan Tibell wrote: I have a rope data type [...] Perhaps you should talk to Derek Elkins about his. It would be nice if we had fewer, more canonical implementations of popular data structures, instead of a proliferation of half bakery. b