tools/pas2c/PascalUnitSyntaxTree.hs
author nemo
Mon, 08 Dec 2014 09:35:14 -0500
changeset 10634 35d059bd0932
parent 10142 adb804cb2638
child 10747 07ade56c3b4a
permissions -rw-r--r--
Use FreeAndNil across the board. Even if we are immediately assigning after, probably avoids accidental mistakes. Also free neglected owner tex on shutdown, and delete hog gears using the normal deletion procedure if for any reason they still exist (EndGame call?).

module PascalUnitSyntaxTree where

data PascalUnit =
    Program Identifier Implementation Phrase
    | Unit Identifier Interface Implementation (Maybe Initialize) (Maybe Finalize)
    | System [TypeVarDeclaration]
    | Redo [TypeVarDeclaration]
    deriving (Show, Eq)
data Interface = Interface Uses TypesAndVars
    deriving (Show, Eq)
data Implementation = Implementation Uses TypesAndVars
    deriving (Show, Eq)
data Identifier = Identifier String BaseType
    deriving (Show, Eq)
data TypesAndVars = TypesAndVars [TypeVarDeclaration]
    deriving (Show, Eq)
data TypeVarDeclaration = TypeDeclaration Identifier TypeDecl
    | VarDeclaration Bool Bool ([Identifier], TypeDecl) (Maybe InitExpression)
    | FunctionDeclaration Identifier Bool Bool Bool TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase))
    | OperatorDeclaration String Identifier Bool TypeDecl [TypeVarDeclaration] (Maybe (TypesAndVars, Phrase))
    deriving (Show, Eq)
data TypeDecl = SimpleType Identifier
    | RangeType Range
    | Sequence [Identifier]
    | ArrayDecl (Maybe Range) TypeDecl
    | RecordType [TypeVarDeclaration] (Maybe [[TypeVarDeclaration]])
    | PointerTo TypeDecl
    | String
    | AString
    | Set TypeDecl
    | FunctionType TypeDecl [TypeVarDeclaration]
    | DeriveType InitExpression
    | VoidType
    | VarParamType TypeDecl -- this is a hack
    deriving (Show, Eq)
data Range = Range Identifier
           | RangeFromTo InitExpression InitExpression
           | RangeInfinite
    deriving (Show, Eq)
data Initialize = Initialize String
    deriving (Show, Eq)
data Finalize = Finalize String
    deriving (Show, Eq)
data Uses = Uses [Identifier]
    deriving (Show, Eq)
data Phrase = ProcCall Reference [Expression]
        | IfThenElse Expression Phrase (Maybe Phrase)
        | WhileCycle Expression Phrase
        | RepeatCycle Expression [Phrase]
        | ForCycle Identifier Expression Expression Phrase Bool -- The last Boolean indicates wether it's up or down counting
        | WithBlock Reference Phrase
        | Phrases [Phrase]
        | SwitchCase Expression [([InitExpression], Phrase)] (Maybe [Phrase])
        | Assignment Reference Expression
        | BuiltInFunctionCall [Expression] Reference
        | NOP
    deriving (Show, Eq)
data Expression = Expression String
    | BuiltInFunCall [Expression] Reference
    | PrefixOp String Expression
    | PostfixOp String Expression
    | BinOp String Expression Expression
    | StringLiteral String
    | PCharLiteral String
    | CharCode String
    | HexCharCode String
    | NumberLiteral String
    | FloatLiteral String
    | HexNumber String
    | Reference Reference
    | SetExpression [Identifier]
    | Null
    deriving (Show, Eq)
data Reference = ArrayElement [Expression] Reference
    | FunCall [Expression] Reference
    | TypeCast Identifier Expression
    | SimpleReference Identifier
    | Dereference Reference
    | RecordField Reference Reference
    | Address Reference
    | RefExpression Expression
    deriving (Show, Eq)
data InitExpression = InitBinOp String InitExpression InitExpression
    | InitPrefixOp String InitExpression
    | InitReference Identifier
    | InitArray [InitExpression]
    | InitRecord [(Identifier, InitExpression)]
    | InitFloat String
    | InitNumber String
    | InitHexNumber String
    | InitString String
    | InitChar String
    | BuiltInFunction String [InitExpression]
    | InitSet [InitExpression]
    | InitAddress InitExpression
    | InitNull
    | InitRange Range
    | InitTypeCast Identifier InitExpression
    deriving (Show, Eq)

data BaseType = BTUnknown
    | BTChar
    | BTString
    | BTAString
    | BTInt Bool -- second param indicates whether signed or not
    | BTBool
    | BTFloat
    | BTRecord String [(String, BaseType)]
    | BTArray Range BaseType BaseType
    | BTFunction Bool Bool [(Bool, BaseType)] BaseType -- in (Bool, BaseType), Bool indiciates whether var or not
    | BTPointerTo BaseType
    | BTUnresolved String
    | BTSet BaseType
    | BTEnum [String]
    | BTVoid
    | BTUnit
    | BTVarParam BaseType
    deriving (Show, Eq)