Implement the while loop
This commit is contained in:
		| @@ -1 +1 @@ | |||||||
| 3.3.5 | 3.3.6 | ||||||
|   | |||||||
| @@ -17,12 +17,21 @@ import Language.Elna.Location (Identifier(..)) | |||||||
| import Control.Monad.Trans.Reader (ReaderT, asks, runReaderT) | import Control.Monad.Trans.Reader (ReaderT, asks, runReaderT) | ||||||
| import Control.Monad.Trans.State (State, runState, modify') | import Control.Monad.Trans.State (State, runState, modify') | ||||||
| import GHC.Records (HasField(..)) | import GHC.Records (HasField(..)) | ||||||
| import Control.Monad.Trans.Class (MonadTrans(lift)) | import Control.Monad.Trans.Class (MonadTrans(..)) | ||||||
|  | import Control.Monad.Trans.Except (ExceptT(..), runExceptT, throwE) | ||||||
|  | import Data.List ((!?)) | ||||||
|  |  | ||||||
| data Store r | data Store r | ||||||
|     = RegisterStore r |     = RegisterStore r | ||||||
|     | StackStore Word32 r |     | StackStore Word32 r | ||||||
|  |  | ||||||
|  | data AllocationError = AllocationError | ||||||
|  |     deriving Eq | ||||||
|  |  | ||||||
|  | instance Show AllocationError | ||||||
|  |   where | ||||||
|  |     show = const "Ran out of registers during register allocation" | ||||||
|  |  | ||||||
| newtype MachineConfiguration r = MachineConfiguration | newtype MachineConfiguration r = MachineConfiguration | ||||||
|     { temporaryRegisters :: [r] |     { temporaryRegisters :: [r] | ||||||
|     } |     } | ||||||
| @@ -32,7 +41,7 @@ newtype MachineState = MachineState | |||||||
|     } deriving (Eq, Show) |     } deriving (Eq, Show) | ||||||
|  |  | ||||||
| newtype Allocator r a = Allocator | newtype Allocator r a = Allocator | ||||||
|     { runAllocator :: ReaderT (MachineConfiguration r) (State MachineState) a |     { runAllocator :: ExceptT AllocationError (ReaderT (MachineConfiguration r) (State MachineState)) a | ||||||
|     } |     } | ||||||
|  |  | ||||||
| instance forall r. Functor (Allocator r) | instance forall r. Functor (Allocator r) | ||||||
| @@ -52,19 +61,21 @@ allocate | |||||||
|     :: forall r |     :: forall r | ||||||
|     . MachineConfiguration r |     . MachineConfiguration r | ||||||
|     -> HashMap Identifier (Vector (Quadruple Variable)) |     -> HashMap Identifier (Vector (Quadruple Variable)) | ||||||
|     -> HashMap Identifier (ProcedureQuadruples (Store r)) |     -> Either AllocationError (HashMap Identifier (ProcedureQuadruples (Store r))) | ||||||
| allocate machineConfiguration = fmap function | allocate machineConfiguration = traverse function | ||||||
|   where |   where | ||||||
|     function :: Vector (Quadruple Variable) -> ProcedureQuadruples (Store r) |     run = flip runState (MachineState{ stackSize = 0 }) | ||||||
|  |         . flip runReaderT machineConfiguration | ||||||
|  |         . runExceptT | ||||||
|  |         . runAllocator | ||||||
|  |         . mapM quadruple | ||||||
|  |     function :: Vector (Quadruple Variable) -> Either AllocationError (ProcedureQuadruples (Store r)) | ||||||
|     function quadruples' = |     function quadruples' = | ||||||
|         let (result, lastState) |         let (result, lastState) = run quadruples' | ||||||
|                 = flip runState (MachineState{ stackSize = 0 }) |          in makeResult lastState <$> result | ||||||
|                 $ flip runReaderT machineConfiguration |     makeResult MachineState{ stackSize } result = ProcedureQuadruples | ||||||
|                 $ runAllocator |  | ||||||
|                 $ mapM quadruple quadruples' |  | ||||||
|          in ProcedureQuadruples |  | ||||||
|         { quadruples = result |         { quadruples = result | ||||||
|             , stackSize = getField @"stackSize" lastState |         , stackSize = stackSize | ||||||
|         } |         } | ||||||
|  |  | ||||||
| quadruple :: Quadruple Variable -> Allocator r (Quadruple (Store r)) | quadruple :: Quadruple Variable -> Allocator r (Quadruple (Store r)) | ||||||
| @@ -131,11 +142,12 @@ operand (VariableOperand variableOperand) = | |||||||
|  |  | ||||||
| storeVariable :: Variable -> Allocator r (Store r) | storeVariable :: Variable -> Allocator r (Store r) | ||||||
| storeVariable (TempVariable index) = do | storeVariable (TempVariable index) = do | ||||||
|     temporaryRegisters' <- Allocator $ asks $ getField @"temporaryRegisters" |     temporaryRegisters' <- Allocator $ lift $ asks $ getField @"temporaryRegisters" | ||||||
|     pure $ RegisterStore |     maybe (Allocator $ throwE AllocationError) (pure . RegisterStore) | ||||||
|         $ temporaryRegisters' !! fromIntegral index |         $ temporaryRegisters' !? fromIntegral index | ||||||
|  |          | ||||||
| storeVariable (LocalVariable index) = do | storeVariable (LocalVariable index) = do | ||||||
|     temporaryRegisters' <- Allocator $ asks $ getField @"temporaryRegisters" |     temporaryRegisters' <- Allocator $ lift $ asks $ getField @"temporaryRegisters" | ||||||
|     Allocator $ lift $ modify' $ MachineState . (+ 4) . getField @"stackSize" |     Allocator $ lift $ lift $ modify' $ MachineState . (+ 4) . getField @"stackSize" | ||||||
|     pure $ StackStore (index * 4) |     maybe (Allocator $ throwE AllocationError) (pure . StackStore (index * 4)) | ||||||
|         $ temporaryRegisters' !! pred (length temporaryRegisters' - fromIntegral index) |         $ temporaryRegisters' !? pred (length temporaryRegisters' - fromIntegral index) | ||||||
|   | |||||||
| @@ -71,7 +71,7 @@ data Statement | |||||||
|     = EmptyStatement |     = EmptyStatement | ||||||
|     | IfStatement Condition Statement (Maybe Statement) |     | IfStatement Condition Statement (Maybe Statement) | ||||||
|     | AssignmentStatement VariableAccess Expression |     | AssignmentStatement VariableAccess Expression | ||||||
|     -- | WhileStatement Condition Statement |     | WhileStatement Condition Statement | ||||||
|     | CompoundStatement [Statement] |     | CompoundStatement [Statement] | ||||||
|     | CallStatement Identifier [Expression] |     | CallStatement Identifier [Expression] | ||||||
|     deriving Eq |     deriving Eq | ||||||
| @@ -86,8 +86,8 @@ instance Show Statement | |||||||
|         ] |         ] | ||||||
|     show (AssignmentStatement lhs rhs) = |     show (AssignmentStatement lhs rhs) = | ||||||
|         concat [show lhs, " := ", show rhs, ";"] |         concat [show lhs, " := ", show rhs, ";"] | ||||||
|     {-show (WhileStatement expression statement) = |     show (WhileStatement expression statement) = | ||||||
|         concat ["while (", show expression, ") ", show statement, ";"]-} |         concat ["while (", show expression, ") ", show statement, ";"] | ||||||
|     show (CompoundStatement statements) = |     show (CompoundStatement statements) = | ||||||
|         concat ["{\n", unlines (show <$> statements), " }"] |         concat ["{\n", unlines (show <$> statements), " }"] | ||||||
|     show (CallStatement name parameters) = show name <> "(" |     show (CallStatement name parameters) = show name <> "(" | ||||||
|   | |||||||
| @@ -175,9 +175,9 @@ statement globalTable (AST.IfStatement ifCondition ifStatement elseStatement) | |||||||
| statement globalTable (AST.AssignmentStatement lvalue rvalue) | statement globalTable (AST.AssignmentStatement lvalue rvalue) | ||||||
|     = variableAccess globalTable lvalue |     = variableAccess globalTable lvalue | ||||||
|     >> expression globalTable rvalue |     >> expression globalTable rvalue | ||||||
| --statement globalTable (AST.WhileStatement whileCondition loop) | statement globalTable (AST.WhileStatement whileCondition loop) | ||||||
| --    = condition globalTable whileCondition |     = condition globalTable whileCondition | ||||||
| --    >> statement globalTable loop |     >> statement globalTable loop | ||||||
|  |  | ||||||
| condition :: SymbolTable -> AST.Condition -> NameAnalysis () | condition :: SymbolTable -> AST.Condition -> NameAnalysis () | ||||||
| condition globalTable (AST.EqualCondition lhs rhs) | condition globalTable (AST.EqualCondition lhs rhs) | ||||||
|   | |||||||
| @@ -188,7 +188,7 @@ statementP | |||||||
|     <|> ifElseP |     <|> ifElseP | ||||||
|     <|> CompoundStatement <$> blockP (many statementP) |     <|> CompoundStatement <$> blockP (many statementP) | ||||||
|     <|> try assignmentP |     <|> try assignmentP | ||||||
|     -- <|> try whileP |     <|> try whileP | ||||||
|     <|> callP |     <|> callP | ||||||
|     <?> "statement" |     <?> "statement" | ||||||
|   where |   where | ||||||
| @@ -200,9 +200,9 @@ statementP | |||||||
|         <$> (symbol "if" *> parensP conditionP) |         <$> (symbol "if" *> parensP conditionP) | ||||||
|         <*> statementP |         <*> statementP | ||||||
|         <*> optional (symbol "else" *> statementP) |         <*> optional (symbol "else" *> statementP) | ||||||
|     {-whileP = WhileStatement |     whileP = WhileStatement | ||||||
|         <$> (symbol "while" *> parensP conditionP) |         <$> (symbol "while" *> parensP conditionP) | ||||||
|         <*> statementP -} |         <*> statementP | ||||||
|     assignmentP = AssignmentStatement |     assignmentP = AssignmentStatement | ||||||
|         <$> variableAccessP |         <$> variableAccessP | ||||||
|         <* symbol ":=" |         <* symbol ":=" | ||||||
|   | |||||||
| @@ -101,11 +101,11 @@ statement globalTable = \case | |||||||
|             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError lhsType |             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError lhsType | ||||||
|         unless (rhsType == intType) |         unless (rhsType == intType) | ||||||
|             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError rhsType |             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError rhsType | ||||||
|     {- AST.WhileStatement whileCondition whileStatement -> do |     AST.WhileStatement whileCondition whileStatement -> do | ||||||
|         conditionType <- condition globalTable whileCondition |         conditionType <- condition globalTable whileCondition | ||||||
|         unless (conditionType == booleanType) |         unless (conditionType == booleanType) | ||||||
|             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError conditionType |             $ TypeAnalysis $ lift $ throwE $ InvalidConditionTypeError conditionType | ||||||
|         statement globalTable whileStatement -} |         statement globalTable whileStatement | ||||||
|     AST.IfStatement ifCondition ifStatement elseStatement -> do |     AST.IfStatement ifCondition ifStatement elseStatement -> do | ||||||
|         conditionType <- condition globalTable ifCondition |         conditionType <- condition globalTable ifCondition | ||||||
|         unless (conditionType == booleanType) |         unless (conditionType == booleanType) | ||||||
|   | |||||||
| @@ -131,7 +131,7 @@ statement localTable (AST.AssignmentStatement variableAccess' assignee) = do | |||||||
|                 . AssignQuadruple rhsOperand |                 . AssignQuadruple rhsOperand | ||||||
|                 <$> lookupLocal identifier |                 <$> lookupLocal identifier | ||||||
|     pure $ rhsStatements <> lhsStatements |     pure $ rhsStatements <> lhsStatements | ||||||
| {- statement localTable (AST.WhileStatement whileCondition whileStatement) = do | statement localTable (AST.WhileStatement whileCondition whileStatement) = do | ||||||
|     (conditionStatements, jumpConstructor) <- condition localTable whileCondition |     (conditionStatements, jumpConstructor) <- condition localTable whileCondition | ||||||
|     startLabel <- createLabel |     startLabel <- createLabel | ||||||
|     endLabel <- createLabel |     endLabel <- createLabel | ||||||
| @@ -141,7 +141,7 @@ statement localTable (AST.AssignmentStatement variableAccess' assignee) = do | |||||||
|         <> conditionStatements |         <> conditionStatements | ||||||
|         <> Vector.fromList [jumpConstructor startLabel, GoToQuadruple endLabel, LabelQuadruple startLabel] |         <> Vector.fromList [jumpConstructor startLabel, GoToQuadruple endLabel, LabelQuadruple startLabel] | ||||||
|         <> whileStatements |         <> whileStatements | ||||||
|         <> Vector.fromList [GoToQuadruple conditionLabel, LabelQuadruple endLabel] -} |         <> Vector.fromList [GoToQuadruple conditionLabel, LabelQuadruple endLabel] | ||||||
|  |  | ||||||
| createTemporary :: Glue Variable | createTemporary :: Glue Variable | ||||||
| createTemporary = do | createTemporary = do | ||||||
|   | |||||||
| @@ -25,6 +25,7 @@ import Control.Exception (IOException, catch) | |||||||
| -- 3 - Parse error. | -- 3 - Parse error. | ||||||
| -- 4 - Name analysis error. | -- 4 - Name analysis error. | ||||||
| -- 5 - Type error. | -- 5 - Type error. | ||||||
|  | -- 6 - Register allocation error. | ||||||
|  |  | ||||||
| main :: IO () | main :: IO () | ||||||
| main = execParser commandLine >>= withCommandLine | main = execParser commandLine >>= withCommandLine | ||||||
| @@ -45,9 +46,9 @@ main = execParser commandLine >>= withCommandLine | |||||||
|         | Just typeError <- typeAnalysis symbolTable program = |         | Just typeError <- typeAnalysis symbolTable program = | ||||||
|             printAndExit 5 typeError |             printAndExit 5 typeError | ||||||
|         | otherwise = |         | otherwise = | ||||||
|             let instructions = generateRiscV |             let makeObject = elfObject output . riscv32Elf . generateRiscV | ||||||
|  |              in either (printAndExit 6) makeObject | ||||||
|                 $ allocate riscVConfiguration |                 $ allocate riscVConfiguration | ||||||
|                 $ glue symbolTable program |                 $ glue symbolTable program | ||||||
|              in elfObject output $ riscv32Elf instructions |  | ||||||
|     printAndExit :: Show b => forall a. Int -> b -> IO a |     printAndExit :: Show b => forall a. Int -> b -> IO a | ||||||
|     printAndExit failureCode e = print e >> exitWith (ExitFailure failureCode) |     printAndExit failureCode e = print e >> exitWith (ExitFailure failureCode) | ||||||
|   | |||||||
							
								
								
									
										1
									
								
								tests/expectations/print_after_loop.txt
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										1
									
								
								tests/expectations/print_after_loop.txt
									
									
									
									
									
										Normal file
									
								
							| @@ -0,0 +1 @@ | |||||||
|  | 2 | ||||||
							
								
								
									
										9
									
								
								tests/vm/print_after_loop.elna
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										9
									
								
								tests/vm/print_after_loop.elna
									
									
									
									
									
										Normal file
									
								
							| @@ -0,0 +1,9 @@ | |||||||
|  | proc main() { | ||||||
|  |   var x: int; | ||||||
|  |  | ||||||
|  |   x := 0; | ||||||
|  |   while (x < 2) { | ||||||
|  |     x := x + 1; | ||||||
|  |   } | ||||||
|  |   printi(x); | ||||||
|  | } | ||||||
		Reference in New Issue
	
	Block a user