[Haskell-cafe] Thompson's Exercise 9.13

Christoph Bauer ich at christoph-bauer.net
Mon Apr 11 09:59:43 EDT 2005


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))

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

Sure, there is a better solution...

Best Regards,
Christoph Bauer

-- 
let () = let rec f a w i j = Printf.printf "%.20f\r" a; let a1 = a *. i /. j in
if w then f a1 false (i +. 2.0) j else f a1 true i (j +. 2.0) in f 2.0 false 2.0 1.0


More information about the Haskell-Cafe mailing list