lua-bc-0.1.0.1: Lua bytecode parser

Safe HaskellNone
LanguageHaskell2010

Language.Lua.Bytecode

Synopsis

Documentation

newtype Reg Source #

Constructors

Reg Int 

Instances

Enum Reg Source # 

Methods

succ :: Reg -> Reg #

pred :: Reg -> Reg #

toEnum :: Int -> Reg #

fromEnum :: Reg -> Int #

enumFrom :: Reg -> [Reg] #

enumFromThen :: Reg -> Reg -> [Reg] #

enumFromTo :: Reg -> Reg -> [Reg] #

enumFromThenTo :: Reg -> Reg -> Reg -> [Reg] #

Eq Reg Source # 

Methods

(==) :: Reg -> Reg -> Bool #

(/=) :: Reg -> Reg -> Bool #

Ord Reg Source # 

Methods

compare :: Reg -> Reg -> Ordering #

(<) :: Reg -> Reg -> Bool #

(<=) :: Reg -> Reg -> Bool #

(>) :: Reg -> Reg -> Bool #

(>=) :: Reg -> Reg -> Bool #

max :: Reg -> Reg -> Reg #

min :: Reg -> Reg -> Reg #

Read Reg Source # 
Show Reg Source # 

Methods

showsPrec :: Int -> Reg -> ShowS #

show :: Reg -> String #

showList :: [Reg] -> ShowS #

PP Reg Source # 

Methods

pp :: PPInfo -> Reg -> Doc Source #

newtype UpIx Source #

Constructors

UpIx Int 

Instances

Eq UpIx Source # 

Methods

(==) :: UpIx -> UpIx -> Bool #

(/=) :: UpIx -> UpIx -> Bool #

Ord UpIx Source # 

Methods

compare :: UpIx -> UpIx -> Ordering #

(<) :: UpIx -> UpIx -> Bool #

(<=) :: UpIx -> UpIx -> Bool #

(>) :: UpIx -> UpIx -> Bool #

(>=) :: UpIx -> UpIx -> Bool #

max :: UpIx -> UpIx -> UpIx #

min :: UpIx -> UpIx -> UpIx #

Read UpIx Source # 
Show UpIx Source # 

Methods

showsPrec :: Int -> UpIx -> ShowS #

show :: UpIx -> String #

showList :: [UpIx] -> ShowS #

PP UpIx Source # 

Methods

pp :: PPInfo -> UpIx -> Doc Source #

newtype Kst Source #

Constructors

Kst Int 

Instances

Eq Kst Source # 

Methods

(==) :: Kst -> Kst -> Bool #

(/=) :: Kst -> Kst -> Bool #

Ord Kst Source # 

Methods

compare :: Kst -> Kst -> Ordering #

(<) :: Kst -> Kst -> Bool #

(<=) :: Kst -> Kst -> Bool #

(>) :: Kst -> Kst -> Bool #

(>=) :: Kst -> Kst -> Bool #

max :: Kst -> Kst -> Kst #

min :: Kst -> Kst -> Kst #

Read Kst Source # 
Show Kst Source # 

Methods

showsPrec :: Int -> Kst -> ShowS #

show :: Kst -> String #

showList :: [Kst] -> ShowS #

PP Kst Source # 

Methods

pp :: PPInfo -> Kst -> Doc Source #

data RK Source #

Constructors

RK_Reg Reg 
RK_Kst Kst 

Instances

Eq RK Source # 

Methods

(==) :: RK -> RK -> Bool #

(/=) :: RK -> RK -> Bool #

Ord RK Source # 

Methods

compare :: RK -> RK -> Ordering #

(<) :: RK -> RK -> Bool #

(<=) :: RK -> RK -> Bool #

(>) :: RK -> RK -> Bool #

(>=) :: RK -> RK -> Bool #

max :: RK -> RK -> RK #

min :: RK -> RK -> RK #

Read RK Source # 
Show RK Source # 

Methods

showsPrec :: Int -> RK -> ShowS #

show :: RK -> String #

showList :: [RK] -> ShowS #

PP RK Source # 

Methods

pp :: PPInfo -> RK -> Doc Source #

data Chunk Source #

Constructors

Chunk Int Function

number of upvalues and function body

data OpCode Source #

Constructors

OP_MOVE Reg Reg

A B R(A) := R(B)

OP_LOADK Reg Kst

A Bx R(A) := Kst(Bx)

OP_LOADKX Reg

A R(A) := Kst(extra arg)

OP_LOADBOOL Reg Bool Bool

A B C R(A) := (Bool)B; if (C) pc++

OP_LOADNIL Reg Int

A B R(A), R(A+1), ..., R(A+B) := nil

OP_GETUPVAL Reg UpIx

A B R(A) := UpValue[B]

OP_GETTABUP Reg UpIx RK

A B C R(A) := UpValue[B][RK(C)]

OP_GETTABLE Reg Reg RK

A B C R(A) := R(B)[RK(C)]

OP_SETTABUP UpIx RK RK

A B C UpValue[A][RK(B)] := RK(C)

OP_SETUPVAL Reg UpIx

A B UpValue[B] := R(A)

OP_SETTABLE Reg RK RK

A B C R(A)[RK(B)] := RK(C)

OP_NEWTABLE Reg Int Int

A B C R(A) := {} (size = B,C)

OP_SELF Reg Reg RK

A B C R(A+1) := R(B); R(A) := R(B)[RK(C)]

OP_ADD Reg RK RK

A B C R(A) := RK(B) + RK(C)

OP_SUB Reg RK RK

A B C R(A) := RK(B) - RK(C)

OP_MUL Reg RK RK

A B C R(A) := RK(B) * RK(C)

OP_MOD Reg RK RK

A B C R(A) := RK(B) % RK(C)

OP_POW Reg RK RK

A B C R(A) := RK(B) ^ RK(C)

OP_DIV Reg RK RK

A B C R(A) := RK(B) / RK(C)

OP_IDIV Reg RK RK

A B C R(A) := RK(B) // RK(C)

OP_BAND Reg RK RK

A B C R(A) := RK(B) & RK(C)

OP_BOR Reg RK RK

A B C R(A) := RK(B) | RK(C)

OP_BXOR Reg RK RK

A B C R(A) := RK(B) ~ RK(C)

OP_SHL Reg RK RK

A B C R(A) := RK(B) << RK(C)

OP_SHR Reg RK RK

A B C R(A) := RK(B) >> RK(C)

OP_UNM Reg Reg

A B R(A) := -R(B)

OP_BNOT Reg Reg

A B R(A) := ~R(B)

OP_NOT Reg Reg

A B R(A) := not R(B)

OP_LEN Reg Reg

A B R(A) := length of R(B)

OP_CONCAT Reg Reg Reg

A B C R(A) := R(B).. ... ..R(C)

OP_JMP (Maybe Reg) Int

A sBx pc+=sBx; if (A) close all upvalues >= R(A - 1)

OP_EQ Bool RK RK

A B C if ((RK(B) == RK(C)) ~= A) then pc++

OP_LT Bool RK RK

A B C if ((RK(B) < RK(C)) ~= A) then pc++

OP_LE Bool RK RK

A B C if ((RK(B) <= RK(C)) ~= A) then pc++

OP_TEST Reg Bool

A C if not (R(A) = C) then pc++

OP_TESTSET Reg Reg Bool

A B C if (R(B) = C) then R(A) := R(B) else pc++

OP_CALL Reg Count Count

A B C R(A), ... ,R(A+C-2) := R(A)(R(A+1), ... ,R(A+B-1))

OP_TAILCALL Reg Count Count

A B C return R(A)(R(A+1), ... ,R(A+B-1))

OP_RETURN Reg Count

A B return R(A), ... ,R(A+B-2) (see note)

OP_FORLOOP Reg Int

A sBx R(A)+=R(A+2); if R(A) <?= R(A+1) then { pc+=sBx; R(A+3)=R(A) }

OP_FORPREP Reg Int

A sBx R(A)-=R(A+2); pc+=sBx

OP_TFORCALL Reg Int

A C R(A+3), ... ,R(A+2+C) := R(A)(R(A+1), R(A+2));

OP_TFORLOOP Reg Int

A sBx if R(A+1) ~= nil then { R(A)=R(A+1); pc += sBx }

OP_SETLIST Reg Int Int

A B C R(A)[(C-1)*FPF+i] := R(A+i), 1 <= i <= B

OP_CLOSURE Reg ProtoIx

A Bx R(A) := closure(KPROTO[Bx])

OP_VARARG Reg Count

A B R(A), R(A+1), ..., R(A+B-2) = vararg

OP_EXTRAARG Int

Ax extra (larger) argument for previous opcode

plusReg Source #

Arguments

:: Reg 
-> Int

offset

-> Reg 

Compute a register relative to another.

diffReg :: Reg -> Reg -> Int Source #

Compute the distance between two registers.

regRange Source #

Arguments

:: Reg

start

-> Int

length

-> [Reg] 

Compute a list of registers given a startin register and length.