codec-beam-0.1.0: Erlang VM byte code assembler

Safe HaskellSafe
LanguageHaskell98

Codec.Beam.Instructions

Contents

Description

This module represents a type-safe port of Erlang's general instructions. If this is your first exposure to BEAM, __I highly recommend Erik Stenman's book: https://happi.github.io/theBeamBook__. The documentation in this module point there derives directly from there, the Jerlang project, and Erlang's source code.

Synopsis

Documentation

label Source #

Arguments

:: Label

unique identifier

-> Op 

Label gives this code address a name and marks the start of a basic block.

func_info Source #

Arguments

:: Text

function name

-> Int

arity

-> Op 

Define a function M:F/A in the current module.

Function and BIF calls

call Source #

Arguments

:: Int

arity

-> Label 
-> Op 

Call the function at label. Save the next instruction as the return address in the CP register.

call_last Source #

Arguments

:: Int

arity

-> Label 
-> Int

number of stack words to deallocate

-> Op 

Deallocate and do a tail recursive call to the function at label. Do not update the CP register. Before the call deallocate Deallocate words of stack.

call_only Source #

Arguments

:: Int

arity

-> Label 
-> Op 

Do a tail recursive call to the function at Label. Do not update the CP register.

call_ext :: Import -> Op Source #

Call the function of arity pointed to by Destination. Save the next instruction as the return address in the CP register.

call_ext_last :: Import -> Int -> Op Source #

Deallocate and do a tail call to function pointed to by Destination. Do not update the CP register. Deallocate some words from the stack before the call.

bif0 :: (Bif0 a1, NoGC a1, IsRegister a2) => a1 -> a2 -> Op Source #

Call the bif and store the result in register.

bif1 :: (Bif1 a2, NoGC a2, IsSource a3, IsRegister a4) => Label -> a2 -> a3 -> a4 -> Op Source #

Call the bif with the source, and store the result in register. On failure jump to label.

bif2 :: (Bif2 a2, NoGC a2, IsSource a3, IsSource a4, IsRegister a5) => Label -> a2 -> a3 -> a4 -> a5 -> Op Source #

Call the bif with the sources, and store the result in register. On failure jump to label.

call_ext_only :: Import -> Op Source #

Do a tail recursive call to the function at label. Do not update the CP register.

apply Source #

Arguments

:: Int

arity

-> Op 

Apply function object (in x[arity]) with args (in x[0..arity-1])

apply_last Source #

Arguments

:: Int

arity

-> Int

words to deallocate

-> Op 

Same as apply but does not save the CP and deallocates words

gc_bif1 Source #

Arguments

:: (Bif1 a3, IsSource a4, IsRegister a5) 
=> Label

jump here on failure

-> Int

number of X-registers to save

-> a3

BIF, something like erlang_localtime

-> a4

argument

-> a5

where to put the result

-> Op 

Call the bif with the argument, and store the result in the register. On failure jump to label. Do a garbage collection if necessary to allocate space on the heap for the result.

gc_bif2 :: (Bif2 a3, IsSource a4, IsSource a5, IsRegister a6) => Label -> Int -> a3 -> a4 -> a5 -> a6 -> Op Source #

Same as gc_bif1, but with two source arguments.

gc_bif3 :: (Bif3 a3, IsSource a4, IsSource a5, IsSource a6, IsRegister a7) => Label -> Int -> a3 -> a4 -> a5 -> a6 -> a7 -> Op Source #

Same as gc_bif1, but with three source arguments.

Allocating, deallocating and returning

allocate Source #

Arguments

:: Int

stack words needed

-> Int

live X registers

-> Op 

Allocate space for some words on the stack. If a GC is needed during allocation there are a number of live X registers. Also save the continuation pointer (CP) on the stack.

allocate_heap Source #

Arguments

:: Int

stack words needed

-> Int

heap words needed

-> Int

live X registers

-> Op 

Allocate space for some words on the stack and ensure there is space for words on the heap. If a GC is needed save Live number of X registers. Also save the continuation pointer (CP) on the stack.

allocate_zero Source #

Arguments

:: Int

stack words needed

-> Int

live X registers

-> Op 

Allocate space for some words on the stack. If a GC is needed during allocation there are a number of live X registers. Clear the new stack words. (By writing NIL.) Also save the continuation pointer (CP) on the stack.

allocate_heap_zero Source #

Arguments

:: Int

stack words needed

-> Int

heap words needed

-> Int

live X registers

-> Op 

Allocate space for some words on the stack and ensure there is space for words on the heap. If a GC is needed save Live number of X registers. Clear the new stack words. (By writing NIL.) Also save the continuation pointer (CP) on the stack.

test_heap Source #

Arguments

:: Int

heap words needed

-> Int

live number of X registers

-> Op 

Ensure there is space for HeapNeed words on the heap. If a GC is needed save live number of X registers.

init' :: Y -> Op Source #

Clear the stack word. (By writing NIL.)

deallocate :: Int -> Op Source #

Restore the continuation pointer (CP) from the stack and deallocate N+1 words from the stack (the + 1 is for the CP).

return' :: Op Source #

Return to the address in the continuation pointer (CP).

trim Source #

Arguments

:: Int

words to remove

-> Int

words ro keep

-> Op 

Reduce the stack usage by some number of words, keeping the CP on the top of the stack.

Sending and receiving

send :: Op Source #

Send argument in x(1) as a message to the destination process in x(0). The message in x(1) ends up as the result of the send in x(0).

remove_message :: Op Source #

Unlink the current message from the message queue and store a pointer to the message in x(0). Remove any timeout.

timeout :: Op Source #

Reset the save point of the mailbox and clear the timeout flag.

loop_rec :: Label -> X -> Op Source #

Loop over the message queue, if it is empty jump to label.

loop_rec_end :: Label -> Op Source #

Advance the save pointer to the next message and jump back to label.

wait :: Label -> Op Source #

Suspend the processes and set the entry point to the beginning of the receive loop at label.

wait_timeout :: IsSource a2 => Label -> a2 -> Op Source #

Sets up a timeout of source milliseconds and saves the address of the following instruction as the entry point if the timeout triggers.

recv_mark :: Label -> Op Source #

Save the end of the message queue and the address of the label so that a recv_set instruction can start | scanning the inbox from this position.

recv_set :: Label -> Op Source #

Check that the saved mark points to label and set the save pointer in the message queue to the last position of the message queue saved by the recv_mark instruction.

Comparision

is_lt :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is not less than second.

is_ge :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is less than second.

is_eq :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is not (numerically) equal to second.

is_ne :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is (numerically) equal to second.

is_eq_exact :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is not exactly equal to second.

is_ne_exact :: (IsSource a2, IsSource a3) => Label -> a2 -> a3 -> Op Source #

Compare two terms and jump to label if first is exactly equal to second.

Type tests

is_integer :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not an integer.

is_float :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a float.

is_number :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a number.

is_atom :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a atom.

is_pid :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a pid.

is_reference :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a reference.

is_port :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a port.

is_nil :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not nil.

is_binary :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a binary.

is_list :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a cons or nil.

is_nonempty_list :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a cons.

is_tuple :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a tuple.

test_arity :: IsSource a2 => Label -> a2 -> Int -> Op Source #

Test the arity of (the tuple in) source and jump to label if it is not equal to arity.

is_boolean :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of source and jump to label if it is not a boolean.

is_function :: IsSource a2 => Label -> a2 -> Op Source #

Test the type of the source and jump to label if it is not a function (i.e. fun or closure).

is_function2 Source #

Arguments

:: (IsSource a2, IsSource a3) 
=> Label 
-> a2

possible function

-> a3

possible arity

-> Op 

Test the type of the source and jump to label if it is not a function of the particular arity.

is_bitstr :: IsSource a2 => Label -> a2 -> Op Source #

is_map :: IsSource a2 => Label -> a2 -> Op Source #

is_tagged_tuple :: IsSource a2 => Label -> a2 -> Int -> Text -> Op Source #

Test the type of source and jumps to label if it is not a tuple. Test the arity of Reg and jumps to label if it is not of the given size. Test the first element of the tuple and jumps to label if it is not given atom.

Indexing and jumping

select_val :: IsSource a1 => a1 -> Label -> [(Label, Source)] -> Op Source #

Jump to the destination label corresponding to source in the destinations list, if no arity matches, jump to fail label.

select_tuple_arity :: IsSource a1 => a1 -> Label -> [(Label, Source)] -> Op Source #

Check the arity of the source tuple and jump to the corresponding destination label, if no arity matches, jump to FailLabel.

jump :: Label -> Op Source #

Jump to label.

Moving, extracting, modifying

move :: (IsSource a1, IsRegister a2) => a1 -> a2 -> Op Source #

Move the source (a literal or a register) to the destination register.

get_list Source #

Arguments

:: (IsRegister a1, IsRegister a2, IsRegister a3) 
=> a1

where to get the list

-> a2

where to put the head (car)

-> a3

where to put the tail (cdr)

-> Op 

Get the head and tail (or car and cdr) parts of a list (a cons cell) from the initial register and put them into the registers.

get_tuple_element Source #

Arguments

:: (IsRegister a1, IsRegister a3) 
=> a1

where to get the tuple

-> Int

target element index, 0-based

-> a3

where to put the element

-> Op 

Get a particular element number from the tuple in source and put it in the destination register.

set_tuple_element :: (IsSource a1, IsRegister a2) => a1 -> a2 -> Int -> Op Source #

Update the element at position of the tuple in register with the new source element.

Building terms

put_list Source #

Arguments

:: (IsSource a1, IsSource a2, IsRegister a3) 
=> a1

the new head

-> a2

the new tail

-> a3 
-> Op 

Build a list, from the front, and puts the resulting list in the register. Just like Erlang's | or Haskell's :.

put_tuple :: IsRegister a2 => Int -> a2 -> Op Source #

Constructs an empty tuple on the heap (size+1 words) and places its address into the Destination register. No elements are set at this moment. Put_tuple instruction is always followed by multiple put instructions which destructively set its elements one by one.

put :: IsSource a1 => a1 -> Op Source #

Raising errors

badmatch :: IsSource a1 => a1 -> Op Source #

case_end :: IsSource a1 => a1 -> Op Source #

fun support

call_fun Source #

Arguments

:: Int

arity

-> Op 

Call fun object (in x[Arity]) with args (in x[0..Arity-1]) Raises badarity if the arity doesn’t match the function object. Raises badfun if a non-function is passed.

Binary matching

bs_start_match2 :: (IsSource a2, IsRegister a5) => Label -> a2 -> Int -> Int -> a5 -> Op Source #

bs_get_integer2 :: (IsSource a4, IsRegister a7) => Label -> X -> Int -> a4 -> Int -> Int -> a7 -> Op Source #

bs_get_float2 :: (IsSource a4, IsRegister a7) => Label -> X -> Int -> a4 -> Int -> Int -> a7 -> Op Source #

bs_get_binary2 :: (IsSource a4, IsRegister a7) => Label -> X -> Int -> a4 -> Int -> Int -> a7 -> Op Source #

bs_skip_bits2 :: IsSource a3 => Label -> X -> a3 -> Int -> Int -> Op Source #

bs_save2 :: IsRegister a1 => a1 -> Int -> Op Source #

bs_restore2 :: IsRegister a1 => a1 -> Int -> Op Source #

bs_append :: (IsSource a2, IsSource a6, IsRegister a8) => Label -> a2 -> Int -> Int -> Int -> a6 -> Int -> a8 -> Op Source #

bs_private_append :: (IsSource a2, IsSource a4, IsRegister a6) => Label -> a2 -> Int -> a4 -> Int -> a6 -> Op Source #

Binary construction

bs_init2 :: (IsSource a2, IsRegister a6) => Label -> a2 -> Int -> Int -> Int -> a6 -> Op Source #

bs_put_integer :: (IsSource a2, IsSource a5) => Label -> a2 -> Int -> Int -> a5 -> Op Source #

bs_put_binary :: (IsSource a2, IsSource a5) => Label -> a2 -> Int -> Int -> a5 -> Op Source #

bs_put_float :: (IsSource a2, IsSource a5) => Label -> a2 -> Int -> Int -> a5 -> Op Source #

bs_add :: (IsSource a2, IsSource a3, IsRegister a5) => Label -> a2 -> a3 -> Int -> a5 -> Op Source #

bs_init_bits :: (IsSource a2, IsRegister a6) => Label -> a2 -> Int -> Int -> Int -> a6 -> Op Source #

bs_get_utf8 :: IsRegister a5 => Label -> X -> Int -> Int -> a5 -> Op Source #

bs_skip_utf8 :: Label -> X -> Int -> Int -> Op Source #

bs_get_utf16 :: IsRegister a5 => Label -> X -> Int -> Int -> a5 -> Op Source #

bs_get_utf32 :: IsRegister a5 => Label -> X -> Int -> Int -> a5 -> Op Source #

bs_utf8_size :: (IsSource a2, IsRegister a3) => Label -> a2 -> a3 -> Op Source #

bs_put_utf8 :: IsSource a3 => Label -> Int -> a3 -> Op Source #

bs_utf16_size :: (IsSource a2, IsRegister a3) => Label -> a2 -> a3 -> Op Source #

bs_put_utf16 :: IsSource a3 => Label -> Int -> a3 -> Op Source #

bs_put_utf32 :: IsSource a3 => Label -> Int -> a3 -> Op Source #

Floating point arithmetic

fmove :: (IsSourceF a1, IsRegisterF a2) => a1 -> a2 -> Op Source #

fconv :: IsSource a1 => a1 -> F -> Op Source #

fadd :: F -> F -> F -> Op Source #

fsub :: F -> F -> F -> Op Source #

fmul :: F -> F -> F -> Op Source #

fdiv :: F -> F -> F -> Op Source #

fnegate :: F -> F -> Op Source #

Try, catch, raise

try :: Y -> Label -> Op Source #

raise :: (IsSource a1, IsSource a2) => a1 -> a2 -> Op Source #

catch :: Y -> Label -> Op Source #

Old-style catch.

Maps

put_map_assoc :: (IsSource a2, IsRegister a3) => Label -> a2 -> a3 -> [(Source, Source)] -> Op Source #

put_map_exact :: (IsSource a2, IsRegister a3) => Label -> a2 -> a3 -> [(Source, Source)] -> Op Source #

has_map_fields :: IsSource a2 => Label -> a2 -> [Source] -> Op Source #

get_map_elements Source #

Arguments

:: IsSource a2 
=> Label

jump here on failure

-> a2

where the map is

-> [(Register, Register)]

list of (what key to use, where to put value)

-> Op 

Get multiple values out of a map