[Haskell-cafe] Thompson's Exercise 9.13

Henning Thielemann lemming at henning-thielemann.de
Sun Apr 10 11:44:07 EDT 2005


On Mon, 11 Apr 2005, Christoph Bauer wrote:

> Kaoru Hosokawa <khosokawa at gmail.com> writes:
>
>> I've been working through Thompson's exercises and got to one I could
>> not solve. It's Exercise 9.13. This is where I need to define init
>> using foldr.
>>
>> 	init :: [a] -> [a]
>> 	init "Greggery Peccary" ~> "Greggary Peccar"
>>
>> This is as far as I got:
>>
>> 	init xs = foldr left [] xs
>>
>> 	left :: a -> [a] -> [a]
>> 	left x []	= []
>> 	left x1 : (x2 : xs) = x1 : (left x2 xs)
>>
>> But this returns [] and doesn't work. I can't get "left" to know that
>> it is working with the rightmost element. It just throws away every
>> element when its right hand side is empty.
>>
>> I found a solution that works for Strings, but I am looking for a more
>> general solution. This exercise may yet again be one of those that is
>> difficult to solve with my current knowledge of Haskell, but I'm
>> asking anyway.
>
> Ok, my second haskell program ;-):
>
> module Init where
>
> import Maybe
>
> left :: a -> Maybe [a]  -> Maybe [a]
> left x None = (Just [])
> left x (Just l) =  (Just (x:l))

left x = Just . maybe [] (x:)

> init :: [a] -> [a]
> init xs = fromJust . foldr left Nothing xs

fromMaybe (error "init: empty list")
   instead of fromJust

> Sure, there is a better solution...

Extended question: How to do it without foldr? :-)

init xs = zipWith const xs (tail xs)

But this does not check for empty lists. :-(


More information about the Haskell-Cafe mailing list