Add types for name analysis
This commit is contained in:
parent
bf774475cc
commit
ce7652c618
@ -28,9 +28,15 @@ library elna-internal
|
|||||||
import: warnings
|
import: warnings
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
Language.Elna.AST
|
Language.Elna.AST
|
||||||
|
Language.Elna.Location
|
||||||
|
Language.Elna.NameAnalysis
|
||||||
Language.Elna.Parser
|
Language.Elna.Parser
|
||||||
|
Language.Elna.SymbolTable
|
||||||
build-depends:
|
build-depends:
|
||||||
parser-combinators ^>= 1.3
|
hashable ^>= 1.4.3,
|
||||||
|
parser-combinators ^>= 1.3,
|
||||||
|
vector ^>= 0.13.1,
|
||||||
|
unordered-containers ^>= 0.2.20
|
||||||
hs-source-dirs: lib
|
hs-source-dirs: lib
|
||||||
|
|
||||||
executable elna
|
executable elna
|
||||||
|
@ -12,34 +12,20 @@ module Language.Elna.AST
|
|||||||
|
|
||||||
import Data.Int (Int32)
|
import Data.Int (Int32)
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import Data.Word (Word16)
|
import Data.Word (Word16, Word32)
|
||||||
import Data.Text (Text)
|
|
||||||
import qualified Data.Text as Text
|
|
||||||
import Data.Char (chr)
|
import Data.Char (chr)
|
||||||
import Data.String (IsString(..))
|
import Language.Elna.Location (Identifier(..), showArrayType)
|
||||||
import Numeric (showHex)
|
import Numeric (showHex)
|
||||||
|
|
||||||
newtype Identifier = Identifier { unIdentifier :: Text }
|
|
||||||
deriving Eq
|
|
||||||
|
|
||||||
instance Show Identifier
|
|
||||||
where
|
|
||||||
show (Identifier identifier) = Text.unpack identifier
|
|
||||||
|
|
||||||
instance IsString Identifier
|
|
||||||
where
|
|
||||||
fromString = Identifier . Text.pack
|
|
||||||
|
|
||||||
data TypeExpression
|
data TypeExpression
|
||||||
= NamedType Identifier
|
= NamedType Identifier
|
||||||
| ArrayType TypeExpression Int32
|
| ArrayType Word32 TypeExpression
|
||||||
deriving Eq
|
deriving Eq
|
||||||
|
|
||||||
instance Show TypeExpression
|
instance Show TypeExpression
|
||||||
where
|
where
|
||||||
show (NamedType typeName) = show typeName
|
show (NamedType typeName) = show typeName
|
||||||
show (ArrayType typeName elementCount) = concat
|
show (ArrayType elementCount typeName) = showArrayType elementCount typeName
|
||||||
[show typeName, "[", show elementCount, "]"]
|
|
||||||
|
|
||||||
data Literal
|
data Literal
|
||||||
= IntegerLiteral Int32
|
= IntegerLiteral Int32
|
||||||
|
58
lib/Language/Elna/Location.hs
Normal file
58
lib/Language/Elna/Location.hs
Normal file
@ -0,0 +1,58 @@
|
|||||||
|
module Language.Elna.Location
|
||||||
|
( Identifier(..)
|
||||||
|
, Location(..)
|
||||||
|
, Node(..)
|
||||||
|
, showArrayType
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Hashable (Hashable(..))
|
||||||
|
import Data.String (IsString(..))
|
||||||
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as Text
|
||||||
|
import Data.Word (Word32)
|
||||||
|
|
||||||
|
data Location = Location
|
||||||
|
{ line :: Word32
|
||||||
|
, column :: Word32
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
|
instance Semigroup Location
|
||||||
|
where
|
||||||
|
(Location thisLine thisColumn) <> (Location thatLine thatColumn) = Location
|
||||||
|
{ line = thisLine + thatLine
|
||||||
|
, column = thisColumn + thatColumn
|
||||||
|
}
|
||||||
|
|
||||||
|
instance Monoid Location
|
||||||
|
where
|
||||||
|
mempty = Location{ line = 1, column = 1 }
|
||||||
|
|
||||||
|
data Node a = Node a Location
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
instance Functor Node
|
||||||
|
where
|
||||||
|
fmap f (Node node location) = Node (f node) location
|
||||||
|
|
||||||
|
newtype Identifier = Identifier { unIdentifier :: Text }
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
instance Show Identifier
|
||||||
|
where
|
||||||
|
show (Identifier identifier) = Text.unpack identifier
|
||||||
|
|
||||||
|
instance IsString Identifier
|
||||||
|
where
|
||||||
|
fromString = Identifier . Text.pack
|
||||||
|
|
||||||
|
instance Ord Identifier
|
||||||
|
where
|
||||||
|
compare (Identifier lhs) (Identifier rhs) = compare lhs rhs
|
||||||
|
|
||||||
|
instance Hashable Identifier
|
||||||
|
where
|
||||||
|
hashWithSalt salt (Identifier identifier) = hashWithSalt salt identifier
|
||||||
|
|
||||||
|
showArrayType :: Show a => Word32 -> a -> String
|
||||||
|
showArrayType elementCount typeName = concat
|
||||||
|
["array[", show elementCount, "] of ", show typeName]
|
3
lib/Language/Elna/NameAnalysis.hs
Normal file
3
lib/Language/Elna/NameAnalysis.hs
Normal file
@ -0,0 +1,3 @@
|
|||||||
|
module Language.Elna.NameAnalysis
|
||||||
|
(
|
||||||
|
) where
|
@ -80,7 +80,7 @@ typeExpressionP = arrayTypeExpression
|
|||||||
<|> NamedType <$> identifierP
|
<|> NamedType <$> identifierP
|
||||||
<?> "type expression"
|
<?> "type expression"
|
||||||
where
|
where
|
||||||
arrayTypeExpression = flip ArrayType
|
arrayTypeExpression = ArrayType
|
||||||
<$> (symbol "array" *> bracketsP (lexeme Lexer.decimal))
|
<$> (symbol "array" *> bracketsP (lexeme Lexer.decimal))
|
||||||
<*> (symbol "of" *> typeExpressionP)
|
<*> (symbol "of" *> typeExpressionP)
|
||||||
|
|
||||||
|
45
lib/Language/Elna/SymbolTable.hs
Normal file
45
lib/Language/Elna/SymbolTable.hs
Normal file
@ -0,0 +1,45 @@
|
|||||||
|
module Language.Elna.SymbolTable
|
||||||
|
( Info(..)
|
||||||
|
, ParameterInfo(..)
|
||||||
|
, SymbolTable(..)
|
||||||
|
, Type(..)
|
||||||
|
, booleanType
|
||||||
|
, intType
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.HashMap.Strict (HashMap)
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Data.Vector (Vector)
|
||||||
|
import Data.Word (Word32)
|
||||||
|
import Language.Elna.Location (Identifier(..), showArrayType)
|
||||||
|
|
||||||
|
data Type
|
||||||
|
= PrimitiveType Text
|
||||||
|
| ArrayType Word32 Type
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
|
instance Show Type
|
||||||
|
where
|
||||||
|
show (PrimitiveType typeName) = show typeName
|
||||||
|
show (ArrayType elementCount typeName) = showArrayType elementCount typeName
|
||||||
|
|
||||||
|
intType :: Type
|
||||||
|
intType = PrimitiveType "int"
|
||||||
|
|
||||||
|
booleanType :: Type
|
||||||
|
booleanType = PrimitiveType "boolean"
|
||||||
|
|
||||||
|
newtype SymbolTable = SymbolTable (HashMap Identifier Info)
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
data ParameterInfo = ParameterInfo
|
||||||
|
{ name :: Identifier
|
||||||
|
, type' :: Type
|
||||||
|
, isReferenceParameter :: Bool
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
|
data Info
|
||||||
|
= TypeInfo Type
|
||||||
|
| VariableInfo Type Bool
|
||||||
|
| ProcedureInfo SymbolTable (Vector ParameterInfo)
|
||||||
|
deriving (Eq, Show)
|
@ -29,21 +29,21 @@ spec =
|
|||||||
in actual `shouldParse` expected
|
in actual `shouldParse` expected
|
||||||
|
|
||||||
it "parses array type definition" $
|
it "parses array type definition" $
|
||||||
let expected = Program [TypeDefinition "t" $ ArrayType (NamedType "integer") 10]
|
let expected = Program [TypeDefinition "t" $ ArrayType 10 (NamedType "int")]
|
||||||
actual = parse programP "" "type t = array[10] of integer"
|
actual = parse programP "" "type t = array[10] of int"
|
||||||
in actual `shouldParse` expected
|
in actual `shouldParse` expected
|
||||||
|
|
||||||
it "parses parameters" $
|
it "parses parameters" $
|
||||||
let given = "proc main(x: integer) {}"
|
let given = "proc main(x: int) {}"
|
||||||
parameters = [Parameter "x" (NamedType "integer") False]
|
parameters = [Parameter "x" (NamedType "int") False]
|
||||||
expected = Program [ProcedureDefinition "main" parameters [] []]
|
expected = Program [ProcedureDefinition "main" parameters [] []]
|
||||||
actual = parse programP "" given
|
actual = parse programP "" given
|
||||||
in actual `shouldParse` expected
|
in actual `shouldParse` expected
|
||||||
|
|
||||||
it "parses ref parameters" $
|
it "parses ref parameters" $
|
||||||
let given = "proc main(x: integer, ref y: boolean) {}"
|
let given = "proc main(x: int, ref y: boolean) {}"
|
||||||
parameters =
|
parameters =
|
||||||
[ Parameter "x" (NamedType "integer") False
|
[ Parameter "x" (NamedType "int") False
|
||||||
, Parameter "y" (NamedType "boolean") True
|
, Parameter "y" (NamedType "boolean") True
|
||||||
]
|
]
|
||||||
expected = Program [ProcedureDefinition "main" parameters [] []]
|
expected = Program [ProcedureDefinition "main" parameters [] []]
|
||||||
@ -51,7 +51,7 @@ spec =
|
|||||||
in actual `shouldParse` expected
|
in actual `shouldParse` expected
|
||||||
|
|
||||||
it "parses variable declaration" $
|
it "parses variable declaration" $
|
||||||
let given = "proc main() { var x: integer; }"
|
let given = "proc main() { var x: int; }"
|
||||||
expected (Program [ProcedureDefinition _ _ variables _]) =
|
expected (Program [ProcedureDefinition _ _ variables _]) =
|
||||||
not $ null variables
|
not $ null variables
|
||||||
expected _ = False
|
expected _ = False
|
||||||
@ -59,11 +59,11 @@ spec =
|
|||||||
in actual `parseSatisfies` expected
|
in actual `parseSatisfies` expected
|
||||||
|
|
||||||
it "parses negation" $
|
it "parses negation" $
|
||||||
let given = "proc main(x: integer) { var y: integer; y := -x; }"
|
let given = "proc main(x: int) { var y: int; y := -x; }"
|
||||||
parameters = pure $ Parameter "x" (NamedType "integer") False
|
parameters = pure $ Parameter "x" (NamedType "int") False
|
||||||
variables = pure
|
variables = pure
|
||||||
$ VariableDeclaration "y"
|
$ VariableDeclaration "y"
|
||||||
$ NamedType "integer"
|
$ NamedType "int"
|
||||||
body = pure
|
body = pure
|
||||||
$ AssignmentStatement (VariableExpression "y")
|
$ AssignmentStatement (VariableExpression "y")
|
||||||
$ NegationExpression
|
$ NegationExpression
|
||||||
@ -91,10 +91,10 @@ spec =
|
|||||||
in actual `shouldParse` expected
|
in actual `shouldParse` expected
|
||||||
|
|
||||||
it "parses hexadecimals" $
|
it "parses hexadecimals" $
|
||||||
let given = "proc main() { var x: integer; x := 0x10; }"
|
let given = "proc main() { var x: int; x := 0x10; }"
|
||||||
variables = pure
|
variables = pure
|
||||||
$ VariableDeclaration "x"
|
$ VariableDeclaration "x"
|
||||||
$ NamedType "integer"
|
$ NamedType "int"
|
||||||
body = pure
|
body = pure
|
||||||
$ AssignmentStatement (VariableExpression "x")
|
$ AssignmentStatement (VariableExpression "x")
|
||||||
$ LiteralExpression (HexadecimalLiteral 16)
|
$ LiteralExpression (HexadecimalLiteral 16)
|
||||||
|
Loading…
Reference in New Issue
Block a user