Created
February 24, 2020 09:57
-
-
Save gdeest/7a2be2b5b43b67ba73f9796a6d2b152b to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings #-} | |
{-# LANGUAGE RecursiveDo #-} | |
import Data.Text.Lazy.IO as T | |
import LLVM.Pretty -- from the llvm-hs-pretty package | |
import LLVM.AST hiding (function) | |
import LLVM.AST.Type as AST | |
import qualified LLVM.AST.Float as F | |
import qualified LLVM.AST.Constant as C | |
import qualified LLVM.AST.Operand as O | |
import qualified LLVM.AST.IntegerPredicate as I | |
import LLVM.IRBuilder.Module | |
import LLVM.IRBuilder.Monad | |
import LLVM.IRBuilder.Instruction | |
import qualified LLVM.Context as Ctx | |
import qualified LLVM.Module as Module | |
import qualified LLVM.Target as Target | |
data Expr | |
= Constant Double | |
| ExprAdd Expr Expr | |
| ExprMul Expr Expr | |
-- evalExpr :: MonadModuleBuilder m => Expr -> IRBuilderT m Operand | |
evalExpr (Constant v) = return $ ConstantOperand $ C.Float $ F.Double v | |
evalExpr (ExprAdd e1 e2) = do | |
r1 <- evalExpr e1 | |
r2 <- evalExpr e2 | |
fadd r1 r2 | |
evalExpr (ExprMul e1 e2) = do | |
r1 <- evalExpr e1 | |
r2 <- evalExpr e2 | |
fmul r1 r2 | |
someExpr :: Expr | |
someExpr = ExprAdd (ExprMul (Constant 3) (Constant 2)) (Constant 7) | |
moduleFoo :: Module | |
moduleFoo = buildModule "foo" $ do | |
function "blah" [] double $ \_ -> do | |
retVal <- evalExpr someExpr | |
ret retVal | |
-- myModule :: Module | |
-- myModule = buildModule "blah" $ do | |
-- function "foo" [(double, "x"), (double, "y")] double $ \[x, y] -> do | |
-- retVal <- fadd x y | |
-- ret retVal | |
main :: IO () | |
-- main = T.putStrLn $ ppllvm moduleFoo | |
main = Ctx.withContext $ \ctx -> do | |
Module.withModuleFromAST ctx moduleFoo $ \llvmMod -> do | |
Target.withHostTargetMachine $ \target -> do | |
Module.writeObjectToFile target (Module.File "truc.o") llvmMod |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment