[Haskell-cafe] let and fixed point operator

Derek Elkins derek.a.elkins at gmail.com
Thu Aug 30 12:40:36 EDT 2007


On Thu, 2007-08-30 at 18:17 +0200, Peter Hercek wrote:
> Hi,
> 
> I find the feature that the construct "let x = f x in expr"
>   assigns fixed point of f to x annoying. The reason is that
>   I can not simply chain mofifications a variable like e.g. this:
> 
> f x =
>    let x = x * scale in
>    let x = x + transform in
>    g x

The common answer is that such code is considered ugly in most
circumstances.  Nevertheless, one solution would be to use the Identity
monad and write that as,
f x = runIdentity $ do 
    x <- x*scale
    x <- x + transform
    return (g x)

> 
> When one is lucky then it results in a compile error; in worse
>   cases it results in stack overflow in runtime. The annoying
>   part is figuring out new and 
> new variable names for essentially
>   the same thing to avoid the search/evaluation of the fixed point.
> 
> I suppose Haskell was designed so that it makes sense. The only
>   usage I can see is like this:
> 
> let fact = \x -> if x == 0 then 1 else x * fact (x-1) in
> 
>    ... but that is not any shorter than:
> 
> let fact x = if x == 0 then 1 else x * fact (x-1) in
> 
> So the question is what am I missing? Any nice use cases where
>   fixed point search is so good that it is worth the trouble with
>   figuring out new and new variable names for essentially the same
>   stuff?
> 
> Peter.

Haskell is lazy, we can have (mutually) recursive values.  The canonical
example,
fibs = 0:1:zipWith (+) fibs (tail fibs)
Slightly more interesting,
karplusStrong = y
    where y = map (\x -> 1-2*x) (take 50 (randoms (mkStdGen 1)))
               ++ zipWith (\x y -> (x+y)/2) y (tail y)

However, the real point is that you shouldn't be naming and renaming the
"same" thing.  Going back to your original example, it would be nicer to
most to write it as,
f = g . transform displacement . scale factor
or pointfully
f x = g (transform displacement (scale factor x))
with the appropriate combinators.



More information about the Haskell-Cafe mailing list