Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How can I return a lambda with guards and double recursion?

I made this function in Python:

def calc(a): return lambda op: {
    '+': lambda b: calc(a+b),
    '-': lambda b: calc(a-b),
    '=': a}[op]

So you can make a calculation like this:

calc(1)("+")(1)("+")(10)("-")(7)("=")

And the result will be 5.

I wanbt to make the same function in Haskell to learn about lambdas, but I am getting parse errors.

My code looks like this:

calc :: Int -> (String -> Int)
calc a = \ op 
    | op == "+" = \ b calc a+b
    | op == "-" = \ b calc a+b
    | op == "=" = a

main = calc 1 "+" 1 "+" 10 "-" 7 "="
like image 340
mama Avatar asked Nov 28 '21 20:11

mama


People also ask

Can lambda functions be recursive?

But a lambda cannot be recursive, it has no way to invoke itself. A lambda has no name and using this within the body of a lambda refers to a captured this (assuming the lambda is created in the body of a member function, otherwise it is an error).

Can lambda function call itself?

A recursive lambda expression is the process in which a function calls itself directly or indirectly is called recursion and the corresponding function is called a recursive function. Using a recursive algorithm, certain problems can be solved quite easily.

What is Lambda recursion?

This custom LAMBDA formula illustrates a feature called recursion, in which a function calls itself. Note: the LAMBDA function is available through the beta channel of Excel 365 only. The LAMBDA function can be used to create custom, reusable functions in Excel. This example illustrates a feature called recursion, in which a function calls itself.

How do you bail out of a recursive lambdas loop?

A key component of writing recursive lambdas is to provide it with an opportunity to bail out of the recursive loop. In the formula above I’ve done this with IF. That is, when n gets to less than 2, n is simply 1 and the formula can stop evaluating there without moving on to the recursive part.

Which lambda function can be used in as many sorting methods?

Explanation: Here, auto cmp is the lambda stored function that can be used in as many sorting methods. Recursion Using Lambda: Let’s discuss the concept of recursion and lambda expressions together by considering the recursive function below:

How to return a variable from a lambda expression?

If you have more than one line of code in Lambda expression and you are using the curly braces ( { }). Then you need to return the statement. You need to write the object/variable with the return statement which you want to return.


Video Answer


4 Answers

There are numerous syntactical problems with the code you have posted. I won't address them here, though: you will discover them yourself after going through a basic Haskell tutorial. Instead I'll focus on a more fundamental problem with the project, which is that the types don't really work out. Then I'll show a different approach that gets you the same outcome, to show you it is possible in Haskell once you've learned more.

While it's fine in Python to sometimes return a function-of-int and sometimes an int, this isn't allowed in Haskell. GHC has to know at compile time what type will be returned; you can't make that decision at runtime based on whether a string is "=" or not. So you need a different type for the "keep calcing" argument than the "give me the answer" argument.

This is possible in Haskell, and in fact is a technique with a lot of applications, but it's maybe not the best place for a beginner to start. You are inventing continuations. You want calc 1 plus 1 plus 10 minus 7 equals to produce 5, for some definitions of the names used therein. Achieving this requires some advanced features of the Haskell language and some funny types1, which is why I say it is not for beginners. But, below is an implementation that meets this goal. I won't explain it in detail, because there is too much for you to learn first. Hopefully after some study of Haskell fundamentals, you can return to this interesting problem and understand my solution.

calc :: a -> (a -> r) -> r
calc x k = k x

equals :: a -> a
equals = id

lift2 :: (a -> a -> a) -> a -> a -> (a -> r) -> r
lift2 f x y = calc (f x y)

plus :: Num a => a -> a -> (a -> r) -> r
plus = lift2 (+)

minus :: Num a => a -> a -> (a -> r) -> r
minus = lift2 (-)
ghci> calc 1 plus 1 plus 10 minus 7 equals
5

1 Of course calc 1 plus 1 plus 10 minus 7 equals looks a lot like 1 + 1 + 10 - 7, which is trivially easy. The important difference here is that these are infix operators, so this is parsed as (((1 + 1) + 10) - 7), while the version you're trying to implement in Python, and my Haskell solution, are parsed like ((((((((calc 1) plus) 1) plus) 10) minus) 7) equals) - no sneaky infix operators, and calc is in control of all combinations.

like image 150
amalloy Avatar answered Oct 13 '22 23:10

amalloy


chi's answer says you could do this with "convoluted type class machinery", like printf does. Here's how you'd do that:

{-# LANGUAGE ExtendedDefaultRules #-}

class CalcType r where
    calc :: Integer -> String -> r

instance CalcType r => CalcType (Integer -> String -> r) where
    calc a op
        | op == "+" = \ b -> calc (a+b)
        | op == "-" = \ b -> calc (a-b)

instance CalcType Integer where
    calc a op
        | op == "=" = a

result :: Integer
result = calc 1 "+" 1 "+" 10 "-" 7 "="

main :: IO ()
main = print result

If you wanted to make it safer, you could get rid of the partiality with Maybe or Either, like this:

{-# LANGUAGE ExtendedDefaultRules #-}

class CalcType r where
    calcImpl :: Either String Integer -> String -> r

instance CalcType r => CalcType (Integer -> String -> r) where
    calcImpl a op
        | op == "+" = \ b -> calcImpl (fmap (+ b) a)
        | op == "-" = \ b -> calcImpl (fmap (subtract b) a)
        | otherwise = \ b -> calcImpl (Left ("Invalid intermediate operator " ++ op))

instance CalcType (Either String Integer) where
    calcImpl a op
        | op == "=" = a
        | otherwise = Left ("Invalid final operator " ++ op)

calc :: CalcType r => Integer -> String -> r
calc = calcImpl . Right

result :: Either String Integer
result = calc 1 "+" 1 "+" 10 "-" 7 "="

main :: IO ()
main = print result

This is rather fragile and very much not recommended for production use, but there it is anyway just as something to (eventually?) learn from.

like image 22
Joseph Sible-Reinstate Monica Avatar answered Oct 13 '22 21:10

Joseph Sible-Reinstate Monica


Here is a simple solution that I'd say corresponds more closely to your Python code than the advanced solutions in the other answers. It's not an idiomatic solution because, just like your Python one, it will use runtime failure instead of types in the compiler.

So, the essence in you Python is this: you return either a function or an int. In Haskell it's not possible to return different types depending on runtime values, however it is possible to return a type that can contain different data, including functions.

data CalcResult = ContinCalc (Int -> String -> CalcResult)
                | FinalResult Int

calc :: Int -> String -> CalcResult
calc a "+" = ContinCalc $ \b -> calc (a+b)
calc a "-" = ContinCalc $ \b -> calc (a-b)
calc a "=" = FinalResult a

For reasons that will become clear at the end, I would actually propose the following variant, which is, unlike typical Haskell, not curried:

calc :: (Int, String) -> CalcResult
calc (a,"+") = ContinCalc $ \b op -> calc (a+b,op)
calc (a,"-") = ContinCalc $ \b op -> calc (a-b,op)
calc (a,"=") = FinalResult a

Now, you can't just pile on function applications on this, because the result is never just a function – it can only be a wrapped function. Because applying more arguments than there are functions to handle them seems to be a failure case, the result should be in the Maybe monad.

contin :: CalcResult -> (Int, String) -> Maybe CalcResult
contin (ContinCalc f) (i,op) = Just $ f i op
contin (FinalResult _) _ = Nothing

For printing a final result, let's define

printCalcRes :: Maybe CalcResult -> IO ()
printCalcRes (Just (FinalResult r)) = print r
printCalcRes (Just _) = fail "Calculation incomplete"
printCalcRes Nothing = fail "Applied too many arguments"

And now we can do

ghci> printCalcRes $ contin (calc (1,"+")) (2,"=")
3

Ok, but that would become very awkward for longer computations. Note that we have after two operations a Maybe CalcResult so we can't just use contin again. Also, the parentheses that would need to be matched outwards are a pain.

Fortunately, Haskell is not Lisp and supports infix operators. And because we're anyways getting Maybe in the result, might as well include the failure case in the data type.

Then, the full solution is this:

data CalcResult = ContinCalc ((Int,String) -> CalcResult)
                | FinalResult Int
                | TooManyArguments

calc :: (Int, String) -> CalcResult
calc (a,"+") = ContinCalc $ \(b,op) -> calc (a+b,op)
calc (a,"-") = ContinCalc $ \(b,op) -> calc (a-b,op)
calc (a,"=") = FinalResult a

infixl 9 #
(#) :: CalcResult -> (Int, String) -> CalcResult
ContinCalc f # args = f args
_ # _ = TooManyArguments

printCalcRes :: CalcResult -> IO ()
printCalcRes (FinalResult r) = print r
printCalcRes (ContinCalc _) = fail "Calculation incomplete"
printCalcRes TooManyArguments = fail "Applied too many arguments"

Which allows to you write

ghci> printCalcRes $ calc (1,"+") # (2,"+") # (3,"-") # (4,"=")
2
like image 5
leftaroundabout Avatar answered Oct 13 '22 22:10

leftaroundabout


A Haskell function of type A -> B has to return a value of the fixed type B every time it's called (or fail to terminate, or throw an exception, but let's neglect that).

A Python function is not similarly constrained. The returned value can be anything, with no type constraints. As a simple example, consider:

def foo(b):
   if b:
      return 42        # int
   else:
      return "hello"   # str

In the Python code you posted, you exploit this feature to make calc(a)(op) to be either a function (a lambda) or an integer.

In Haskell we can't do that. This is to ensure that the code can be type checked at compile-time. If we write

bar :: String -> Int
bar s = foo (reverse (reverse s) == s)

the compiler can't be expected to verify that the argument always evaluates to True -- that would be undecidable, in general. The compiler merely requires that the type of foo is something like Bool -> Int. However, we can't assign that type to the definition of foo shown above.

So, what we can actually do in Haskell?

One option could be to abuse type classes. There is a way in Haskell to create a kind of "variadic" function exploiting some kind-of convoluted type class machinery. That would make

calc 1 "+" 1 "+" 10 "-" 7 :: Int

type-check and evaluate to the wanted result. I'm not attempting that: it's complex and "hackish", at least in my eye. This hack was used to implement printf in Haskell, and it's not pretty to read.

Another option is to create a custom data type and add some infix operator to the calling syntax. This also exploits some advanced feature of Haskell to make everything type check.

{-# LANGUAGE GADTs, FunctionalDependencies, TypeFamilies, FlexibleInstances #-}

data R t where
   I :: Int -> R String
   F :: (Int -> Int) -> R Int

instance Show (R String) where
    show (I i) = show i

type family Other a where
   Other String = Int
   Other Int    = String

(#) :: R a -> a -> R (Other a)
I i # "+" = F (i+)   -- equivalent to F (\x -> i + x)
I i # "-" = F (i-)   -- equivalent to F (\x -> i - x)
F f # i   = I (f i)
I _ # s   = error $ "unsupported operator " ++ s

main :: IO ()
main =
   print (I 1 # "+" # 1 # "+" # 10 # "-" # 7)

The last line prints 5 as expected.

The key ideas are:

  • The type R a represents an intermediate result, which can be an integer or a function. If it's an integer, we remember that the next thing in the line should be a string by making I i :: R String. If it's a function, we remember the next thing should be an integer by having F (\x -> ...) :: R Int.

  • The operator (#) takes an intermediate result of type R a, a next "thing" (int or string) to process of type a, and produces a value in the "other type" Other a. Here, Other a is defined as the type Int (respectively String) when a is String (resp. Int).

like image 4
chi Avatar answered Oct 13 '22 23:10

chi