[Haskell-cafe] Proposal: Non-recursive let
Andreas Abel
andreas.abel at ifi.lmu.de
Wed Jul 17 00:42:03 CEST 2013
Ah, now I have the solution:
{-# LANGUAGE CPP #-}
(|>) = flip ($)
#define LET(p, e) (e) |> \ (p) ->
bla = LET(x, 5)
LET(Just x, Just (x+1))
x
#define MLET(p, e) (e) |> \ (p) -> do
main = do
MLET((x, y), (5, 3))
print (x + y)
Beautiful, ain't it? Sigh.
--Andreas
On 11.07.2013 17:40, Carter Schonwald wrote:
> Yup. Nested cases *are* non recursive lets.
>
> (Can't believe I forgot about that )
>
> On Thursday, July 11, 2013, Edward Kmett wrote:
>
>
> blah = case foo 1 [] of
> (x, s) -> case bar x s of
> (y, s) -> case baz x y s of
> (z, s) -> ...
>
> -Edward
--
Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel at ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/
More information about the Haskell-Cafe
mailing list