[Haskell-cafe] Maybe and partial functions

oleg at pobox.com oleg at pobox.com
Tue Mar 13 06:08:22 EDT 2007


Neil Mitchell wrote:
> I suggest you try rewriting this program to be complete:
>
>  http://darcs.haskell.org/nofib/imaginary/digits-of-e2/Main.lhs
>
> (if you do, please post the result to the list)

As Gen Zhang noted, the problem seems to be quite straightforward:
just express in types the fact that we deal with infinite streams and
so Nil just cannot happen. One way of doing this as follows. Showing
totality (that is, termination of recursion in carry propagate) is
harder. But re-writing the program so to avoid head/tail on the empty
list is easy:

module E where

import Prelude hiding (head, tail, map, iterate, take)

data I a = C a (I a) deriving Show

-- these are total functions: they give WHNF in one step provided non-bottom
-- arguments
head (C a _) = a
tail (C _ l) = l
map f (C a l) = C (f a) (map f l)
rept a = C a (rept a)

take n (C a l) | n > 0 = a:take (n-1) l
take _ _ = []


iterate f z = C z (iterate f (f z))

-- There are no pattern-matching failures here.
-- The totality is harder to see: all digits are roughly of the same range,
-- but each recursive call increments base. Eventually, base becomes bigger
-- than d+9 and so the first alternative will be selected, which is in the
-- WHNF and so recursion terminates.
carryPropagate base (C d ds)
   | carryguess == (d+9) `div` base
       = C carryguess (C (remainder+nextcarry) fraction)
   | otherwise
       = (C (dCorrected `div` base) (C (dCorrected `mod` base) fraction))
  where carryguess = d `div` base
        remainder = d `mod` base
        C nextcarry fraction = carryPropagate (base+1) ds
        dCorrected = d + nextcarry

e =  map (show.head) $
     iterate (carryPropagate 2 . map (10*) . tail) $
     C 2 (rept 1)

en n = "2." ++ concat (take n (tail e))



More information about the Haskell-Cafe mailing list