| Copyright | (c) Petr Penzin 2015 | 
|---|---|
| License | BSD2 | 
| Maintainer | penzin.dev@gmail.com | 
| Stability | experimental | 
| Portability | cross-platform | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Binary.Neko.Instructions
Description
Types and primitives to deal with Binary.Neko instructions
- data Instruction
- = AccNull
 - | AccTrue
 - | AccFalse
 - | AccThis
 - | AccInt Int
 - | AccStack Int
 - | AccGlobal Int
 - | AccEnv Int
 - | AccField String
 - | AccArray
 - | AccIndex Int
 - | AccBuiltin String
 - | SetStack Int
 - | SetGlobal Int
 - | SetEnv Int
 - | SetField String
 - | SetArray
 - | SetIndex Int
 - | SetThis
 - | Push
 - | Pop Int
 - | Call Int
 - | ObjCall Int
 - | Jump Int
 - | JumpIf Int
 - | JumpIfNot Int
 - | Trap Int
 - | EndTrap
 - | Ret Int
 - | MakeEnv Int
 - | MakeArray Int
 - | Bool
 - | IsNull
 - | IsNotNull
 - | Add
 - | Sub
 - | Mult
 - | Div
 - | Mod
 - | Shl
 - | Shr
 - | UShr
 - | Or
 - | And
 - | Xor
 - | Eq
 - | Neq
 - | Gt
 - | Gte
 - | Lt
 - | Lte
 - | Not
 - | TypeOf
 - | Compare
 - | Hash
 - | New
 - | JumpTable Int
 - | Apply Int
 - | AccStack0
 - | AccStack1
 - | AccIndex0
 - | AccIndex1
 - | PhysCompare
 - | TailCall (Int, Int)
 - | Loop
 
 - readInstructions :: Word32 -> Hashtbl -> ByteString -> (ByteString, String, Maybe [Instruction])
 - readInstruction :: Hashtbl -> ByteString -> (Maybe Instruction, ByteString)
 - getInstructions :: Word32 -> Hashtbl -> Get [Instruction]
 - getInstruction :: Hashtbl -> Get Instruction
 - getOp :: Word8 -> Maybe Int32 -> Hashtbl -> Get Instruction
 - opcode :: Instruction -> (Word8, Maybe Word32)
 - putInstruction :: Instruction -> Put
 - putInstructions :: [Instruction] -> Put
 - hasParam :: Instruction -> Bool
 
Documentation
data Instruction Source #
Various NekoVM instructions
Constructors
Instances
Arguments
| :: Word32 | code size  | 
| -> Hashtbl | context (names of fields)  | 
| -> ByteString | bytes to read from  | 
| -> (ByteString, String, Maybe [Instruction]) | unconsumed input, status message and list of instructions  | 
Read instructions Consume bytestring, produce instructions and status message
Arguments
| :: Hashtbl | Names of fieds for the module  | 
| -> ByteString | Input  | 
| -> (Maybe Instruction, ByteString) | Result or nothing, unconsumed input  | 
Read a single bytecode instruction
Arguments
| :: Word32 | code size - number of instructions+arguments left to parse  | 
| -> Hashtbl | Builtins hashtable to provide context  | 
| -> Get [Instruction] | decoder  | 
Grab instructions from a bytestring Decode bytestring, consuming one byte per instruction with no paramenters and two for instructions with parameters
Arguments
| :: Hashtbl | Builtins hashtable for getting names  | 
| -> Get Instruction | Instruction parser  | 
Grab a single instruction from a bytestring Some instruction acces filds by using hashes of the names, therefore require a hash table with field names.
Arguments
| :: Word8 | Operation number  | 
| -> Maybe Int32 | Additional argument  | 
| -> Hashtbl | Some instructions require access to builtins hashtable  | 
| -> Get Instruction | Instruction parser  | 
Second level of instruction read logic
Arguments
| :: Instruction | Instruction to process  | 
| -> (Word8, Maybe Word32) | Opcode and additional argument  | 
Get integer opcode
putInstruction :: Instruction -> Put Source #
Write instruction out using Put monad
putInstructions :: [Instruction] -> Put Source #
Write a few instructions out using Put monad
hasParam :: Instruction -> Bool Source #
Determine whether instruction has a parameter