A new list type

From HaskellWiki
Jump to navigation Jump to search

Does anybody find this amusing?

module XList where

import Prelude hiding (length, head, tail, foldr, foldl, map, zip, zipWith, replicate)

data List t = Node {length_ :: Int, head :: t, tail :: List t} | End   deriving (Eq, Show)

length End = 0
length n   = length_ n

infixr 5 #:

x #: xs = Node (1 + length xs) x xs

foldr _ v (End)         = v
foldr f v (Node _ x xs) = f x (foldr f v xs)

foldl _ v (End)         = v
foldl f v (Node _ x xs) = foldl f (v `f` x) xs

foldl' _ v (End)         = v
foldl' f v (Node _ x xs) = (foldl' f $! v `f` x) xs

map _ (End)         = End
map f (Node n x xs) = Node n (f x) (map f xs)

zipWith f (End) _ = End
zipWith f _ (End) = End
zipWith f (Node n0 x xs) (Node n1 y ys) = Node (n0 `min` n1) (f x y) (zipWith f xs ys)

zip = zipWith (\x y -> (x,y))

join (End)         ys = ys
join (Node n x xs) ys = Node (n + length ys) x (join xs ys)

merge = foldr join End

select _ End = End
select f (Node n x xs) = case f x of
  True  -> x #: select f xs
  False -> select f xs

replicate 0 _ = End
replicate n x = Node n x (replicate (n-1) x)

Somebody (a non Haskeller) said that having to traverse a potentially large linked list merely to compute its size is unnecessarily wasteful. Whether or not you agree with that statement, the above (which is obviously incomplete) is what I came up with to address this criticism. (You might argue that linked lists just plain aren't a good idea for very large structures.)

Of course, in the presence of lazy evaluation, all is not quite that simple. Functions that generate known-size lists (e.g., replicate) can add size information as they build it. If map is applied to a list who's size is known, the size of the result is known. (Interestingly, if it isn't known, then presumably asking for the size of the result also computes and stores the size of the source list - if anybody still has it.) The really interesting case is select (which is equivalent to Prelude.filter, but with a less brain-dead name).

Anybody else have any insightful or amusing comments?

MathematicalOrchid 13:28, 14 February 2007 (UTC)

"traversing a potentially large linked list merely to compute its size is unnecessarily wasteful." Especially when it's infinite. See Things to avoid for why you should try to avoid calling length. Although it probably requires quite a change of mindset for a non-Haskeller to appreciate that.

Remi

Agreed; trying to count the elements in an infinite list would be a Bad Idea. ;-)

This came up in a discussion of sorting algorithms. You might want to choose which algorithm to apply depending on how big the list is - but not much point doing that if it takes longer to figure out how big the list is then to just use the first algorithm to hand! (Note that a sorting algorithm can never work on an infinite list.)

For the special case of a sorting algorithm, it might be simpler to just count the size of the list once, and then manually manage that information throughout the sorting process. (Rather than, as above, defining a whole new datatype and redefining all of the prelude on it.)

I thought I would post it because it's an interesting idea though.

MathematicalOrchid 15:32, 14 February 2007 (UTC)