[Haskell-beginners] Re: defining 'init' in terms of 'foldr'

Heinrich Apfelmus apfelmus at quantentunnel.de
Tue May 12 07:31:32 EDT 2009


Michael Mossey wrote:
> In S. Thompson's book, problem 9.13 asks us to define 'init' in terms of
> foldr. I was baffled at first because I didn't see a natural way to do
> this. It would look something like
> 
> init xs = foldr f initialValue xs
> 
> where f would cons on each character except the rightmost.
> 
> f <when passed rightmost char> b = []
> f <when passed any other char a> b = a : b
> 
> How does f "know" when it is passed the first character? initialValue
> has to signal this somehow. On #haskell, one person suggested doing it
> with some post-processing:
> 
> init xs = snd $ foldr f (True,[]) xs
>   where f _  (True,_)  = (False,[])
>         f a  (False,b) = (False,a:b)
> 
> I had an idea. If the initial value is the entire list, then its length
> can function as the "signal" that we are dealing with the rightmost
> char. This requires no post-processing:
> 
> init xs = foldr f xs xs
>    where f a b | length b == length xs = []
>                | otherwise = a:b
> 
> These seem contrived. I wonder if there is a more natural solution that
> Thompson had in mind. Any comments?

It is best to see  foldr f b  as an operation that takes a list

  x0 : x1 : x2 : ... : []

and replaces every (:) with  f  and the [] with  b :

  x0 `f` x1 `f` x2 `f` ... `f` b

See also

  http://en.wikipedia.org/wiki/Fold_(higher-order_function)

for Cale's nice pictures.


It is then clear that we have to choose  b  to signal the end of the
list. Furthermore,  b  should be the same as  init [] . Unfortunately,
this expression is a run-time error, but this is a fault of the type
signature

  init :: [a] -> [a]

which should really be

  init' :: [a] -> Maybe [a]

to make it clear that some lists like the empty one simply don't have an
initial segment. And this version has a natural implementation in terms
of  foldr :

  init' = foldr f Nothing
     where
     f _ Nothing   = Just []
     f x (Just xs) = Just (x:xs)

Of course, we need some post-processing to obtain the original  init
from this, but I think that it's very natural.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



More information about the Beginners mailing list