[Haskell-cafe] Thompson's Exercise 9.13
Daniel Fischer
daniel.is.fischer at web.de
Sun Apr 10 13:22:13 EDT 2005
Am Montag, 11. April 2005 15:59 schrieb Christoph Bauer:
>
> Ok, my second haskell program ;-):
>
> module Init where
>
> import Maybe
>
> left :: a -> Maybe [a] -> Maybe [a]
> left x None = (Just [])
^^^^^^^^
Nothing, as below :-)
> left x (Just l) = (Just (x:l))
>
> init :: [a] -> [a]
> init xs = fromJust . foldr left Nothing xs
>
> Sure, there is a better solution...
I don't think so. As far as I see, it's impossible to do it with just
init xs = foldr fun val xs,
(unless we use some dirty trick)
because we must have
fun x (init ys) = x:init ys
for any nonempty list ys and
init [] = val
forces val to be 'error "init of empty List"' or something of the sort and
this has to be evaluated when we reach the end of the list, for we would need
fun _ (error "blah") = []
for nonempty lists.
Dirty trick: unsafePerformIO
import System.IO.Unsafe
fun :: a -> [a] -> [a]
fun x xs = unsafePerformIO ((xs `seq` (return (x:xs))) `catch`
(\ _ -> return []))
init3 :: [a] -> [a]
init3 = foldr fun (unsafePerformIO (ioError (userError "init of []")))
*Init> init3 []
*** Exception: user error (init of [])
*Init> init3 [1]
[]
*Init> init3 [1 .. 10]
[1,2,3,4,5,6,7,8,9]
Though this works, it is utterly horrible and despicable. DON'T DO THAT!!!!!
>
> Best Regards,
> Christoph Bauer
Cheers,
Daniel
More information about the Haskell-Cafe
mailing list