
Hi, I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list. I started with: data Container a = Single a | Many a [a] but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int. I can't figure out how to get this right. :( Please help. Günther

data Container a = Container a [a] ? Or, maybe, you need something like zipper. On 5 Jun 2009, at 01:53, Günther Schmidt wrote:
Hi,
I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list.
I started with:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I can't figure out how to get this right. :(
Please help.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Günther Schmidt wrote:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I think you meant to do either data Container a = Single a | Many a (Container a) or data Container a = Container a [a] - Jake

Hi Jake, Jake McArthur schrieb:
Günther Schmidt wrote:
data Container a = Single a | Many a [a] but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I think you meant to do either
data Container a = Single a | Many a (Container a)
nope, I pretty much meant what I wrote above, the solution here would mean deeply nested containers, since it's a recursive data structure. I need a data structure as in my example without the [] being possible to be empty. It's quite possible that in order to achieve this I would need to split this in 2 separate data declarations. The idea behind this is that an "a" can "pocket" siblings, but only one level deep and that an "a's" list of "pocketed/swallowed" siblings must not be empty, because otherwise it would automatically be an "Single a". Sorry, I really don't know how to put this better. Günther
or
data Container a = Container a [a]
- Jake

Unless I'm missing something in your description, why not data Container a = Single a | Many a a [a] Dan Günther Schmidt wrote:
Hi Jake,
Jake McArthur schrieb:
Günther Schmidt wrote:
data Container a = Single a | Many a [a] but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int. I think you meant to do either
data Container a = Single a | Many a (Container a)
nope, I pretty much meant what I wrote above, the solution here would mean deeply nested containers, since it's a recursive data structure.
I need a data structure as in my example without the [] being possible to be empty.
It's quite possible that in order to achieve this I would need to split this in 2 separate data declarations.
The idea behind this is that an "a" can "pocket" siblings, but only one level deep and that an "a's" list of "pocketed/swallowed" siblings must not be empty, because otherwise it would automatically be an "Single a".
Sorry, I really don't know how to put this better.
Günther
or
data Container a = Container a [a]
- Jake
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston schrieb:
Unless I'm missing something in your description, why not
data Container a = Single a | Many a a [a]
Hi Dan, the above solution would still allow to construct, for instance, Many 5 42 [] :: Container Int The reason why I'm trying to find the design for a data structure in which this would not even be possible is to be able to avoid writing additional "bookkeeping" code into the functions that operate on the structure, ie. the lookups, inserts, delete etc. Günther

I note that you didn't address the suggestion of a zipper. Günther Schmidt wrote:
Dan Weston schrieb:
Unless I'm missing something in your description, why not
data Container a = Single a | Many a a [a]
Hi Dan,
the above solution would still allow to construct, for instance,
Many 5 42 [] :: Container Int
The reason why I'm trying to find the design for a data structure in which this would not even be possible is to be able to avoid writing additional "bookkeeping" code into the functions that operate on the structure, ie. the lookups, inserts, delete etc.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tony Morris http://tmorris.net/

Hi Tony, that's because I wasn't sure whether or not it would be applicable here. As with monads, continuations, delimited continuations and quite a number of other high level concepts I only understand them in part even though I realize at the same time that understanding them fully would yield enormous benefits. I am aware of the power of these concepts, but have not gained the intuition yet. As for the zipper: In some of the examples I've seen, the zipper is implemented "on top" of an underlying data structure, but not the data structure itself. In my app I was actually going to pull a zipper over it, once I had the underlying structure right. Günther PS: please also see my reply to Tillman Tony Morris schrieb:
I note that you didn't address the suggestion of a zipper.
Günther Schmidt wrote:
Dan Weston schrieb:
Unless I'm missing something in your description, why not
data Container a = Single a | Many a a [a]
Hi Dan,
the above solution would still allow to construct, for instance,
Many 5 42 [] :: Container Int
The reason why I'm trying to find the design for a data structure in which this would not even be possible is to be able to avoid writing additional "bookkeeping" code into the functions that operate on the structure, ie. the lookups, inserts, delete etc.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 2009-06-05 at 02:08 +0200, Günther Schmidt wrote:
As for the zipper: In some of the examples I've seen, the zipper is implemented "on top" of an underlying data structure, but not the data structure itself. In my app I was actually going to pull a zipper over it, once I had the underlying structure right.
I have a package on Hackage that implements a zipper-ish non-empty list structure. PointedList [1] is a datatype composed of a list of items on the left, the current item, and a list of items on the right. Is that close to what you're looking for? [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/pointedlist

Hi Jeff, it might actually be, I'll check it out after a good nights sleep. Apparently working on this in the wee hours only leads to self embarrassing requests for help. Actually when it comes to the "underlying" data structure, Jake and Tillmann have already found it for me, even though I failed to realize that in Jakes post and only "got it" after Tillmanns post. It's been a long night :) Günther Jeff Wheeler schrieb:
On Fri, 2009-06-05 at 02:08 +0200, Günther Schmidt wrote:
As for the zipper: In some of the examples I've seen, the zipper is implemented "on top" of an underlying data structure, but not the data structure itself. In my app I was actually going to pull a zipper over it, once I had the underlying structure right.
I have a package on Hackage that implements a zipper-ish non-empty list structure. PointedList [1] is a datatype composed of a list of items on the left, the current item, and a list of items on the right.
Is that close to what you're looking for?
[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/pointedlist

Hi Günther, Günther Schmidt wrote:
data Container a = Single a | Many a [a] but the problem above
I need a data structure as in my example without the [] being possible to be empty.
So lets write a variant of list which cannot be empty. A usual list is empty, or a head and a tail: data List a = Empty | HeadAndTail a (List a) Now, our kind of list should be just one element, or a head and a tail: data NonEmptyList a = JustOne a | HeadAndNonEmptyTail a (NonEmptyList a) So we can replace [] by NonEmptyList in your definition to get what you want: data Container a = Single a | Many a (NonEmptyList a) However, since Container and NonEmptyList are isomorphic, we can use one instead of the other: data Container a = Single a | Many a (Container a) Whether this is a good idea depends on the purpose of the types, but I guess it is. Tillmann

Hi Tillmann, thank you for the elaborate example. This is exactly what it took for me to realize that you and Jake have indeed given me the solution that I need. I had a very hard time getting my head around it, but to my defense I'm usually working on this stuff in the wee hours. :) Günther Tillmann Rendel schrieb:
Hi Günther,
Günther Schmidt wrote:
data Container a = Single a | Many a [a] but the problem above
I need a data structure as in my example without the [] being possible to be empty.
So lets write a variant of list which cannot be empty. A usual list is empty, or a head and a tail:
data List a = Empty | HeadAndTail a (List a)
Now, our kind of list should be just one element, or a head and a tail:
data NonEmptyList a = JustOne a | HeadAndNonEmptyTail a (NonEmptyList a)
So we can replace [] by NonEmptyList in your definition to get what you want:
data Container a = Single a | Many a (NonEmptyList a)
However, since Container and NonEmptyList are isomorphic, we can use one instead of the other:
data Container a = Single a | Many a (Container a)
Whether this is a good idea depends on the purpose of the types, but I guess it is.
Tillmann

Günther Schmidt
I need a data structure as in my example without the [] being possible to be empty.
Well, a list can by definition be empty, so this is clearly impossible. The best you can do is to hide the constructors and have "smart" constructor functions that guarantee not to construct your data structure with an empty list component. I'm puzzled why you need to use a list here though.
The idea behind this is that an "a" can "pocket" siblings, but only one level deep and that an "a's" list of "pocketed/swallowed" siblings must not be empty, because otherwise it would automatically be an "Single a".
data Container a = Container a [a]
If you cannot use this directly, then perhaps you can use it as a replacement for normal lists that cannot be non-empty? chead (Container x _) = x ctail (Container _ []) = error "Can't take tail of singleton list" ctail (Container _ (x:xs) = x:xs -k -- If I haven't seen further, it is by standing in the footprints of giants

Hi Jake, apologies, Jake McArthur schrieb:
Günther Schmidt wrote:
data Container a = Single a | Many a [a] but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I think you meant to do either
data Container a = Single a | Many a (Container a)
you're right, the above solution is indeed exactly what I need. It took me until Tillmans later elaborate reply to realize. Sometimes I'm unable to see things even when they bite me in the face, ouch! Günther
or
data Container a = Container a [a]
- Jake

Are you looking for something like Streams [1]?
They're infinite sequences, defined like this:
data Stream a = Cons a (Stream a)
They can obviously never be empty (unless you see bottom (undefined) as empty).
- Tom
[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Stream
On Thu, Jun 4, 2009 at 11:53 PM, GüŸnther Schmidt
Hi,
I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list.
I started with:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I can't figure out how to get this right. :(
Please help.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Tom, thanks for replying, no, I'm not looking for streams. I hope I made myself a bit more clear in my response to Jake. Günther Tom Lokhorst schrieb:
Are you looking for something like Streams [1]?
They're infinite sequences, defined like this:
data Stream a = Cons a (Stream a)
They can obviously never be empty (unless you see bottom (undefined) as empty).
- Tom
[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Stream
On Thu, Jun 4, 2009 at 11:53 PM, GüŸnther Schmidt
wrote: Hi,
I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list.
I started with:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I can't figure out how to get this right. :(
Please help.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Günther, Miguel had the easiest suggestion to get right: Your goal is to avoid the redundant encoding of a list of one element, so why do you need to get rid of the Many a [] case when you can get rid of your Single a case!
module NE where
import Prelude hiding (foldr, foldl, foldl1, head, tail) import Data.Foldable (Foldable, foldr, toList, foldl, foldl1) import Data.Traversable (Traversable, traverse) import Control.Applicative
data NE a = NE a [a] deriving (Eq,Ord,Show,Read)
Now we can fmap over non-empty lists
instance Functor NE where fmap f (NE a as) = NE (f a) (map f as)
It is clear how to append to a non-empty list.
cons :: a -> NE a -> NE a a `cons` NE b bs = NE a (b:bs)
head is total.
head :: NE a -> a head (NE a _) = a
tail can return an empty list, so lets model that
tail :: NE a -> [a] tail (NE _ as) = as
We may not be able to construct a non-empty list from a list, if its empty so model that.
fromList :: [a] -> Maybe (NE a) fromList (x:xs) = Just (NE x xs) fromList [] = Nothing
We can make our non-empty lists an instance of Foldable so you can use Data.Foldable's versions of foldl, foldr, etc. and nicely foldl1 has a very pretty total definition, so lets use it.
instance Foldable NE where foldr f z (NE a as) = a `f` foldr f z as foldl f z (NE a as) = foldl f (z `f` a) as foldl1 f (NE a as) = foldl f a as
We can traverse non-empty lists too.
instance Traversable NE where traverse f (NE a as) = NE <$> f a <*> traverse f as
And they clearly offer a monadic structure:
instance Monad NE where return a = NE a [] NE a as >>= f = NE b (bs ++ concatMap (toList . f) as) where NE b bs = f a
and you can proceed to add suitable instance declarations for it to be a Comonad if you are me, etc. Now a singleton list has one representation NE a [] A list with two elements can only be represented by NE a [b] And so on for NE a [b,c], NE 1 [2..], etc. You could also make the
data Container a = Single a | Many a (Container a)
definition work that Jake McArthur provided. For the category theory
inspired reader Jake's definition is equivalent to the Cofree comonad of the
Maybe functor, which can encode a non-empty list.
I leave that one as an exercise for the reader, but observe
Single 1
Many 1 (Single 2)
Many 1 (Many 2 (Single 3))
And the return for this particular monad is easy:
instance Monad Container where
return = Single
In general Jake's non-empty list is a little nicer because it avoids a
useless [] constructor at the end of the list.
-Edward Kmett
On Thu, Jun 4, 2009 at 5:53 PM, GüŸnther Schmidt
Hi,
I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list.
I started with:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I can't figure out how to get this right. :(
Please help.
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi folks data NE x = x :> Maybe (NE x) ? It's Applicative in at least four different ways. Can anyone find more? Conor On 5 Jun 2009, at 01:34, Edward Kmett wrote:
Günther,
Miguel had the easiest suggestion to get right:
Your goal is to avoid the redundant encoding of a list of one element, so why do you need to get rid of the Many a [] case when you can get rid of your Single a case!
module NE where
import Prelude hiding (foldr, foldl, foldl1, head, tail) import Data.Foldable (Foldable, foldr, toList, foldl, foldl1) import Data.Traversable (Traversable, traverse) import Control.Applicative
data NE a = NE a [a] deriving (Eq,Ord,Show,Read)
Now we can fmap over non-empty lists
instance Functor NE where fmap f (NE a as) = NE (f a) (map f as)
It is clear how to append to a non-empty list.
cons :: a -> NE a -> NE a a `cons` NE b bs = NE a (b:bs)
head is total.
head :: NE a -> a head (NE a _) = a
tail can return an empty list, so lets model that
tail :: NE a -> [a] tail (NE _ as) = as
We may not be able to construct a non-empty list from a list, if its empty so model that.
fromList :: [a] -> Maybe (NE a) fromList (x:xs) = Just (NE x xs) fromList [] = Nothing
We can make our non-empty lists an instance of Foldable so you can use Data.Foldable's versions of foldl, foldr, etc. and nicely foldl1 has a very pretty total definition, so lets use it.
instance Foldable NE where foldr f z (NE a as) = a `f` foldr f z as foldl f z (NE a as) = foldl f (z `f` a) as foldl1 f (NE a as) = foldl f a as
We can traverse non-empty lists too.
instance Traversable NE where traverse f (NE a as) = NE <$> f a <*> traverse f as
And they clearly offer a monadic structure:
instance Monad NE where return a = NE a [] NE a as >>= f = NE b (bs ++ concatMap (toList . f) as) where NE b bs = f a
and you can proceed to add suitable instance declarations for it to be a Comonad if you are me, etc.
Now a singleton list has one representation
NE a []
A list with two elements can only be represented by NE a [b]
And so on for NE a [b,c], NE 1 [2..], etc.
You could also make the
data Container a = Single a | Many a (Container a)
definition work that Jake McArthur provided. For the category theory inspired reader Jake's definition is equivalent to the Cofree comonad of the Maybe functor, which can encode a non-empty list.
I leave that one as an exercise for the reader, but observe
Single 1 Many 1 (Single 2) Many 1 (Many 2 (Single 3))
And the return for this particular monad is easy:
instance Monad Container where return = Single
In general Jake's non-empty list is a little nicer because it avoids a useless [] constructor at the end of the list.
-Edward Kmett
On Thu, Jun 4, 2009 at 5:53 PM, GüŸnther Schmidt
wrote: Hi, I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list.
I started with:
data Container a = Single a | Many a [a]
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.
I can't figure out how to get this right. :(
Please help.
Günther
_______________________________________________ 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
participants (11)
-
Conor McBride
-
Dan Weston
-
Edward Kmett
-
Günther Schmidt
-
Jake McArthur
-
Jeff Wheeler
-
Ketil Malde
-
Miguel Mitrofanov
-
Tillmann Rendel
-
Tom Lokhorst
-
Tony Morris