-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Add RISC-V code generation - Integrate RISC-V code generation into the app - Add command to print the c runtime
- Loading branch information
1 parent
ca27157
commit d96ae03
Showing
22 changed files
with
1,772 additions
and
6 deletions.
There are no files selected for viewing
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
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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,16 @@ | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
|
||
module Commands.PrintCRuntime (printCRuntime) where | ||
|
||
import qualified CodeGen.Runtime.PrintRuntime as R | ||
import Configuration.AppConfiguration (Output (..), PrintCRuntime (..)) | ||
|
||
printCRuntime :: PrintCRuntime -> IO () | ||
printCRuntime (PrintCRuntime output) = do | ||
R.printCRuntime $ outputToFilePath output | ||
|
||
outputToFilePath :: Output -> FilePath | ||
outputToFilePath = \case | ||
FileOutput filePath -> filePath | ||
AutoFileOutput -> "runtime.c" |
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
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
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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,34 @@ | ||
module Configuration.Commands.PrintCRuntime (printCRuntime) where | ||
|
||
import Configuration.AppConfiguration | ||
import Options.Applicative | ||
|
||
printCRuntime :: Mod CommandFields Command | ||
printCRuntime = command "print-c-runtime" compileParserInfo | ||
|
||
compileParserInfo :: ParserInfo Command | ||
compileParserInfo = info printCRuntimeParser printCRuntimeInfoMod | ||
|
||
printCRuntimeParser :: Parser Command | ||
printCRuntimeParser = | ||
CmdPrintCRuntime . PrintCRuntime <$> outputParser | ||
|
||
printCRuntimeInfoMod :: InfoMod a | ||
printCRuntimeInfoMod = | ||
fullDesc | ||
<> header "Print C runtime" | ||
<> progDesc "Print C runtime" | ||
|
||
outputParser :: Parser Output | ||
outputParser = fileOutputP <|> defaultP | ||
where | ||
fileOutputP = | ||
FileOutput | ||
<$> strOption | ||
( long "output" | ||
<> short 'o' | ||
<> metavar "OUTPUT" | ||
<> help "Output file path (default: runtime.c)" | ||
) | ||
|
||
defaultP = pure AutoFileOutput |
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
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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,166 @@ | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE RecursiveDo #-} | ||
|
||
module CodeGen.RiscV.AsmGen (ppRiscVAsm) where | ||
|
||
import CodeGen.Module (Module (..)) | ||
import qualified CodeGen.RiscV.Lib as Rv | ||
import Control.Monad.State (MonadState, State, evalState, gets, modify) | ||
import Data.Map (Map) | ||
import qualified Data.Map as Map | ||
import Data.Text (Text) | ||
import qualified Data.Text as Txt | ||
import Foreign (fromBool) | ||
import MonadUtils (locally) | ||
import qualified StdLib | ||
import Transformations.Anf.Anf | ||
import Trees.Common | ||
|
||
ppRiscVAsm :: Module -> Text | ||
ppRiscVAsm m = Rv.ppCodeLines $ genModule m | ||
|
||
-- The Code | ||
|
||
type CodeGenM = Rv.AsmBuilderT (State Env) | ||
|
||
data Env = Env | ||
{ locVars :: Map Identifier' Rv.Operand, | ||
globVars :: Map Identifier' Rv.Operand, | ||
funs :: Map Identifier' (Rv.Operand, Arity) | ||
} | ||
|
||
genModule :: Module -> [Rv.CodeLine] | ||
genModule (Module (Program decls)) = flip evalState (Env Map.empty Map.empty Map.empty) $ | ||
Rv.compileT $ do | ||
mapM_ genStdLibDecl StdLib.allDeclsWithArity | ||
mapM_ genGlobDecl decls | ||
|
||
-- In the `main` we define our global variables. | ||
Rv.mainFunction $ \_ -> mapM_ gVarDef decls | ||
where | ||
gVarDef :: GlobalDeclaration -> CodeGenM () | ||
gVarDef = \case | ||
GlobVarDecl ident value -> do | ||
addr <- findGlobVar ident | ||
value' <- genExpr value | ||
Rv.storeToLabeledAddr addr value' | ||
_ -> return () | ||
|
||
genStdLibDecl :: StdLib.DeclarationWithArity -> CodeGenM () | ||
genStdLibDecl decl = declareAsExtern decl >>= register decl | ||
where | ||
declareAsExtern :: StdLib.DeclarationWithArity -> CodeGenM Rv.Operand | ||
declareAsExtern (ident, _) = Rv.externFunction ident | ||
|
||
register :: StdLib.DeclarationWithArity -> Rv.Operand -> CodeGenM () | ||
register (ident, arity) fun = regFun (Txt ident) fun arity | ||
|
||
genGlobDecl :: GlobalDeclaration -> CodeGenM () | ||
genGlobDecl = \case | ||
GlobVarDecl ident _ -> do | ||
var <- Rv.globalVar (Txt.pack $ genId ident) | ||
regGlobVar ident var | ||
GlobFunDecl ident params body -> mdo | ||
regFun ident fun (length params) | ||
fun <- locally $ do | ||
Rv.function | ||
(Txt.pack $ genId ident) | ||
(fromIntegral $ length params) | ||
$ \args -> do | ||
mapM_ (uncurry regLocVar) (params `zip` args) | ||
genExpr body | ||
return () | ||
|
||
genId :: Identifier' -> String | ||
genId = \case | ||
Txt txt -> Txt.unpack txt | ||
Gen n txt -> Txt.unpack txt <> "_" <> show n | ||
|
||
genExpr :: Expression -> CodeGenM Rv.Operand | ||
genExpr = \case | ||
ExprAtom atom -> genAtom atom | ||
ExprComp ce -> genComp ce | ||
ExprLetIn (ident, val) expr -> do | ||
val' <- genExpr val | ||
regLocVar ident val' | ||
genExpr expr | ||
|
||
genAtom :: AtomicExpression -> CodeGenM Rv.Operand | ||
genAtom = \case | ||
AtomId ident -> findAny ident | ||
AtomUnit -> Rv.immediate 0 | ||
AtomBool bool -> Rv.immediate $ fromBool bool | ||
AtomInt int -> Rv.immediate int | ||
|
||
genComp :: ComplexExpression -> CodeGenM Rv.Operand | ||
genComp = \case | ||
CompApp f arg -> do | ||
f' <- findAny f | ||
arg' <- genAtom arg | ||
applyF <- findFun (Txt "miniml_apply") | ||
Rv.call applyF [f', arg'] | ||
CompIte c t e -> do | ||
c' <- genAtom c | ||
Rv.ite c' (\_ -> genExpr t) (\_ -> genExpr e) | ||
CompBinOp op lhs rhs -> do | ||
lhs' <- genAtom lhs | ||
rhs' <- genAtom rhs | ||
let opF = case op of | ||
BoolOp AndOp -> Rv.and | ||
BoolOp OrOp -> Rv.or | ||
ArithOp PlusOp -> Rv.add | ||
ArithOp MinusOp -> Rv.sub | ||
ArithOp MulOp -> Rv.mul | ||
ArithOp DivOp -> | ||
( \lhs'' rhs'' -> do | ||
divF <- findFun (Txt "miniml_div") | ||
Rv.call divF [lhs'', rhs''] | ||
) | ||
CompOp EqOp -> Rv.eq | ||
CompOp NeOp -> Rv.ne | ||
CompOp LtOp -> Rv.lt | ||
CompOp LeOp -> Rv.le | ||
CompOp GtOp -> Rv.gt | ||
CompOp GeOp -> Rv.ge | ||
opF lhs' rhs' | ||
CompUnOp op x -> do | ||
x' <- genAtom x | ||
let opF = case op of | ||
UnMinusOp -> Rv.neg | ||
opF x' | ||
|
||
-- Vars & Funs | ||
|
||
findAny :: Identifier' -> CodeGenM Rv.Operand | ||
findAny ident = do | ||
maybeLocVar <- gets ((Map.!? ident) . locVars) | ||
case maybeLocVar of | ||
Just locVar -> return locVar | ||
Nothing -> do | ||
maybeFun <- gets ((Map.!? ident) . funs) | ||
case maybeFun of | ||
Just (fun, arity) -> do | ||
funToPafF <- findFun (Txt "miniml_fun_to_paf") | ||
arity' <- Rv.immediate $ fromIntegral arity | ||
Rv.call funToPafF [fun, arity'] | ||
Nothing -> findGlobVar ident | ||
|
||
findGlobVar :: (MonadState Env m) => Identifier' -> m Rv.Operand | ||
findGlobVar ident = gets ((Map.! ident) . globVars) | ||
|
||
findFun :: Identifier' -> CodeGenM Rv.Operand | ||
findFun ident = gets (fst . (Map.! ident) . funs) | ||
|
||
regLocVar :: (MonadState Env m) => Identifier' -> Rv.Operand -> m () | ||
regLocVar ident var = modify $ | ||
\env -> env {locVars = Map.insert ident var (locVars env)} | ||
|
||
regGlobVar :: (MonadState Env m) => Identifier' -> Rv.Operand -> m () | ||
regGlobVar ident gVar = modify $ | ||
\env -> env {globVars = Map.insert ident gVar (globVars env)} | ||
|
||
regFun :: (MonadState Env m) => Identifier' -> Rv.Operand -> Arity -> m () | ||
regFun ident fun paramsCnt = modify $ | ||
\env -> env {funs = Map.insert ident (fun, paramsCnt) (funs env)} |
Oops, something went wrong.