I want to create parser-like behaviour in Haskell such that I can assign an expression to a variable based on a string. I have difficulties doing so.
If I have types with the following definitions:
data Expr =
Numb Int
| Add Expr Expr
| Let {var :: PVariable, definition, body :: Expr}
type PVariable = String
And want to create a function 'eval' that would be able to handle different operations such as Add, Subtract, Multiply etc... but also the Let binding, sucht that 'eval' would be subject to the following definition:
eval :: Exp -> Integer
eval (Number expr) = expr
eval (Add expr1 expr2) = eval(expr1) eval(expr2)
...
eval (Let v expr1 body) = ...
How could I then create eval such that it would assign an expr1 to the string v, that would then be expressed in the body, such that the parser-like behaviour could accomplish for instance something similar to the conversion from:
Let {var = "Var1", definition = expr1, body = (Add (Var "Var1") (Var "Var1"))}
where expr1 would be a chosen expression such that the above could be expressed as
let Var1 = expr1 in expr1 expr1
That could then have different Expr assigned to expr1 such as (Numb 2), so that we would get something similar to the following in Haskell:
let Var1 = 2 in Var1 Var1
So far I have tried to deal with isolating fields of the record 'Let' so that I can evaluate each of these considering that I want to stay with the function type declarations. But I don't think that this is the easiest way, and it would probably require that I create a whole function to extract these, as far as I can see from : How to generically extract field names and values in Haskell records
Is there a smarter way to go about it?
CodePudding user response:
You'll need the function eval
to have extra argument that would contain the variable bindings and pass it to subexpressions recursively. You also need a special case to evaluate Var
-expressions:
module Main where
import qualified Data.Map as M
data Expr =
Numb Int
| Add Expr Expr
| Let {var :: PVariable, definition, body :: Expr}
| Var PVariable
type PVariable = String
type Env = M.Map PVariable Int
eval :: Env -> Expr -> Int
eval _ (Numb a) = a
eval env (Add e1 e2) = (eval env e1) (eval env e2)
eval env (Var v) = M.findWithDefault (error $ "undefined variable: " v) v env
eval env (Let v expr body) = let
val = eval env expr
env' = M.insert v val env
in eval env' body
main = print $ eval M.empty $ Let "a" (Numb 1) (Add (Var "a") (Numb 2))