[Haskell-cafe] Non Empty List?

Edward Kmett ekmett at gmail.com
Thu Jun 4 20:34:05 EDT 2009


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 <gue.schmidt at web.de> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090604/54cd7ee4/attachment.html


More information about the Haskell-Cafe mailing list