[Haskell-cafe] Re: Deadlock in real number multiplication (Was: Where's the problem ?)

apfelmus apfelmus at quantentunnel.de
Thu Jul 5 05:47:06 EDT 2007


Philip Armstrong wrote:
> genericLength           :: (Num i) => [b] -> i
> genericLength []        =  0
> genericLength (_:l)     =  1 + genericLength l
> 
> So genericLength is lazily building up unevaluated (+) expressions and
> running out of stack space.
> 
> Is there a good reason for genericLength to be lazy?

Yes, since addition in  i  may well be lazy.

  data Nat = Zero | Succ Nat

  instance Num Nat where
     Zero     + b = b
     (Succ a) + b = Succ (a + b)
     ...

  natLength :: [a] -> Nat
  natLength = genericLength

Also, you can turn the foldr into a foldl' with a cleverly chosen data
type like

  data Int' = I Int | Plus Int' Int'

  eval :: Int' -> Int
  eval = eval' 0
     where
     eval' (I i) k      = k + i
     eval' (Plus x y) k = eval' y $! eval' x k

  instance Num Int' where
     (+) = Plus
     ...

or in its bare essence

  newtype DiffInt = DI { unDI :: Int -> Int }

  instance Num DiffInt where
     (+) f g k = DI $ unDI g $! unDI f k

  evalDI :: DiffInt -> Int
  evalDI f = unDI f 0


Regards,
apfelmus



More information about the Haskell-Cafe mailing list