[Haskell-cafe] Re: let and fixed point operator

Peter Hercek peter at syncad.com
Thu Aug 30 13:16:59 EDT 2007


Derek Elkins wrote:
> 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)

This is nice but more complicated. The goal should be to have it
  as simple as possible.


> 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)

This is very nice argument! Thanks. I actually used it myself, but did
  not realize it when I was looking for the pro/contra arguments. This
  with the fact that it is not that good style to use the same name for
  intermediate results might be worth it.


> 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.

Essentially the same idea as the one from Brent Yorgey.
Works fine till the operations can fill easily on one line. Then it does not
  scale that well since when it needs to be on more lines it interferes with
  automatic insertion of curly braces and semicolons by the layout rules (which
  are influenced by the context). Of course when there are more transformations
  it makes sense to name the intermediate results differently, but even few
  transformations may not fit easily when identifier names are long.

Thanks,
Peter.



More information about the Haskell-Cafe mailing list