epic-0.1.11: Compiler for a simple functional language

Portabilitynon-portable
Stabilityexperimental
Maintainereb@cs.st-andrews.ac.uk

Epic.Epic

Contents

Description

Combinators for builing Epic programs

Synopsis

Expressions

class EpicExpr e whereSource

Build expressions, with a name supply

Methods

term :: e -> State Int ExprSource

class EpicFn e Source

Build a function definition, with a name supply

Instances

EpicFn Expr 
EpicFn Term 
EpicFn e => EpicFn (Expr -> e) 
EpicFn e => EpicFn ([Name], e) 

class Alternative e Source

Build a case alternative, with a name supply

type Term = State Int ExprSource

A sub-term, with a name supply

data Name Source

Instances

Eq Name 
Show Name 
EpicExpr sc => LetExpr (Name, sc) 
Alternative ([Name], Expr) 
EpicFn e => EpicFn ([Name], e) 
EpicExpr e => EpicExpr ([Name], e) 

(@@)Source

Arguments

:: (EpicExpr f, EpicExpr a) 
=> f

function

-> a

argument

-> Term 

Application

case_ :: EpicExpr e => e -> [State Int CaseAlt] -> TermSource

Build a case expression with a list of alternatives

con_Source

Arguments

:: Int

Tag

-> Term 

Build a constructor with the given tag

tuple_ :: TermSource

Build a tuple

conSource

Arguments

:: Alternative e 
=> Int

the tag

-> e

RHS of alternative

-> State Int CaseAlt 

Case alternative for constructor with the given tag

tupleSource

Arguments

:: Alternative e 
=> e

RHS of alternative

-> State Int CaseAlt 

Case alternative for a tuple with the given tag

constcaseSource

Arguments

:: EpicExpr a 
=> Int

the constant

-> a 
-> State Int CaseAlt 

Case alternative for a constant

defaultcase :: EpicExpr a => a -> State Int CaseAltSource

Default case if no other branches apply

if_ :: (EpicExpr a, EpicExpr t, EpicExpr e) => a -> t -> e -> TermSource

while_Source

Arguments

:: (EpicExpr t, EpicExpr b) 
=> t

Boolean test (most likely effectful)

-> b

Body

-> Term 

While loops (primitive, for efficiency).

whileAcc_Source

Arguments

:: (EpicExpr t, EpicExpr a, EpicExpr b) 
=> t

Boolean test (most likely effectful)

-> a

Accumulator (of type a)

-> b

Body (of type a -> a)

-> Term 

While loop, with an accumulator

lazy_ :: EpicExpr a => a -> TermSource

Evaluate an expression lazily

effect_ :: EpicExpr a => a -> TermSource

Evaluate an expression but don't update the closure with the result. | Use this if the expression has a side effect.

foreign_ :: EpicExpr e => Type -> String -> [(e, Type)] -> TermSource

foreignL_ :: EpicExpr e => Type -> String -> [(e, Type)] -> TermSource

let_ :: (LetExpr e, EpicExpr val) => val -> e -> State Int ExprSource

letN_ :: (EpicExpr val, EpicExpr scope) => Name -> val -> scope -> TermSource

Let bindings with an explicit name

update_ :: (EpicExpr val, EpicExpr scope) => Expr -> val -> scope -> TermSource

Update a local variable (could be an explicit name or bound with a lambda, so we let it be an Expr.

op_ :: (EpicExpr a, EpicExpr b) => Op -> a -> b -> TermSource

str :: String -> TermSource

Constant string

int :: Int -> TermSource

Constant integer

float :: Float -> TermSource

Constant float

char :: Char -> TermSource

Constant character

bool :: Bool -> TermSource

Constant bool

(!.)Source

Arguments

:: EpicExpr t 
=> t

Expression in constructor form

-> Int

Argument number

-> Term 

Project an argument from an expression which evaluates to constructor form.

fn :: String -> TermSource

Reference to a function name

ref :: Name -> TermSource

Reference to a function name

(+>) :: EpicExpr c => c -> Term -> TermSource

Constructor for the unit type

Sequence terms --- evaluate the first then second

malloc_Source

Arguments

:: (EpicExpr a, EpicExpr b) 
=> a

Size of block to allocate

-> b

Expression to evaluate

-> Term 

Evaluate an expression under manually allocated memory. Creates a pool of memory. All allocation is from this pool, and there is no garbage collection. The pool is freed after evaluation.

Types

data Type Source

Instances

Operators

eq_ :: OpSource

lt_ :: OpSource

gt_ :: OpSource

Declarations and programs

data EpicDecl Source

Top level declarations

Constructors

forall e . EpicFn e => EpicFn Name e

Normal function

Include String

Include a C header

Link String

Link to a C library

CType String

Export a C type

Instances

Compiling and execution

compile :: Program -> FilePath -> IO ()Source

Compile a program to an executable

compileObj :: Program -> FilePath -> IO ()Source

Compile a program to a .o

link :: [FilePath] -> FilePath -> IO ()Source

Link a collection of object files. By convention, the entry point is the function called main.

compileWith :: [CompileOptions] -> Program -> FilePath -> IO ()Source

Compile a program to an executable, with options

compileObjWith :: [CompileOptions] -> Program -> FilePath -> IO ()Source

Compile a program to a .o, with options

linkWith :: [CompileOptions] -> [FilePath] -> FilePath -> IO ()Source

Link a collection of object files, with options. By convention, the entry point is the function called main.

data CompileOptions Source

(Debugging) options to give to compiler

Constructors

KeepC

Keep intermediate C file

Trace

Generate trace at run-time (debug)

ShowBytecode

Show generated code

ShowParseTree

Show parse tree

MakeHeader FilePath

Output a .h file too

GCCOpt String

Extra GCC option

Debug

Generate debug info

Checking Int

Checking level (0 none)

ExternalMain

main is defined externally (in C)

MainInc FilePath

File to #include in main program

Instances

Some basic definitions

basic_defs :: [EpicDecl]Source

Some default definitions: putStr, putStrLn, readStr, append, intToString