simple-pascal-0.1: Simplified Pascal language to SSVM compiler

Language.Pascal.Types

Synopsis

Documentation

type Id = StringSource

Type for symbol identifiers

data Annotate node ann Source

Attach annotation to node

Constructors

Annotate 

Fields

content :: node
 
annotation :: ann
 

Instances

(Eq node, Eq ann) => Eq (Annotate node ann) 
Show node => Show (Annotate node ann) 
CodeGen (a TypeAnn) => CodeGen (:~ a TypeAnn) 
CodeGen (:~ Expression TypeAnn) 
CodeGen (:~ LValue TypeAnn) 

data SrcPos Source

Position of node in the source code

Constructors

SrcPos 

Fields

srcLine :: Int
 
srcColumn :: Int
 

Instances

type :~ node ann = Annotate (node ann) annSource

Recursive annotated type

withType :: Annotate a SrcPos -> Type -> Annotate a TypeAnnSource

Attach type info to node

annotate :: ann -> Annotate node old -> Annotate node annSource

Change annotation of annotated node

data Program a Source

Program

Constructors

Program 

Fields

progConsts :: [(Id, Expression :~ a)]

constants

progTypes :: Map Id Type

user defined types

progVariables :: [Annotate Symbol a]

global variables

progFunctions :: [Function :~ a]

functions

progBody :: [Statement :~ a]

program body statements

Instances

Typed Program 
Eq a => Eq (Program a) 
Show (Program a) 
CodeGen (Program TypeAnn) 

data Function a Source

Function (or procedure)

Constructors

Function 

Fields

fnName :: String

function name

fnFormalArgs :: [Annotate Symbol a]

formal arguments

fnResultType :: Type

return type (if TVoid then this is procedure)

fnVars :: [Annotate Symbol a]

local variables

fnBody :: [Statement :~ a]

function body statements

Instances

type SymbolTable = [Map Id Symbol]Source

Symbol table

data Symbol Source

A symbol

Constructors

Symbol 

Fields

symbolName :: Id
 
symbolType :: Type
 
symbolDefLine :: Int

Source line where symbol was defined

symbolDefCol :: Int

Source column

Instances

(#) :: Id -> Type -> SymbolSource

Make symbol from it's name and type

data Type Source

Supported data types

Constructors

TInteger 
TString 
TBool 
TVoid 
TUser Id

user defined type

TAny

any value (dynamic typing)

TArray Integer Type

array of some type

TRecord [(Id, Type)]

record

TField Int Type

record field: field index and type

TFunction [Type] Type

formal arguments types and return type

Instances

data LValue a Source

Assignment LHS value: variable or array item

Constructors

LVariable Id 
LArray Id (Expression :~ a) 
LField Id Id 

Instances

Typed LValue 
Eq a => Eq (LValue a) 
Show (LValue a) 
CodeGen (:~ LValue TypeAnn) 

data Statement a Source

Program statements

Constructors

Assign (LValue :~ a) (Expression :~ a)

lvalue := expression;

Procedure Id [Expression :~ a]

procedureName(arguments);

Return (Expression :~ a)

return expression;

Break

break (for loop)

Continue

contnune (for loop)

Exit

exit (procedure or program)

IfThenElse (Expression :~ a) [Statement :~ a] [Statement :~ a]

if expression then ... else ...

For Id (Expression :~ a) (Expression :~ a) [Statement :~ a]

for i := start to end do ...

Instances

data Lit Source

Literal values

Instances

data Expression a Source

Expressions

Constructors

Variable Id

named variable value

ArrayItem Id (Expression :~ a)

array item

RecordField Id Id

record field

Literal Lit

literal value

Call Id [Expression :~ a]

functionName(arguments)

Op BinOp (Expression :~ a) (Expression :~ a)

binary operation (x+y etc)

data BinOp Source

Supported binary operations

Constructors

Add 
Sub 
Mul 
Div 
Mod 
Pow 
IsGT 
IsLT 
IsEQ 
IsNE 

Instances

data Context Source

Compiler context (where we are?)

Constructors

Unknown

unknown context (== internal error)

Outside

Outside program body or functions

ProgramBody

In the program body

ForLoop Id Int

In the for loop (started on nth instruction, with named counter)

InFunction Id Type

In the named function (returning named type)

Instances

contextId :: Context -> StringSource

Context ID, for labels and variable names generation

data CodeGenState Source

Code generator state

Constructors

CGState

already generated code

Fields

constants :: [(Id, Lit)]
 
variables :: [Id]

declared variables (not used currently)

currentContext :: [Context]

current contexts stack

quoteMode :: Bool

quote (word declaration) mode

generated :: Code
 

emptyGState :: CodeGenStateSource

Starting code generator state

inContext :: Checker m => Context -> m a -> m aSource