Skip to content

Instantly share code, notes, and snippets.

@petermarks
Created September 20, 2010 21:05
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save petermarks/588647 to your computer and use it in GitHub Desktop.
Save petermarks/588647 to your computer and use it in GitHub Desktop.
Simple arithmetic expression language
module Expressions where
import Data.Maybe
import Text.Printf
data Expr = Term Int | Op Operator Expr Expr | Var String
deriving (Show, Eq)
data Operator = Sum | Mult | Sub | Div
deriving (Show, Eq)
type Result = Either [String] Int
foldExpr :: (Int -> a) -> (Operator -> a -> a -> a) -> (String -> a) -> Expr -> a
foldExpr ft _ _ (Term i) = ft i
foldExpr ft fo fv (Op o u v) = fo o (foldExpr ft fo fv u) (foldExpr ft fo fv v)
foldExpr ft fo fv (Var id) = fv id
eval :: [(String, Int)] -> Expr -> Result
eval env = foldExpr Right applyOp getV
where
getV x = maybe (Left [x]) Right $ lookup x env
applyOp :: Operator -> Result -> Result -> Result
applyOp o (Right x) (Right y) = Right (getOp o x y)
applyOp _ (Left xs) (Left ys) = Left $ xs ++ ys
applyOp _ (Left xs) _ = Left xs
applyOp _ _ (Left ys) = Left ys
getOp :: Operator -> Int -> Int -> Int
getOp o = case o of
Sum -> (+)
Mult -> (*)
Sub -> (-)
Div -> div
printExpr :: Expr -> String
printExpr = foldExpr show (flip (printf "(%s %s %s)") . printOp) id
printOp o = case o of
Sum -> "+"
Mult -> "*"
Sub -> "-"
Div -> "/"
countTerms :: Expr -> Int
countTerms = foldExpr (const 1) (const (+)) (const 1)
sample = Op Mult (Op Sum (Var "x") (Var "y")) (Term 4)
@willtim
Copy link

willtim commented Sep 21, 2010

I had to change these lines:
26: printExpr = foldExpr show (\o u v -> printf "(%s %s %s)" u (printOp o) v)
35: countTerms = foldExpr (const 1) (_ -> (+))

@petermarks
Copy link
Author

Oops, that was slack. It seems we didn't actually compile that version in our haste at the end of the session. I've corrected it here now.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment