Implement if statements with equality
This commit is contained in:
@@ -9,15 +9,24 @@ import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Maybe (catMaybes)
|
||||
import Data.Vector (Vector)
|
||||
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||
import qualified Data.Text.Lazy as Text.Lazy
|
||||
import qualified Data.Vector as Vector
|
||||
import Data.Word (Word32)
|
||||
import qualified Language.Elna.Frontend.AST as AST
|
||||
import Language.Elna.Backend.Intermediate (Operand(..), Quadruple(..), Variable(..))
|
||||
import Language.Elna.Backend.Intermediate
|
||||
( Label(..)
|
||||
, Operand(..)
|
||||
, Quadruple(..)
|
||||
, Variable(..)
|
||||
)
|
||||
import Language.Elna.Frontend.SymbolTable (SymbolTable)
|
||||
import GHC.Records (HasField(..))
|
||||
|
||||
newtype Paste = Paste
|
||||
data Paste = Paste
|
||||
{ temporaryCounter :: Word32
|
||||
, labelCounter :: Word32
|
||||
}
|
||||
|
||||
newtype Glue a = Glue
|
||||
@@ -39,7 +48,7 @@ instance Monad Glue
|
||||
glue :: SymbolTable -> AST.Program -> HashMap AST.Identifier (Vector (Quadruple Variable))
|
||||
glue globalTable
|
||||
= fst
|
||||
. flip runState Paste{ temporaryCounter = 0 }
|
||||
. flip runState Paste{ temporaryCounter = 0, labelCounter = 0 }
|
||||
. runGlue
|
||||
. program globalTable
|
||||
|
||||
@@ -77,6 +86,18 @@ statement localTable (AST.CallStatement (AST.Identifier callName) arguments) = d
|
||||
$ Vector.length argumentStatements
|
||||
statement localTable (AST.CompoundStatement statements) =
|
||||
fold <$> traverse (statement localTable) statements
|
||||
statement localTable (AST.IfStatement ifCondition ifStatement elseStatement) = do
|
||||
(conditionStatements, jumpConstructor) <- condition localTable ifCondition
|
||||
ifLabel <- createLabel
|
||||
endLabel <- createLabel
|
||||
ifStatements <- statement localTable ifStatement
|
||||
possibleElseStatements <- traverse (statement localTable) elseStatement
|
||||
pure $ conditionStatements <> case possibleElseStatements of
|
||||
Just elseStatements -> Vector.cons (jumpConstructor ifLabel) elseStatements
|
||||
<> Vector.fromList [GoToQuadruple endLabel, LabelQuadruple ifLabel]
|
||||
<> Vector.snoc ifStatements (LabelQuadruple endLabel)
|
||||
Nothing -> Vector.fromList [jumpConstructor ifLabel, GoToQuadruple endLabel, LabelQuadruple ifLabel]
|
||||
<> Vector.snoc ifStatements (LabelQuadruple endLabel)
|
||||
{- statement localTable (AST.AssignmentStatement variableAccess' assignee) = do
|
||||
(rhsOperand, rhsStatements) <- expression localTable assignee
|
||||
let variableType' = variableType variableAccess' localTable
|
||||
@@ -90,18 +111,6 @@ statement localTable (AST.CompoundStatement statements) =
|
||||
Vector.snoc accumulatedStatements
|
||||
$ AssignQuadruple rhsOperand
|
||||
$ Variable identifier
|
||||
statement localTable (AST.IfStatement ifCondition ifStatement elseStatement) = do
|
||||
(conditionStatements, jumpConstructor) <- condition localTable ifCondition
|
||||
ifLabel <- createLabel
|
||||
endLabel <- createLabel
|
||||
ifStatements <- statement localTable ifStatement
|
||||
possibleElseStatements <- traverse (statement localTable) elseStatement
|
||||
pure $ conditionStatements <> case possibleElseStatements of
|
||||
Just elseStatements -> Vector.cons (jumpConstructor ifLabel) elseStatements
|
||||
<> Vector.fromList [GoToQuadruple endLabel, LabelQuadruple ifLabel]
|
||||
<> Vector.snoc ifStatements (LabelQuadruple endLabel)
|
||||
Nothing -> Vector.fromList [jumpConstructor ifLabel, GoToQuadruple endLabel, LabelQuadruple ifLabel]
|
||||
<> Vector.snoc ifStatements (LabelQuadruple endLabel)
|
||||
statement localTable (AST.WhileStatement whileCondition whileStatement) = do
|
||||
(conditionStatements, jumpConstructor) <- condition localTable whileCondition
|
||||
startLabel <- createLabel
|
||||
@@ -124,21 +133,23 @@ createTemporary = do
|
||||
{ temporaryCounter = getField @"temporaryCounter" generator + 1
|
||||
}
|
||||
|
||||
{-
|
||||
import Language.Elna.Types (Type(..))
|
||||
import qualified Language.Elna.SymbolTable as SymbolTable
|
||||
|
||||
newtype Label = Label Text
|
||||
deriving Eq
|
||||
|
||||
instance Show Label
|
||||
createLabel :: Glue Label
|
||||
createLabel = do
|
||||
currentCounter <- Glue $ gets $ getField @"labelCounter"
|
||||
Glue $ modify' modifier
|
||||
pure $ Label
|
||||
$ Text.Lazy.toStrict
|
||||
$ Text.Builder.toLazyText
|
||||
$ "L" <> Text.Builder.decimal currentCounter
|
||||
where
|
||||
show (Label label) = '.' : Text.unpack label
|
||||
modifier generator = generator
|
||||
{ labelCounter = getField @"labelCounter" generator + 1
|
||||
}
|
||||
|
||||
condition
|
||||
:: SymbolTable
|
||||
-> AST.Condition
|
||||
-> Glue (Vector Quadruple, Label -> Quadruple)
|
||||
-> Glue (Vector (Quadruple Variable), Label -> Quadruple Variable)
|
||||
condition localTable (AST.EqualCondition lhs rhs) = do
|
||||
(lhsOperand, lhsStatements) <- expression localTable lhs
|
||||
(rhsOperand, rhsStatements) <- expression localTable rhs
|
||||
@@ -146,7 +157,7 @@ condition localTable (AST.EqualCondition lhs rhs) = do
|
||||
( lhsStatements <> rhsStatements
|
||||
, EqualQuadruple lhsOperand rhsOperand
|
||||
)
|
||||
condition localTable (AST.NonEqualCondition lhs rhs) = do
|
||||
{- condition localTable (AST.NonEqualCondition lhs rhs) = do
|
||||
(lhsOperand, lhsStatements) <- expression localTable lhs
|
||||
(rhsOperand, rhsStatements) <- expression localTable rhs
|
||||
pure
|
||||
@@ -178,6 +189,9 @@ condition localTable (AST.GreaterOrEqualCondition lhs rhs) = do
|
||||
( lhsStatements <> rhsStatements
|
||||
, GreaterOrEqualQuadruple lhsOperand rhsOperand
|
||||
)
|
||||
-}{-
|
||||
import Language.Elna.Types (Type(..))
|
||||
import qualified Language.Elna.SymbolTable as SymbolTable
|
||||
|
||||
variableAccess
|
||||
:: SymbolTable
|
||||
|
||||
Reference in New Issue
Block a user