Add stage options
This commit is contained in:
parent
fbd08f2707
commit
a1c9910300
@ -16,6 +16,7 @@ common warnings
|
||||
build-depends:
|
||||
base >=4.7 && <5,
|
||||
bytestring ^>= 0.12.1,
|
||||
filepath ^>= 1.5.3,
|
||||
megaparsec ^>= 9.6,
|
||||
optparse-applicative ^>= 0.18.1,
|
||||
vector ^>= 0.13.1,
|
||||
@ -36,7 +37,8 @@ library elna-internal
|
||||
Language.Elna.Architecture.RiscV
|
||||
Language.Elna.Backend.Allocator
|
||||
Language.Elna.Backend.Intermediate
|
||||
Language.Elna.CommandLine
|
||||
Language.Elna.Driver
|
||||
Language.Elna.Driver.CommandLine
|
||||
Language.Elna.Frontend.AST
|
||||
Language.Elna.Frontend.NameAnalysis
|
||||
Language.Elna.Frontend.Parser
|
||||
@ -62,8 +64,7 @@ executable elna
|
||||
import: warnings
|
||||
main-is: Main.hs
|
||||
build-depends:
|
||||
elna:elna-internal,
|
||||
filepath ^>= 1.5.3
|
||||
elna:elna-internal
|
||||
hs-source-dirs: src
|
||||
|
||||
test-suite elna-test
|
||||
|
@ -1,48 +0,0 @@
|
||||
{- This Source Code Form is subject to the terms of the Mozilla Public License,
|
||||
v. 2.0. If a copy of the MPL was not distributed with this file, You can
|
||||
obtain one at https://mozilla.org/MPL/2.0/. -}
|
||||
|
||||
module Language.Elna.CommandLine
|
||||
( CommandLine(..)
|
||||
, commandLine
|
||||
, execParser
|
||||
) where
|
||||
|
||||
import Options.Applicative
|
||||
( Parser
|
||||
, ParserInfo(..)
|
||||
, argument
|
||||
, execParser
|
||||
, fullDesc
|
||||
, help
|
||||
, helper
|
||||
, info
|
||||
, long
|
||||
, metavar
|
||||
, optional
|
||||
, progDesc
|
||||
, short
|
||||
, str
|
||||
, strOption
|
||||
)
|
||||
import Control.Applicative ((<**>))
|
||||
|
||||
data CommandLine = CommandLine
|
||||
{ input :: FilePath
|
||||
, output :: Maybe FilePath
|
||||
} deriving (Eq, Show)
|
||||
|
||||
parser :: Parser CommandLine
|
||||
parser = CommandLine
|
||||
<$> argument str inFile
|
||||
<*> optional (strOption outFile)
|
||||
where
|
||||
inFile = metavar "INFILE" <> help "Input file."
|
||||
outFile = long "output"
|
||||
<> short 'o'
|
||||
<> metavar "OUTFILE"
|
||||
<> help "Output file."
|
||||
|
||||
commandLine :: ParserInfo CommandLine
|
||||
commandLine = info (parser <**> helper)
|
||||
$ fullDesc <> progDesc "Elna compiler."
|
37
lib/Language/Elna/Driver.hs
Normal file
37
lib/Language/Elna/Driver.hs
Normal file
@ -0,0 +1,37 @@
|
||||
{- This Source Code Form is subject to the terms of the Mozilla Public License,
|
||||
v. 2.0. If a copy of the MPL was not distributed with this file, You can
|
||||
obtain one at https://mozilla.org/MPL/2.0/. -}
|
||||
|
||||
module Language.Elna.Driver
|
||||
( Driver(..)
|
||||
, IntermediateStage(..)
|
||||
, drive
|
||||
, execParser
|
||||
) where
|
||||
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Language.Elna.Driver.CommandLine
|
||||
( CommandLine(..)
|
||||
, IntermediateStage(..)
|
||||
, commandLine
|
||||
)
|
||||
import Options.Applicative (execParser)
|
||||
import System.FilePath (replaceExtension, takeFileName)
|
||||
|
||||
data Driver = Driver
|
||||
{ input :: FilePath
|
||||
, output :: FilePath
|
||||
, intermediateStage :: Maybe IntermediateStage
|
||||
} deriving (Eq, Show)
|
||||
|
||||
drive :: IO Driver
|
||||
drive = rewrite <$> execParser commandLine
|
||||
where
|
||||
rewrite CommandLine{..} =
|
||||
let defaultOutputName = replaceExtension (takeFileName input) "o"
|
||||
outputName = fromMaybe defaultOutputName output
|
||||
in Driver
|
||||
{ input = input
|
||||
, output = outputName
|
||||
, intermediateStage = intermediateStage
|
||||
}
|
69
lib/Language/Elna/Driver/CommandLine.hs
Normal file
69
lib/Language/Elna/Driver/CommandLine.hs
Normal file
@ -0,0 +1,69 @@
|
||||
{- This Source Code Form is subject to the terms of the Mozilla Public License,
|
||||
v. 2.0. If a copy of the MPL was not distributed with this file, You can
|
||||
obtain one at https://mozilla.org/MPL/2.0/. -}
|
||||
|
||||
module Language.Elna.Driver.CommandLine
|
||||
( CommandLine(..)
|
||||
, IntermediateStage(..)
|
||||
, commandLine
|
||||
) where
|
||||
|
||||
import Options.Applicative
|
||||
( Parser
|
||||
, ParserInfo(..)
|
||||
, argument
|
||||
, flag'
|
||||
, fullDesc
|
||||
, help
|
||||
, helper
|
||||
, info
|
||||
, long
|
||||
, metavar
|
||||
, optional
|
||||
, progDesc
|
||||
, short
|
||||
, str
|
||||
, strOption
|
||||
)
|
||||
import Control.Applicative (Alternative(..), (<**>))
|
||||
|
||||
data IntermediateStage
|
||||
= ParseStage
|
||||
| ValidateStage
|
||||
| CodeGenStage
|
||||
deriving (Eq, Show)
|
||||
|
||||
data CommandLine = CommandLine
|
||||
{ input :: FilePath
|
||||
, output :: Maybe FilePath
|
||||
, intermediateStage :: Maybe IntermediateStage
|
||||
} deriving (Eq, Show)
|
||||
|
||||
intermediateStageP :: Parser IntermediateStage
|
||||
intermediateStageP
|
||||
= flag' ParseStage parseStageP
|
||||
<|> flag' ValidateStage validateStageP
|
||||
<|> flag' CodeGenStage codeGenStageP
|
||||
where
|
||||
parseStageP = long "parse"
|
||||
<> help "Run the lexer and parser, but stop before assembly generation"
|
||||
validateStageP = long "validate"
|
||||
<> help "Run through the semantic analysis stage, stopping before TAC generation"
|
||||
codeGenStageP = long "codegen"
|
||||
<> help "Perform lexing, parsing, and assembly generation, but stop before code emission"
|
||||
|
||||
commandLineP :: Parser CommandLine
|
||||
commandLineP = CommandLine
|
||||
<$> argument str inFile
|
||||
<*> optional (strOption outFile)
|
||||
<*> optional intermediateStageP
|
||||
where
|
||||
inFile = metavar "INFILE" <> help "Input file."
|
||||
outFile = long "output"
|
||||
<> short 'o'
|
||||
<> metavar "OUTFILE"
|
||||
<> help "Output file."
|
||||
|
||||
commandLine :: ParserInfo CommandLine
|
||||
commandLine = info (commandLineP <**> helper)
|
||||
$ fullDesc <> progDesc "Elna compiler."
|
42
src/Main.hs
42
src/Main.hs
@ -6,7 +6,11 @@ module Main
|
||||
( main
|
||||
) where
|
||||
|
||||
import Language.Elna.CommandLine (CommandLine(..), commandLine, execParser)
|
||||
import Language.Elna.Driver
|
||||
( Driver(..)
|
||||
, IntermediateStage(..)
|
||||
, drive
|
||||
)
|
||||
import Language.Elna.Object.ElfCoder (elfObject)
|
||||
import Language.Elna.Backend.Allocator (allocate)
|
||||
import Language.Elna.Glue (glue)
|
||||
@ -15,8 +19,6 @@ import Language.Elna.Frontend.Parser (programP)
|
||||
import Language.Elna.Frontend.TypeAnalysis (typeAnalysis)
|
||||
import Language.Elna.RiscV.CodeGenerator (generateRiscV, riscVConfiguration)
|
||||
import Language.Elna.RiscV.ElfWriter (riscv32Elf)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import System.FilePath (replaceExtension, takeFileName)
|
||||
import Text.Megaparsec (runParser, errorBundlePretty)
|
||||
import qualified Data.Text.IO as Text
|
||||
import System.Exit (ExitCode(..), exitWith)
|
||||
@ -32,27 +34,29 @@ import Control.Exception (IOException, catch)
|
||||
-- 6 - Register allocation error.
|
||||
|
||||
main :: IO ()
|
||||
main = execParser commandLine >>= withCommandLine
|
||||
main = drive >>= withCommandLine
|
||||
where
|
||||
withCommandLine CommandLine{..} =
|
||||
let defaultOutputName = replaceExtension (takeFileName input) "o"
|
||||
outputName = fromMaybe defaultOutputName output
|
||||
in catch (Text.readFile input) (printAndExit 2 :: IOException -> IO a)
|
||||
>>= withParsedInput outputName
|
||||
. runParser programP input
|
||||
withParsedInput output (Right program)
|
||||
= either (printAndExit 4) (withSymbolTable output program)
|
||||
$ nameAnalysis program
|
||||
withCommandLine driver@Driver{ input }
|
||||
= catch (Text.readFile input) (printAndExit 2 :: IOException -> IO a)
|
||||
>>= withParsedInput driver
|
||||
. runParser programP input
|
||||
withParsedInput driver@Driver{ intermediateStage } (Right program)
|
||||
| Just ParseStage <- intermediateStage = pure ()
|
||||
| otherwise
|
||||
= either (printAndExit 4) (withSymbolTable driver program)
|
||||
$ nameAnalysis program
|
||||
withParsedInput _ (Left errorBundle)
|
||||
= putStrLn (errorBundlePretty errorBundle)
|
||||
>> exitWith (ExitFailure 3)
|
||||
withSymbolTable output program symbolTable
|
||||
withSymbolTable driver@Driver{ intermediateStage } program symbolTable
|
||||
| Just typeError <- typeAnalysis symbolTable program =
|
||||
printAndExit 5 typeError
|
||||
| otherwise =
|
||||
let makeObject = elfObject output . riscv32Elf . generateRiscV
|
||||
in either (printAndExit 6) makeObject
|
||||
$ allocate riscVConfiguration symbolTable
|
||||
$ glue symbolTable program
|
||||
| Just ValidateStage <- intermediateStage = pure ()
|
||||
| otherwise = either (printAndExit 6) (withTac driver)
|
||||
$ allocate riscVConfiguration symbolTable
|
||||
$ glue symbolTable program
|
||||
withTac Driver{ intermediateStage, output } tac
|
||||
| Just CodeGenStage <- intermediateStage = pure ()
|
||||
| otherwise = elfObject output $ riscv32Elf $ generateRiscV tac
|
||||
printAndExit :: Show b => forall a. Int -> b -> IO a
|
||||
printAndExit failureCode e = print e >> exitWith (ExitFailure failureCode)
|
||||
|
Loading…
x
Reference in New Issue
Block a user