[Haskell-cafe] Folding Integrals

Mattias Bengtsson moonlite at dtek.chalmers.se
Tue Dec 11 23:22:58 EST 2007


I found myself writing this for an Euler-problem:

> digits :: Int -> [Int]
> digits i | i < 10    = [i]
>          | otherwise = i `mod` 10 : digits ( i `div` 10 )

And i realised it was quite some time ago (before this function) i had
actually written any explicitly recursive function. I managed to finish
the Euler problem however and i was happy about that.
However it frustrated me that i couldn't find a nice way to abstract
away that explicit recursion but today i managed to! :)
My first thought was that the solution probably was using some function
like scanr, mapAccum or unfoldr to do it (especially the name of unfoldr
made me think that it would be the solution). 
After abstracting my digits function i realised that it wasn't anything
more than a fold over the Int type (treating the Int as a sequence of
digits). "i `mod` 10" and "i `div` 10" would be nothing more than the
head and tail functions (that corresponds to the (:) pattern matching). 

This is what i came up with finally:
(I'm not 100% sure on the foldr- and foldl names though. Not sure if the
semantics are correct, perhaps the function names should be switched?)

> module FoldIntegral (foldr, foldl) where 
> import Prelude hiding (foldr,foldl,head,tail)
> 
> head, tail :: Integral a => a -> a
> head i = i `mod` 10
> tail i = i `div` 10
> 
> foldr :: Integral a => (a -> b -> b) -> b -> a -> b
> foldr f z i 
>     | i == 0    = z
>     | otherwise = foldr f (h `f` z) t
>     where h = head i
>           t = tail i
> 
> foldl :: Integral b => (a -> b -> a) -> a -> b -> a
> foldl f z i 
>     | i == 0    = z
>     | otherwise = (foldl f z t) `f` h
>     where h = head i
>           t = tail i

Which would make the digits function a one-liner:

> digits = foldr (:) [] 

I hope someone enjoys this.

Mattias
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20071212/ac7d60fc/attachment.bin


More information about the Haskell-Cafe mailing list