Skip to content

Instantly share code, notes, and snippets.

@mpickering
Created September 21, 2021 08:51
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 mpickering/94fc74ff9fd4c2e6ba05ca99ab25ed75 to your computer and use it in GitHub Desktop.
Save mpickering/94fc74ff9fd4c2e6ba05ca99ab25ed75 to your computer and use it in GitHub Desktop.
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TemplateHaskell #-}
-- Used by QuasiQuote. Example taken from the GHC documentation.
module QuasiExpr where
import Language.Haskell.TH
import Language.Haskell.TH.Quote
data Expr = IntExpr Integer
| AntiIntExpr String
| BinopExpr BinOp Expr Expr
| AntiExpr String
deriving Show
data BinOp = AddOp
| SubOp
| MulOp
| DivOp
deriving Show
eval :: Expr -> Integer
eval (IntExpr n) = n
eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y)
where
opToFun AddOp = (+)
opToFun SubOp = (-)
opToFun MulOp = (*)
opToFun DivOp = div
expr = QuasiQuoter parseExprExp undefined undefined undefined
-- cheating...
parseExprExp :: String -> Q Exp
parseExprExp _ = [| BinopExpr AddOp (IntExpr 1) (IntExpr 2) |]
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
-- example taken from the GHC documentation
module QuasiQuote where
import QuasiExpr
val :: Integer
val = eval [expr|1 + 2|]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment