HsParrot-0.0.2.20120717: Haskell integration with Parrot virtual machine

Safe HaskellNone

Language.PIR

Contents

Description

Parrot PIR syntax tree.

   All that is gold does not glitter,
   Not all those who wander are lost;
   The old that is strong does not wither,
   Deep roots are not reached by the frost.

Synopsis

Documentation

type PIR = [Decl]

PIR code consists of declarations.

data Decl

Constructors

DeclSub

Subroutine declaration

Fields

dsName :: !SubName
 
dsFlags :: ![SubFlag]
 
dsBody :: ![Stmt]
 
DeclNS

Namespace declaration

Fields

dnPackage :: !PkgName
 
dnBody :: ![Decl]
 
DeclInc

.include directive

Fields

diFile :: !FilePath
 
DeclHLL

HLL directive

Fields

dhLang :: !String
 
dhGroup :: !String
 

Instances

Eq Decl 
Show Decl 
Typeable Decl 
YAML Decl 
Emit Decl

Emits PIR code for declarations (namespace, include, or sub declarations).

data Stmt

Constructors

StmtComment !String

Comment

StmtLine !FilePath !Int

#line directive

StmtPad ![(VarName, Expression)] ![Stmt]

Lexical Pad

StmtRaw !Doc

Backdoor into raw Doc

StmtIns !Ins

Generic instructions

StmtSub !SubName ![Stmt]

Inner subroutine

data Ins

Constructors

InsLocal !RegType !VarName

.local directive

InsNew !LValue !ObjType

new opcode

InsBind !LValue !Expression

set opcode

InsAssign !LValue !Expression

assign opcode

InsPrim !(Maybe LValue) !PrimName ![Expression]

Other opcodes

InsFun ![Sig] !Expression ![Expression]

Function call

InsTailFun !Expression ![Expression]

Tail call

InsLabel !LabelName

Label

InsComment !String !(Maybe Ins)

Comment

InsExp !Expression

Generic expressions

InsConst !LValue !ObjType !Expression

Constant

data LValue

Constructors

VAR !VarName

A variable declared by .local

PMC !Int

PMC register n

STR !Int

String register n

INT !Int

Integer register n

NUM !Int

Number register n

KEYED !LValue !Expression 

data Literal

Constructors

LitStr !String

A literal string

LitInt !Integer

A literal integer

LitNum !Double

A literal number

Instances

Eq Literal 
Show Literal 
Typeable Literal 
YAML Literal 
Emit Literal

Emits a literal (a LitStr, LitInt, or LitNum), and escapes if necessary.

data SubFlag

Tags a PIR subroutine definition with @MAIN, @LOAD, @ANON, @METHOD, or @MULTI.

Instances

Eq SubFlag 
Show SubFlag 
Typeable SubFlag 
YAML SubFlag 
Emit SubFlag

Emits PIR code for a SubFlag (e.g. :main, :anon, etc.).

data RegType

Constructors

RegInt

I (Integer) register

RegNum

N (Number) register

RegStr

S (String) register

RegPMC

P (PMC) register

data ObjType

A PMC type, which, for example, can be given as an argument to the new opcode (e.g. new .PerlScalar).

Instances

Eq ObjType 
Show ObjType 
Typeable ObjType 
YAML ObjType 
Emit ObjType

Emits PIR code for an ObjType (e.g. .PerlScalar).

LiteralClass ObjType 

emitRets :: [Sig] -> Doc

emitFun :: (Emit b, Emit c) => CallConv -> b -> [c] -> [Sig] -> Doc

emitArgs :: Emit a => [a] -> Doc

emitFunName :: Emit b => CallConv -> String -> [b] -> [Sig] -> Doc

include :: PkgName -> Decl

.include directive.

hll :: String -> String -> Decl

.HLL directive.

(<:=) :: LValue -> Expression -> Ins

Short for InsBind (binding).

(<==) :: LValue -> Expression -> Ins

Short for InsAssign.

(<--) :: LValue -> PrimName -> [Expression] -> Ins

Calls an opcode which returns a value.

(.-) :: PrimName -> [Expression] -> Ins

Calls an opcode, ignoring any return values.

(<-&) :: [Sig] -> Expression -> [Expression] -> Ins

Calls an user-defined sub which returns a list of values.

(.&) :: Expression -> [Expression] -> Ins

Calls an user-defined sub, ignoring any return values.

lit0 :: Expression

Literal zero

nullPMC :: RegClass a => a

$P0 register

funPMC :: RegClass a => a

$P1 register

rv :: RegClass a => a

$P2 register

arg0 :: RegClass a => a

$P10 register

arg1 :: RegClass a => a

$P11 register

arg2 :: RegClass a => a

$P12 register

arg3 :: RegClass a => a

$P13 register

tempPMC :: RegClass a => a

$P8 register

tempPMC2 :: RegClass a => a

$P9 register

tempSTR :: RegClass a => a

$S8 register

tempSTR2 :: RegClass a => a

$S9 register

tempSTR3 :: RegClass a => a

$S10 register

tempINT :: RegClass a => a

$I8 register

tempINT2 :: RegClass a => a

$I9 register

tempINT3 :: RegClass a => a

$I10 register

tempINT4 :: RegClass a => a

$I11 register

tempNUM :: RegClass a => a

$N8 register

tempNUM2 :: RegClass a => a

$N9 register

class RegClass y where

Methods

reg :: LValue -> y

sub

Arguments

:: SubName

Name of the subroutine

-> [Sig]

Signature

-> [Ins]

Subroutine body

-> Decl

The final subroutine declaration

Subroutine declaration.

data Sig

Constructors

MkSig 

slurpy :: Expression -> Sig

Marks a parameter as slurpy.

(-->) :: Decl -> [Expression] -> Decl

Returns from a sub.

vop1

Arguments

:: SubName

Perl 6 name of the opcode to wrap

-> PrimName

PIR opcode

-> Decl

Final subroutine declaration

In the case a Perl 6 builtin corresponds exactly to a PIR opcode, you can use vop1 to create an appropriate wrapper for an opcode expecting one argument.

vop2

Arguments

:: SubName

Perl 6 name of the opcode to wrap

-> PrimName

PIR opcode

-> Decl

Final subroutine declaration

In the case a Perl 6 builtin corresponds exactly to a PIR opcode, you can use vop2 to create an appropriate wrapper for an opcode expecting two arguments.

vop2keyed

Arguments

:: SubName

Perl 6 name of the sub to create

-> LValue

Intermediate register to convert the index to (e.g. tempINT or tempSTR)

-> Decl

Final subroutine declaration

Creates a sub which accepts a thing which allows keyed access (for example aggregates) and an index.

vop1x

Arguments

:: SubName

Perl 6 name of the sub to create

-> PrimName

Opcode to wrap

-> (forall a. RegClass a => a)

Register to use for the return value of the op

-> (forall b. RegClass b => b)

Register type to convert the parameter to

-> Decl

Final subroutine declaration

Generic wrapper for unary opcodes.

vop1coerce

Arguments

:: SubName

Perl 6 name of the sub to create

-> (forall a. RegClass a => a)

Register type to convert the parameter to

-> Decl

Final subroutine declaration

Generic wrapper for coercion/context forcing (used by &prefix:<+>, &prefix:<~>, etc.)

vop2x

Arguments

:: SubName

Perl 6 name of the sub to create

-> PrimName

Opcode to wrap

-> (forall a. RegClass a => a)

Register to use for the return value of the op

-> (forall b. RegClass b => b)

Register type to convert the first parameter to

-> (forall c. RegClass c => c)

Register type to convert the second parameter to

-> Decl

Final subroutine declaration

Generic wrapper for two-ary opcodes.

vop1ii :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts and returns an I register.

vop1nn :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts and returns a N register.

vop1ss :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts and returns a S register.

vop1si :: SubName -> PrimName -> Decl

Wrapper for an opcode which returns a S register and accepts a I register.

vop1is :: SubName -> PrimName -> Decl

Wrapper for an opcode which returns a I register and accepts a S register.

vop1ip :: SubName -> PrimName -> Decl

Wrapper for an opcode which returns a I register and accepts a P register.

vop2iii :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts and returns I registers.

vop2nnn :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts and returns N registers.

vop2iss :: SubName -> PrimName -> Decl

Wrapper for an opcode which accepts two S registers and returns a native integer (I register).

stmtControlLoop

Arguments

:: VarName

Perl 6 name of the new sub

-> PrimName

PIR opcode to use for branching

-> Decl

Final declaration of the sub

Creates appropriate &statement_control:foo subroutines.

stmtControlCond

Arguments

:: VarName

Perl 6 name of the new sub

-> PrimName

PIR opcode to use for branching

-> Decl

Final declaration of the sub

Creates appropriate &statement_control:foo subroutines.

op2Logical

Arguments

:: VarName

Perl 6 name of the sub to create

-> PrimName

PIR opcode to use (if, unless)

-> Decl

Final declaration of the sub

Creates appropriate &infix:foo subs for logical operators (||, &&, etc.).

escaped :: String -> String

Escapes characters which have a special meaning in PIR.

preludePIR :: Doc

The Prelude, defining primitives like &say, &infix:+, etc.

Generated by DrIFT : Look, but Don't Touch. *

class Show x => Emit x where

Methods

emit :: x -> Doc

Instances

Emit Int 
Emit String 
Emit Doc 
Emit ObjType

Emits PIR code for an ObjType (e.g. .PerlScalar).

Emit RegType 
Emit SubFlag

Emits PIR code for a SubFlag (e.g. :main, :anon, etc.).

Emit Literal

Emits a literal (a LitStr, LitInt, or LitNum), and escapes if necessary.

Emit LValue 
Emit Expression 
Emit Ins 
Emit Stmt 
Emit Decl

Emits PIR code for declarations (namespace, include, or sub declarations).

Emit a => Emit [a] 
Emit [ArgFlag] 
Emit a => Emit (Maybe a) 

nested :: Emit x => x -> Doc

eqSep :: (Emit a, Emit b, Emit c) => a -> b -> [c] -> Doc

commaSep :: Emit x => [x] -> Doc