<div>G<span class="Apple-style-span" style="border-collapse: collapse; white-space: pre-wrap; -webkit-border-horizontal-spacing: 2px; -webkit-border-vertical-spacing: 2px; ">ünther, </span></div><div><span class="Apple-style-span" style="border-collapse: collapse; white-space: pre-wrap; -webkit-border-horizontal-spacing: 2px; -webkit-border-vertical-spacing: 2px;"><br>
</span></div><div><span class="Apple-style-span" style="border-collapse: collapse; white-space: pre-wrap; -webkit-border-horizontal-spacing: 2px; -webkit-border-vertical-spacing: 2px; ">Miguel had the easiest suggestion to get right:</span></div>
<div><br></div><div>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!</div><div><br></div><div>&gt; module NE where</div>
<div><br></div><div>&gt; import Prelude hiding (foldr, foldl, foldl1, head, tail)</div><div>&gt; import Data.Foldable (Foldable, foldr, toList, foldl, foldl1)</div><div>&gt; import Data.Traversable (Traversable, traverse)</div>
<div>&gt; import Control.Applicative</div><div><br></div><div>&gt; data NE a = NE a [a] deriving (Eq,Ord,Show,Read)</div><div><br></div><div>Now we can fmap over non-empty lists</div><div><br></div><div>&gt; instance Functor NE where</div>
<div>&gt;   fmap f (NE a as) = NE (f a) (map f as)</div><div><br></div><div>It is clear how to append to a non-empty list.</div><div><br></div><div>&gt; cons :: a -&gt; NE a -&gt; NE a</div><div>&gt; a `cons` NE b bs = NE a (b:bs)</div>
<div><br></div><div>head is total.</div><div><br></div><div>&gt; head :: NE a -&gt; a</div><div>&gt; head (NE a _) = a</div><div><br></div><div>tail can return an empty list, so lets model that</div><div><br></div><div>&gt; tail :: NE a -&gt; [a]</div>
<div>&gt; tail (NE _ as) = as</div><div><br></div><div>We may not be able to construct a non-empty list from a list, if its empty so model that.</div><div><br></div><div>&gt; fromList :: [a] -&gt; Maybe (NE a)</div><div>&gt; fromList (x:xs) = Just (NE x xs)</div>
<div>&gt; fromList [] = Nothing</div><div><br></div><div>We can make our non-empty lists an instance of Foldable so you can use Data.Foldable&#39;s versions of foldl, foldr, etc. and nicely foldl1 has a very pretty total definition, so lets use it.</div>
<div><br></div><div>&gt; instance Foldable NE where</div><div>&gt;    foldr f z (NE a as) = a `f` foldr f z as</div><div>&gt;    foldl f z (NE a as) = foldl f (z `f` a) as</div><div>&gt;    foldl1 f (NE a as) = foldl f a as</div>
<div><br></div><div>We can traverse non-empty lists too.</div><div><br></div><div>&gt; instance Traversable NE where</div><div>&gt;    traverse f (NE a as) = NE &lt;$&gt; f a &lt;*&gt; traverse f as</div><div><br></div><div>
And they clearly offer a monadic structure:</div><div><br></div><div>&gt; instance Monad NE where</div><div>&gt;    return a = NE a []</div><div>&gt;    NE a as &gt;&gt;= f = NE b (bs ++ concatMap (toList . f) as) where</div>
<div>&gt;       NE b bs = f a </div><div><br></div><div>and you can proceed to add suitable instance declarations for it to be a Comonad if you are me, etc.</div><div><br></div><div>Now a singleton list has one representation</div>
<div><br></div><div>NE a []</div><div><br></div><div>A list with two elements can only be represented by NE a [b]</div><div><br></div><div>And so on for NE a [b,c], NE 1 [2..], etc.<br></div><div><br></div><div>You could also make the </div>
<div><br></div><div>&gt; data Container a = Single a | Many a (Container a) </div><div><br></div><div>definition work that Jake McArthur provided. For the category theory inspired reader Jake&#39;s definition is equivalent to the Cofree comonad of the Maybe functor, which can encode a non-empty list.</div>
<div><br></div><div>I leave that one as an exercise for the reader, but observe<br></div><div><br></div><div>Single 1</div><div>Many 1 (Single 2)</div><div>Many 1 (Many 2 (Single 3))</div><div><br></div><div>And the return for this particular monad is easy:</div>
<div><br></div><div>instance Monad Container where </div><div>    return = Single</div><div><br></div><div>In general Jake&#39;s non-empty list is a little nicer because it avoids a useless [] constructor at the end of the list.</div>
<div><br></div><div>-Edward Kmett</div><br><div class="gmail_quote">On Thu, Jun 4, 2009 at 5:53 PM, GüŸnther Schmidt <span dir="ltr">&lt;<a href="mailto:gue.schmidt@web.de">gue.schmidt@web.de</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
Hi,<br>
<br>
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.<br>
<br>
<br>
I started with:<br>
<br>
data Container a = Single a | Many a [a]                <br>
<br>
but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int.<br>
<br>
I can&#39;t figure out how to get this right. :(<br>
<br>
Please help.<br>
<br>
Günther<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br>