Skip to content

Instantly share code, notes, and snippets.

@cblp
Created August 28, 2022 08:11
Show Gist options
  • Save cblp/87070c6a98e9bd381ac708d7b3dc93b3 to your computer and use it in GitHub Desktop.
Save cblp/87070c6a98e9bd381ac708d7b3dc93b3 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE LambdaCase #-}
import Control.Monad.State
data Action
= For Expr (Expr -> Action)
| Print Expr
data Expr
= Var String
| Range Int
| Literal Integer
| Mult Expr Expr
instance Num Expr where
(*) = Mult
fromInteger = Literal
interpret :: Action -> String
interpret action = evalState (interpretAction action) 0
interpretAction :: Action -> State Int String
interpretAction = \case
For seq body -> do
var <- freshVar
body' <- interpretAction (body $ Var var)
pure $ unwords ["for", var, "in", interpretExpr seq, "{", body', "}"]
Print expr -> pure $ "print(" <> interpretExpr expr <> ")"
freshVar :: State Int String
freshVar = state \i -> ("var" ++ show i, i + 1)
interpretExpr :: Expr -> String
interpretExpr = \case
Var v -> v
Range i -> "range(" ++ show i ++ ")"
Literal i -> show i
Mult a b -> "(" ++ interpretExpr a ++ " * " ++ interpretExpr b ++ ")"
program = For (Range 10) \i -> Print (2 * i)
-- $> print $ interpret program
-- "for var0 in range(10) { print((2 * var0)) }"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment