Create numerated temporary variables
This commit is contained in:
parent
0c45a9886a
commit
ad0bf43ba5
@ -32,6 +32,7 @@ library elna-internal
|
|||||||
import: warnings
|
import: warnings
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
Language.Elna.AST
|
Language.Elna.AST
|
||||||
|
Language.Elna.CodeGenerator
|
||||||
Language.Elna.Intermediate
|
Language.Elna.Intermediate
|
||||||
Language.Elna.Location
|
Language.Elna.Location
|
||||||
Language.Elna.NameAnalysis
|
Language.Elna.NameAnalysis
|
||||||
|
3
lib/Language/Elna/CodeGenerator.hs
Normal file
3
lib/Language/Elna/CodeGenerator.hs
Normal file
@ -0,0 +1,3 @@
|
|||||||
|
module Language.Elna.CodeGenerator
|
||||||
|
(
|
||||||
|
) where
|
@ -21,6 +21,7 @@ import Language.Elna.SymbolTable (SymbolTable, Info(..))
|
|||||||
import qualified Language.Elna.SymbolTable as SymbolTable
|
import qualified Language.Elna.SymbolTable as SymbolTable
|
||||||
import Data.Foldable (Foldable(..), foldrM)
|
import Data.Foldable (Foldable(..), foldrM)
|
||||||
import GHC.Records (HasField(..))
|
import GHC.Records (HasField(..))
|
||||||
|
import qualified Data.Text as Text
|
||||||
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
||||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||||
import qualified Data.Text.Lazy as Text.Lazy
|
import qualified Data.Text.Lazy as Text.Lazy
|
||||||
@ -31,25 +32,37 @@ data Operand
|
|||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
newtype Label = Label Text
|
newtype Label = Label Text
|
||||||
deriving (Eq, Show)
|
deriving Eq
|
||||||
|
|
||||||
data Variable = Variable Text | TempVariable
|
instance Show Label
|
||||||
deriving (Eq, Show)
|
where
|
||||||
|
show (Label label) = '.' : Text.unpack label
|
||||||
|
|
||||||
newtype Generator = Generator
|
data Variable = Variable Text | TempVariable Int32
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
instance Show Variable
|
||||||
|
where
|
||||||
|
show (Variable variable) = '$' : Text.unpack variable
|
||||||
|
show (TempVariable variable) = '$' : show variable
|
||||||
|
|
||||||
|
data Generator = Generator
|
||||||
{ labelCounter :: Int32
|
{ labelCounter :: Int32
|
||||||
|
, temporaryCounter :: Int32
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
instance Semigroup Generator
|
instance Semigroup Generator
|
||||||
where
|
where
|
||||||
lhs <> rhs = Generator
|
lhs <> rhs = Generator
|
||||||
{ labelCounter = getField @"labelCounter" lhs + getField @"labelCounter" rhs
|
{ labelCounter = getField @"labelCounter" lhs + getField @"labelCounter" rhs
|
||||||
|
, temporaryCounter = getField @"temporaryCounter" lhs + getField @"temporaryCounter" rhs
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Monoid Generator
|
instance Monoid Generator
|
||||||
where
|
where
|
||||||
mempty = Generator
|
mempty = Generator
|
||||||
{ labelCounter = 0
|
{ labelCounter = 0
|
||||||
|
, temporaryCounter = 0
|
||||||
}
|
}
|
||||||
|
|
||||||
newtype Intermediate a = Intermediate
|
newtype Intermediate a = Intermediate
|
||||||
@ -106,6 +119,16 @@ createLabel = do
|
|||||||
{ labelCounter = getField @"labelCounter" generator + 1
|
{ labelCounter = getField @"labelCounter" generator + 1
|
||||||
}
|
}
|
||||||
|
|
||||||
|
createTemporary :: Intermediate Variable
|
||||||
|
createTemporary = do
|
||||||
|
currentCounter <- Intermediate $ gets temporaryCounter
|
||||||
|
Intermediate $ modify' modifier
|
||||||
|
pure $ TempVariable currentCounter
|
||||||
|
where
|
||||||
|
modifier generator = generator
|
||||||
|
{ temporaryCounter = getField @"temporaryCounter" generator + 1
|
||||||
|
}
|
||||||
|
|
||||||
intermediate :: SymbolTable -> AST.Program -> HashMap AST.Identifier (Vector Quadruple)
|
intermediate :: SymbolTable -> AST.Program -> HashMap AST.Identifier (Vector Quadruple)
|
||||||
intermediate globalTable
|
intermediate globalTable
|
||||||
= fst
|
= fst
|
||||||
@ -237,8 +260,8 @@ variableAccess localTable (AST.ArrayAccess access1 index1) Nothing (ArrayType _
|
|||||||
variableAccess localTable access1 (Just indexPlace) baseType statements
|
variableAccess localTable access1 (Just indexPlace) baseType statements
|
||||||
variableAccess localTable (AST.ArrayAccess arrayAccess' arrayIndex) (Just baseIndex) (ArrayType arraySize baseType) statements = do
|
variableAccess localTable (AST.ArrayAccess arrayAccess' arrayIndex) (Just baseIndex) (ArrayType arraySize baseType) statements = do
|
||||||
(indexPlace, statements') <- expression localTable arrayIndex
|
(indexPlace, statements') <- expression localTable arrayIndex
|
||||||
let resultVariable = TempVariable
|
resultVariable <- createTemporary
|
||||||
resultOperand = VariableOperand resultVariable
|
let resultOperand = VariableOperand resultVariable
|
||||||
indexCalculation = Vector.fromList
|
indexCalculation = Vector.fromList
|
||||||
[ ProductQuadruple (IntOperand $ fromIntegral arraySize) baseIndex resultVariable
|
[ ProductQuadruple (IntOperand $ fromIntegral arraySize) baseIndex resultVariable
|
||||||
, AddQuadruple indexPlace resultOperand resultVariable
|
, AddQuadruple indexPlace resultOperand resultVariable
|
||||||
@ -262,19 +285,19 @@ expression localTable = \case
|
|||||||
case variableAccess' of
|
case variableAccess' of
|
||||||
(AST.Identifier identifier, Nothing, statements) ->
|
(AST.Identifier identifier, Nothing, statements) ->
|
||||||
pure (VariableOperand (Variable identifier), statements)
|
pure (VariableOperand (Variable identifier), statements)
|
||||||
(AST.Identifier identifier, Just operand, statements) ->
|
(AST.Identifier identifier, Just operand, statements) -> do
|
||||||
let arrayAddress = TempVariable
|
arrayAddress <- createTemporary
|
||||||
arrayStatement = ArrayQuadruple (Variable identifier) operand arrayAddress
|
let arrayStatement = ArrayQuadruple (Variable identifier) operand arrayAddress
|
||||||
in pure
|
pure
|
||||||
( VariableOperand arrayAddress
|
( VariableOperand arrayAddress
|
||||||
, Vector.snoc statements arrayStatement
|
, Vector.snoc statements arrayStatement
|
||||||
)
|
)
|
||||||
(AST.LiteralExpression literal') -> pure (literal literal', mempty)
|
(AST.LiteralExpression literal') -> pure (literal literal', mempty)
|
||||||
(AST.NegationExpression negation) -> do
|
(AST.NegationExpression negation) -> do
|
||||||
(operand, statements) <- expression localTable negation
|
(operand, statements) <- expression localTable negation
|
||||||
let tempVariable = TempVariable
|
tempVariable <- createTemporary
|
||||||
negationQuadruple = NegationQuadruple operand tempVariable
|
let negationQuadruple = NegationQuadruple operand tempVariable
|
||||||
in pure
|
pure
|
||||||
( VariableOperand tempVariable
|
( VariableOperand tempVariable
|
||||||
, Vector.snoc statements negationQuadruple
|
, Vector.snoc statements negationQuadruple
|
||||||
)
|
)
|
||||||
@ -289,9 +312,9 @@ expression localTable = \case
|
|||||||
binaryExpression f lhs rhs = do
|
binaryExpression f lhs rhs = do
|
||||||
(lhsOperand, lhsStatements) <- expression localTable lhs
|
(lhsOperand, lhsStatements) <- expression localTable lhs
|
||||||
(rhsOperand, rhsStatements) <- expression localTable rhs
|
(rhsOperand, rhsStatements) <- expression localTable rhs
|
||||||
let tempVariable = TempVariable
|
tempVariable <- createTemporary
|
||||||
newQuadruple = f lhsOperand rhsOperand tempVariable
|
let newQuadruple = f lhsOperand rhsOperand tempVariable
|
||||||
in pure
|
pure
|
||||||
( VariableOperand tempVariable
|
( VariableOperand tempVariable
|
||||||
, Vector.snoc (lhsStatements <> rhsStatements) newQuadruple
|
, Vector.snoc (lhsStatements <> rhsStatements) newQuadruple
|
||||||
)
|
)
|
||||||
|
Loading…
Reference in New Issue
Block a user