cleavir bir
1.1.0Block-based Intermediate Representation for compiled Lisp code.
Block-based Intermediate Representation (BIR) is Cleavir's primary intermediate representation. BIR is designed to represent both high-level, implementation-independent properties of Lisp programs, as well as lower-level implementation-defined machine-dependent properties, and to allow the compiler to make the transition from high to low level smoothly and efficiently. Pervasive use of CLOS facilitates extension and customization by clients.
Table of Contents
- Structure of the IR
- Analyses and transformations
- Verifier
- Disassembler
- Examples
- System Information
- Index
Structure of the IR
BIR has several levels of structure. The classes used to describe this structure are mostly defined in structure.lisp
.
At the top level is the module
. A module is a set of functions being compiled together. Functions can directly call or otherwise refer only to other functions in the same module. All other accesses are indirect, e.g. through a global environment via cl:fdefinition
.
The next level down is the function
. A function is the IR representation of a Lisp function being compiled. It has a lambda list, like the Lisp function, and some iblock
s, representing the compiled code.
iblock
s, short for "instruction blocks", are straight-line sequences of instruction
s. Every iblock has zero or more non-terminator instructions, which represent some action that has straightforward control flow, and one final terminator
instruction that indicates what iblock
s control proceeds to after its execution. In other words, an iblock is a basic block.
instruction
s represent actions the machine can carry out. Each kind of action has its own subclass of instruction
. Most instruction classes are defined in instructions.lisp, and clients may define their own instructions as well.
Data
Instructions input and output "data", of the datum
class. A datum represents zero or more values that can exist at runtime. In some cases, these data may not correspond directly to Lisp objects. There are several subclasses of datum
based on properties and role. Most data have strong restrictions on their use in order to facilitate analysis and optimization. ssa
(single static assignment) data are assigned in at most one place, and linear-datum
are used in at most one place, for example.
Linearity
One of the most important properties of data is linearity, in the sense of linear logic. A linear-datum
is one that is only used in one place in the program. This is closely dual to the ssa
, a datum that is defined in only one place. Most BIR data are linear, and this is critical for performant analysis.
To see why, consider the code
(loop for x = ...
do (if (typep x 'single-float)
(print (- (* x 3.9) 7.2))
(return x)))
Here, in (* x 3.9)
, x
is clearly a single float, and so this multiplication may be safely transformed into a fast machine operation. But just as clearly, in (return x)
x
is not a single float, and in (typep x 'single-float)
it could be anything. Therefore, for a variable datum
like x
that can be used in any number of places, the compiler needs to associate type information (as well as any other forward-flow information) with a datum
and a control point, not just a datum
.
For a linear-datum
, however, forward-flow information can be associated directly with the datum
. The implicit meaning of this is that the information is associated to the datum and to the control point at which it is used. In this example, the compiler will construct a linear-datum
(an output
, specifically) for the result of the (* x 3.9)
call. This output
is only used in one place, the call to -
. So Cleavir can tag that output
as having type single-float
without having to worry about control flow.
Linearity is pervasive: almost all BIR instructions only accept linear data. In this example, the BIR would include a special readvar
instruction that takes the (non-linear) variable
datum for x
as input, and outputs a linear datum (an output
) with its value. This output
would then serve as the input to the *
call.
Note that linear data can be used multiple times in any execution of the program - e.g. here, the result datum for the *
call will be read once for each execution of the loop that reaches this point. The important thing is that the datum is used only once in the program text.
Multiple Values
Although a datum
can represent any number of values, BIR's semantics are such that only the primary value is retained after the values are produced, unless the datum
is immediately input into the few instructions that use all values, such as mv-call
. This reflects a usual implementation of multiple values, in which only one set of them is really live at any given time in most circumstances. If multiple multiple values are live simultaneously in the source program, e.g. in cl:multiple-value-prog1
, one set of values will be explicitly saved and restored in the BIR by special instructions. This facilitates code generators being able to straightforwardly map BIR data to registers or memory locations.
Primops
A broad subset of instructions has "function-like" semantics, in that they have one or more inputs that are evaluated normally, and possibly return a result. These "primops" are not actually functions, and can probably be dealt with by the code generator directly (i.e. using some stereotyped sequence of machine instructions rather than an actual function call). In BIR, primops are represented with the primop
instruction, which links to the specific primop-info
of the primop. These are the primop info structures in the Cleavir/Primop/ directory.
Primops will for the most part be produced from calls by transformations, rather than being present in the initial BIR. This is in order to improve modularity: a frontend can produce BIR while being disinterested in the particular nature of the backend, while client transforms on the BIR can cooperate with the client's backend to "lower" the IR to a more efficient but less general form.
Local calls
BIR has a concept of "local" calls. A call is local if it is to another function in the same compilation module. Local calls are more useful to the compiler because it means the caller can "know" about the callee, and vice versa. Marking as many calls as possible as local is important to ensure they can be analyzed effectively.
For example, if a function is called non-locally, it must be prepared to accept any input; but if it's only called locally, it can be compiled to only accept whatever inputs are actually provided to those local calls. If we have (flet ((f (x) (... (car x) ...))) (f (cons ...)))
, f
may safely use inline car
operations without type checking.
Dynamic environments
A dynamic-environment
represents a Lisp dynamic environment, including information about exit points, values with only dynamic extent, and unwind-protect cleanups. Any function
is a dynamic-environment
, and in this capacity represents the dynamic environment the function was called in. Certain instructions are also dynamic environments.
Every dynamic environment except a function has a parent dynamic environment, and this chain of parents will eventually reach the function. Each iblock has a dynamic environment, and all instructions in that iblock conceptually share that dynamic environment. The localization of dynamic environments to iblocks means that a straight-line sequence of iblocks cannot be in general collapsed into a single basic block, because different instructions need different dynamic environments.
One consequence of this is that any jump between iblocks may involve complex operations, as dynamic environments are unbound. This can include unbinding dynamic variables, invalidating exit points, and evaluating cl:unwind-protect
cleanup code. Code generators must be careful to ensure all such "unwinding" operations will be carried out.
A client may or may not represent dynamic environments as concrete objects at runtime. BIR dynamic environments are intended to allow a variety of runtime realizations while maintaining static invariants, such as dynamic environments never being shared between functions.
Nonlocal exits
Dynamic environments are used to represent nonlocal exit points, i.e. cl:block
s and cl:tagbody
s that are jumped to from an inner function. (Local exits are simple jumps.) A point that can be nonlocally exited to is marked by a come-from
instruction.
The come-from
appears in the BIR at the point at which the cl:block
or cl:tagbody
is entered, and represents its dynamic environment. The come-from
has as successors both the "normal" successor, i.e. the body of the cl:block
or the prefix of the cl:tagbody
, and any iblocks that can be exited to, i.e. the result of the cl:block
or the end of the cl:tagbody
.
come-from
instructions are also, fairly uniquely, values. In this capacity they represent the continuation. The continuation does in general need to exist at runtime and be closed over, so that at runtime it is clear what continuation/stack frame is being returned to.
One of the transformation passes, eliminate-come-froms
, will automatically detect and delete any come-from
instructions not used for nonlocal exits. This is important because in practice, most exits are within one function, and do not require any runtime dynamic environment.
The representation of nonlocal exits has gone through several iterations, and may go through more. Common Lisp seems fairly unique among programming languages in having continuations that are only used from fixed points in the program, and this ground is not well-trodden. The idea is to simply indicate the information known statically, such as where exits take place and where they end up, as well as provide enough information to generate code that takes any necessary dynamic actions, such as recording a stack pointer as an exit mark.
Analyses and transformations
BIR has several properties intended to allow analyses and optimizations to be expressed simply and efficiently. Analysis passes may look through the IR and store information elsewhere, or in the IR itself. Optimization passes may transform the IR to new more efficient forms. Cleavir's own optimization passes mostly live in Cleavir/BIR-transformations/.
BIR can be mapped over efficiently with the functions and macros in map.lisp. These operators generally work without consing and in forward flow order, using internally maintained sequential lists.
Verifier
The BIR verifier function verify
, defined in verify.lisp, checks that a given module maintains invariants necessary for BIR to be well-formed. Compiler writers should use verify
after passses if they are unsure that the pass's transformation is valid. Note that the verifier does not prove any kind of "correctness" of the Lisp code the BIR represents, or that the BIR accurately represents any source code; a verification failure merely indicates a bug in Cleavir's BIR handling, or in a client's pass.
verify
returns silently if no problems were encountered. If the BIR is invalid, however, it will print a disassembly of the module and a listings of what conditions it found were violated.
Disassembler
The BIR disassembler prints a textual representation of BIR for use in debugging compilers. The main entry point is cleavir-bir-disassembler:display
. This function can be used on multiple levels of BIR structure, from a module down to an instruction, for when only part of a module needs to be displayed. The disassembler output will look like that in the examples below.
The BIR visualizer system provides an alternate, more visual way to look at BIR.
Examples
This section briefly describes how BIR represents various examples of Lisp code.
Identity function
The identity function (defun identity (x) x)
can be represented as
-------module-------
constants: ()
function IDENTITY (x)
with environment ()
with start iblock IDENTITY-START
iblock IDENTITY-START ():
dynenv = (FUNCTION IDENTITY)
(leti x) -> X
(readvar x) -> x-0
(returni x-0)
The function has no constants, only one function in its module, and only one iblock in that function. The iblock merely binds a variable
datum X, immediately reads from it, and returns the result. The reason for the variable binding is that in BIR, function argument
s are linear SSA data, i.e. may only be assigned once and used once, so in general an argument will need to be bound to an argument to allow Lisp code to work with it. In this case, however, there is only one binding and one read for the variable, so it could be deleted, and the returni
can simply return the argument directly. This optimization can be performed by the "delete temporary variables" transform in BIR-transformations.
Calls, constants
(lambda (x) (foo x) (foo x))
might be represented as
-------module-------
constants: (FOO)
function (LAMBDA (X)) (x)
with environment ()
with start iblock (LAMBDA (X))-START
iblock (LAMBDA (X))-START:
dynenv = (FUNCTION (LAMBDA (X)))
(leti x) -> X
(constant-fdefinition 'foo) -> 0
(readvar x) -> X-0
(call foo x-0) -> 1
(readvar x) -> X-1
(call foo x-1) -> 2
(returni 2)
The function is unknown to the compiler, so it is looked up at runtime using the constant-fdefinition
instruction.
Note that there are two readvar
instructions. This is because the X variable is read more than once, and so can't be represented with a linear datum. A readvar
instruction must exist for each different usage, even here where there is no actual need to perform any kind of new lookup operation at runtime. Similarly, a constant may be referenced any number of times, but there must be one constant-fdefinition
, constant-reference
, or constant-symbol-value
instruction for each usage.
Control flow
Now consider a non-straight-line function,
(lambda (predicate f x)
(loop until (cleavir-primop:funcall predicate x)
do (setq x (cleavir-primop:funcall f x))))
Here cleavir-primop:funcall
is used instead of funcall
to avoid code to resolve function designators.
-------module-------
constants: (NIL)
function (LAMBDA (PREDICATE F X)) (predicate f x)
with environment ()
with start iblock (LAMBDA (PREDICATE F X))-START
iblock (LAMBDA (PREDICATE F X))-START ():
dynenv = (FUNCTION (LAMBDA (PREDICATE F X)))
(leti x) -> X
(jump (tag-next-loop))
iblock TAG-NEXT-LOOP ():
dynenv = (FUNCTION (LAMBDA (PREDICATE F X)))
(readvar x) -> X-1
(call predicate x-1) -> 4
(ifi 4 (if-then if-else))
iblock IF-ELSE ():
dynenv = (FUNCTION (LAMBDA (PREDICATE F X)))
(readvar x) -> X-0
(call f x-0) -> 2
(writevar 2) -> X
(jump (tag-next-loop))
iblock IF-THEN ():
dynenv = (FUNCTION (LAMBDA (PREDICATE F X)))
(constant-reference 'nil) -> 0
(returni 0)
The function now has four iblocks: the beginning and loop pre-header (LAMBDA (PREDICATE F X))-START
, the loop header TAG-NEXT-LOOP
, another in-loop iblock IF-ELSE
in which the function f
is called, and the exit block IF-THEN
. Control starts at (LAMBDA (PREDICATE F X))-START
, and then proceeds unconditionally (using the jump
instruction) to TAG-NEXT-LOOP
. TAG-NEXT-LOOP
calls the predicate, and tests its result with ifi
: if true ifi
jumps to IF-THEN
, and otherwise IF-ELSE
. IF-ELSE
calls f
, stores its result in the variable X
, then jumps back to the top of the loop. IF-THEN
simply returns nil from the function.
ifi
is the main branch instruction in BIR, and is used for almost all conditionals (the exception being multiway branches, which are more arcane). It has similar semantics to cl:if
, jumping to either the "then" or "else" block based on its input being nil
or not. However some conditional-test
instructions have no meaning except for outputting to ifi
, and in this case, the ifi
may be compiled to branch directly on a condition without a boolean value actually existing at runtime. In this case, the ifi
's input is just a boolean value, so this is not done.
Local functions and calls
The Lisp function (lambda (x) (flet ((foo () x)) (values (foo) #'foo)))
could be represented, after a few optimizations, as
-------module-------
constants: ()
function (LAMBDA (X)) (x)
with environment ()
with start iblock (LAMBDA (X))-START
iblock (LAMBDA (X))-START:
dynenv = (FUNCTION (LAMBDA (X)))
(leti x) -> X
(enclose (flet foo)) -> (FLET FOO)-0
(local-call (flet foo)) -> 0
(fixed-to-multiple 0 (FLET FOO)-0) -> 4
(returni 4)
function (FLET FOO) (x)
with environment (x)
with start iblock (FLET FOO)-START
iblock (FLET FOO)-START:
dynenv = (FUNCTION (FLET FOO))
(readvar x) -> x-0
(returni x-0)
The enclose
instruction produces a Lisp closure from a function. The difference, here, is that a function is just code, whereas a closure is a Lisp object that has the code as well as anything it closes over.
The difference is demonstrated by (local-call (flet foo))
. A local call is a call to another function in the same module - here (flet foo)
. The function is called directly, rather than the closure being called. Such a call can be dealt with more directly - for example, a closure may not need to be allocated for the function if it is only ever locally called, analysis can use information about the exact code being called, and the code generator may have unrestrained ability to choose a convenient calling convention.
The variable X
is shared between the two functions in the module, with the anonymous function binding it, and foo
reading from it (and having it in its environment).
Nonlocal exit
(lambda (f x) (block nil (cleavir-primop:funcall f (lambda () (return x)))))
could be
-------module-------
constants: ()
function (LAMBDA (F X)) (f x)
with environment ()
with start iblock (LAMBDA (F X))-START
iblock (LAMBDA (F X))-START:
dynenv = (FUNCTION (LAMBDA (F X)))
(leti x) -> X
(come-from tag (block-nil block-nil-merge))
iblock BLOCK-NIL ():
dynenv = (COME-FROM IN (LAMBDA (F X))-START)
(enclose (lambda ())) -> (LAMBDA ())-0
(call f (lambda ())-0) -> 1
(jump 1 block-nil-merge)
iblock BLOCK-NIL-MERGE (0):
dynenv = (FUNCTION (LAMBDA (F X)))
entrances = ((lambda ())-start)
(returni 0)
function (LAMBDA ()) ()
with environment (tag x)
with start iblock (LAMBDA ())-START
iblock (LAMBDA ())-START:
dynenv = (FUNCTION (LAMBDA ()))
(readvar x) -> x-0
(unwind x-0 tag block-nil-merge) -> 0
The outer function, (lambda (f x))
, binds x
and then uses the come-from
instruction. This instruction indicates a nonlocal entrance point, i.e. a point another function can immediately exit to using return-from
, go
, etc. The outer function then proceeds to BLOCK-NIL
, which creates a closure and calls f
with this closure. If this call returns normally, the result is passed to BLOCK-NIL-MERGE
.
The inner function simply reads the variable x
, and then uses the unwind
instruction. This performs a nonlocal exit. The second input to the unwind
instruction, tag
, represents the nonlocal entrance at the come-from, and may have to exist at runtime as a sort of closure variable representing the target stack frame. unwind
passes its first input, the read variable, to BLOCK-NIL-MERGE
in the outer function.
BLOCK-NIL-MERGE
simply returns its input, whether it's received from the outer function, or a nonlocal exit from the inner function. The input 0
is a phi node that is only used once, but which can be assigned by multiple jump
and unwind
instructions.
System Information
Definition Index
-
CLEAVIR-BIR
Cleavir's Block-based Intermediate Representation for compiled Lisp code.
-
EXTERNAL SPECIAL-VARIABLE *ORIGIN*
No documentation provided. -
EXTERNAL SPECIAL-VARIABLE *POLICY*
No documentation provided. -
EXTERNAL SPECIAL-VARIABLE *TOP-CTYPE*
No documentation provided. -
EXTERNAL CLASS ABSTRACT-CALL
-
EXTERNAL CLASS ABSTRACT-LOCAL-CALL
Abstract instruction representing a local call, i.e. a call to a FUNCTION in this MODULE. The first input is this callee. Importantly, illegal calls, i.e. ones whose arguments are not compatible with the lambda list of the callee, are not classified as local calls. This so that the presumed runtime mechanism for argument count errors can be used. MV-LOCAL-CALLs do not have a known argument count, and therefore could end up being illegal at runtime, but otherwise this also lets us assume local calls are legal.
-
EXTERNAL CLASS ACCESSVAR
Abstract instruction dealing with a variable.
-
EXTERNAL CLASS ARGUMENT
A DATUM representing an argument to a FUNCTION.
-
EXTERNAL CLASS CALL
Instruction representing a normal call, to a function that Cleavir does not know to be in this MODULE (probably because it really isn't). The first input is the CALLEE, and the subsequent inputs are the arguments. Because this is a normal call, only the primary values are to be taken from each input.
-
EXTERNAL CLASS CASE
No documentation provided. -
EXTERNAL CLASS CATCHI
Terminator and dynamic environment representing a dynamic exit point, i.e. CL:CATCH. The one input is the catch tag and there are no outputs. The first of the NEXT IBLOCKs is the normal child continuation, i.e. the body of the cl:catch, and the second IBLOCK is the end of the catch, i.e. the destination of any throws. See THROWI
-
EXTERNAL CLASS COME-FROM
Terminator and dynamic environment representing a possible nonlocal entry, as from cl:block or cl:tagbody. As a VALUE, represents the runtime representation of the continuation. The first of the NEXT IBLOCKs is the normal child continuation, i.e. the body of the cl:block or the prefix of the cl:tagbody, and the subsequent IBLOCKs are the possible destinations for an UNWIND to this COME-FROM. No inputs or outputs. See UNWIND
-
EXTERNAL CLASS CONDITIONAL-TEST
Abstract instruction representing a computation whose value is guaranteed to be used only as the input to an IFI instruction. (Note that non-CONDITIONAL-TESTs are also allowed to output to an IFI instruction.) The reason for this constraint is that these can usually be specially treated by a backend.
-
EXTERNAL CLASS CONSTANT
A datum representing a constant. For linearity purposes, constants cannot be used directly as inputs to most instructions, and must instead go through CONSTANT-REFERENCE or the like first. See CONSTANT-REFERENCE
-
EXTERNAL CLASS CONSTANT-BIND
Terminator and dynamic environment representing the binding of a dynamic variable. Within this dynamic environment, the symbol has this value (unless there is a more recent binding, of course). The first input is the VARIABLE-CELL being bound, and the second input its new value. No outputs.
-
EXTERNAL CLASS CONSTANT-FDEFINITION
Instruction representing the lookup of a global function with a known name. The single input is a FUNCTION-CELL, and the single output is the function looked up. See FUNCTION-CELL
-
EXTERNAL CLASS CONSTANT-REFERENCE
Instruction representing the use of a constant. The single input is a CONSTANT and the single output is its value.
-
EXTERNAL CLASS CONSTANT-SYMBOL-VALUE
Instruction representing the lookup of the value of a symbol with a known name. The single input is a VARIABLE-CELL, and the single output is its value.
-
EXTERNAL CLASS DATUM
Abstract. A representation of zero or more runtime values. In some cases, data may represent non-Lisp objects, such as "unboxed" objects, or low-level objects like pointers.
-
EXTERNAL CLASS DYNAMIC-ENVIRONMENT
Abstract. Something that can serve as a dynamic environment. This is a dynamic environment in the sense of CLHS 3.1.1.2. An equivalent characterization is that it is a property of the continuation. Dynamic environments include dynamic variable bindings and exit points, for example.
-
EXTERNAL CLASS DYNAMIC-LETI
Terminator and dynamic environment representing the initial binding of a variable that has dynamic extent. The variable can only validly be used within this dynamic environment. See LETI
-
EXTERNAL CLASS ENCLOSE
-
EXTERNAL CLASS EQ-TEST
Instruction representing a cl:eq test. The sole output is true if the two inputs are cl:eq, and otherwise false.
-
EXTERNAL CLASS FIXED-TO-MULTIPLE
Instruction representing the aggregation of single values, as by cl:values.
-
EXTERNAL CLASS FIXED-VALUES-SAVE
Specialization of VALUES-SAVE used when the number of values is known. Transformed from VALUES-SAVE by meta evaluation.
-
EXTERNAL CLASS FUNCTION
Cleavir's representation of the code for a Lisp function.
-
EXTERNAL CLASS FUNCTION-CELL
A datum representing a function cell. A function cell is an implementation defined object that is the identity of a function definition, so for example (setf fdefinition) on the name does alter the cell to refer to the new function. This separates the definition from the name, which is useful for e.g. allowing the same name to refer to different functions in different global environments. If an implementation does not have special function cells, it could just use the function name as a cell. Cleavir marks cells as different from other constants so that they may be resolved specially by an implementation's linking loader. See CONSTANT-FDEFINITION
-
EXTERNAL CLASS IBLOCK
A sequence of instructions with no branching. In other words this is a conventional "basic block", except that Cleavir will sometimes keep distinct iblock segments around for various purposes, such as to indicate differnet dynamic environments.
-
EXTERNAL CLASS IFI
Terminator representing a branch. If the sole input is NIL, control is transferred to the second NEXT, and otherwise to the first. This is the canonical way to branch in Cleavir, which optimization passes know how to deal with.
-
EXTERNAL CLASS INSTRUCTION
Abstract. Cleavir's representation of a computation to be done. All instructions have a sequence of input data and a sequence of output data. With a few exceptions, documented in individual instruction classes, all inputs and outputs are linear. See INPUTS See OUTPUTS See SUCCESSOR See IBLOCK See LINEAR-DATUM
-
EXTERNAL CLASS JUMP
Terminator representing an unconditional local control transfer. Inputs are passed to the single NEXT IBLOCK.
-
EXTERNAL CLASS LETI
Instruction representing the initial binding of a variable. See WRITEVAR
-
EXTERNAL CLASS LINEAR-DATUM
Abstract. A datum with only one use (statically). Note that a datum with only one use in a program's source is linear, even if that use can be reached multiple times during execution of the program.
-
EXTERNAL CLASS LOAD-TIME-VALUE
A datum representing a cl:load-time-value form. For linearity purposes, LOAD-TIME-VALUE data cannot be used directly as inputs to instructions except for LOAD-TIME-VALUE-REFERENCE. See LOAD-TIME-VALUE-REFERENCE
-
EXTERNAL CLASS LOAD-TIME-VALUE-REFERENCE
Instruction representing the lookup of a load-time-value. The single input is a LOAD-TIME-VALUE, and the single output is the computed value.
-
EXTERNAL CLASS LOCAL-CALL
A normal local call. The primary values of the second and further inputs are the arguments.
-
EXTERNAL CLASS MODULE
A set of functions which are compiled together (as opposed to "separate compilation") and which can participate in interprocedural optimizations such as inlining. For example, lexically nested functions are always compiled together.
-
EXTERNAL CLASS MV-CALL
Instruction representing a multiple-value call to a function that Cleavir does not know to be in this MODULE (probably because it really isn't). The first input is the CALLEE, and the subsequent inputs are the arguments.
-
EXTERNAL CLASS MV-LOCAL-CALL
A multiple-value local call. The second and further inputs are the arguments.
-
EXTERNAL CLASS NO-INPUT
Mixin. An instruction with no inputs.
-
EXTERNAL CLASS NO-OUTPUT
Mixin. An instruction with no outputs.
-
EXTERNAL CLASS ONE-INPUT
Mixin. An instruction with exactly one input.
-
EXTERNAL CLASS ONE-OUTPUT
Mixin. An instruction with exactly one output.
-
EXTERNAL CLASS OUTPUT
A DATUM output by an instruction. All instructions output only OUTPUTs, except for terminators which output PHIs, and WRITEVAR which outputs a VARIBLE.
-
EXTERNAL CLASS PHI
A DATUM representing an argument to an IBLOCK. Alternatively, it may be characterized as a data merger point, as in conventional SSA form.
-
EXTERNAL CLASS PRIMOP
Instruction with similar semantics to a call, but which is specially handled by the backend rather than becoming a normal function call. Inputs and outputs depend on the particular primop.
-
EXTERNAL CLASS READVAR
Instruction representing reading the value of a VARIABLE. The single input is the VARIABLE to read from, and the single output is the value read.
-
EXTERNAL CLASS RETURNI
Terminator, representing the return of the one input from this FUNCTION.
-
EXTERNAL CLASS SET-CONSTANT-SYMBOL-VALUE
Instruction representing the modification of the value of a symbol with a known name. The first input is a VARIABLE-CELL, and the second is the value the symbol's value will be changed to. No output.
-
EXTERNAL CLASS SSA
Abstract. A datum with only one definition. SSA stands for "static single assignment".
-
EXTERNAL CLASS TERMINATOR
Abstract. An instruction that terminates (is at the end of) an IBLOCK.
-
EXTERNAL CLASS TERMINATOR0
Abstract. A TERMINATOR with no NEXT IBLOCKs. This means that is an end to execution in this function.
-
EXTERNAL CLASS TERMINATOR1
Abstract. A TERMINATOR with exactly one NEXT IBLOCK. After this instruction, control unconditionally transfers to that IBLOCK.
-
EXTERNAL CLASS THEI
Instruction representing a type assertion on the sole input. The output is identical to the output (this makes the linearity property easy to conserve).
-
EXTERNAL CLASS THROWI
Terminator representing a dynamic exit i.e. CL:THROW. The first input is the catch tag, and the second input is the values thrown. See CATCHI
-
EXTERNAL CLASS TRANSFER
Abstract. A datum with exactly one definition and exactly one use. See SSA See LINEAR-DATUM
-
EXTERNAL CLASS TYPEQ-TEST
Instruction representing a type test, as from cl:typep. The sole output is true if the sole input is of the TEST-CTYPE, and otherwise false.
-
EXTERNAL CLASS UNREACHABLE
Terminator. Represents the fact that control never reaches this point. No inputs or outputs.
-
EXTERNAL CLASS UNWIND
Terminator representing a nonlocal control transfer, i.e. a control transfer to another function. Inputs are passed to the destination.
-
EXTERNAL CLASS UNWIND-PROTECT
Terminator and dynamic environment representing unwind protection. Nonlocal exits from within this dynamic environment to any outside dynamic environment are interrupted by the execution of a cleanup function, which is the sole input to this instruction. No outputs.
-
EXTERNAL CLASS VALUE
Abstract. An SSA datum with only one definition - itself. Used for e.g. constants. See SSA
-
EXTERNAL CLASS VALUES-COLLECT
Terminator and dynamic environment representing the collection of many values together. The append values are only valid within this dynamic environment. Used in the representation of cl:multiple-value-call with multiple argument forms. The inputs are the values to collect, and the output is the result of their appendage. See VALUES-SAVE
-
EXTERNAL CLASS VALUES-RESTORE
Instruction representing the restoration of values saved by VALUES-SAVE. The input and output are these values. See VALUES-SAVE
-
EXTERNAL CLASS VALUES-SAVE
Terminator and dynamic environment, representing saving some computed values temporarily while other computations complete. The saved values are only valid within this dynamic environment. Used in the representation of cl:multiple-value-call and cl:multiple-value-prog1. The input and output are the values saved. See VALUES-SAVE See VALUES-COLLECT
-
EXTERNAL CLASS VARIABLE
A DATUM representing a mutable lexical variable. It can be read from and written to any number of times, and across FUNCTIONs, but these writes and reads must be mediated by WRITEVAR and READVAR instructions.
-
EXTERNAL CLASS VARIABLE-CELL
A datum representing a variable cell. A variable cell is an implementation defined object that is the identity of a dynamic variable definition, so for example makunbound followed by (setf symbol-value) on the name does alter the cell to refer to the new value. This separates the definition from the name, which is useful for e.g. allowing the same name to refer to different functions in different global environments. If an implementation does not have special variable cells, it could just use the variable name as a cell. Cleavir marks cells as different from other constants so that they may be resolved specially by an implementation's linking loader. See CONSTANT-SYMBOL-VALUE See SET-CONSTANT-SYMBOL-VALUE See CONSTANT-BIND
-
EXTERNAL CLASS WRITEVAR
Instruction representing writing a value to a VARIABLE. The single input is the value to write, and the single output is the VARIABLE to write to.
-
EXTERNAL CONDITION TYPE-CONFLICT
No documentation provided. -
EXTERNAL CONDITION UNUSED-VARIABLE
No documentation provided. -
EXTERNAL FUNCTION CLOSED-OVER-P
- VARIABLE
Return true iff this variable is shared across multiple FUNCTIONs.
-
EXTERNAL FUNCTION COMPUTE-IBLOCK-FLOW-ORDER
- FUNCTION
Compute the forward flow order for the iblocks of FUNCTION, and clean up any existing unreachable iblocks.
-
EXTERNAL FUNCTION CONSTANT-IN-MODULE
- CONSTANT-VALUE
- MODULE
Find the CONSTANT for the given value in MODULE, allocating a new one in the module if necessary. See CONSTANT
-
EXTERNAL FUNCTION DELETE-IBLOCK
- IBLOCK
Delete an iblock from the program. The iblock must not be reachable. See MAYBE-DELETE-IBLOCK
-
EXTERNAL FUNCTION DELETE-IBLOCK-IF-EMPTY
- IBLOCK
If IBLOCK is empty (i.e. consists entirely of a JUMP instruction and is not nonlocally exited to), forward its predecessors to its successors.
-
EXTERNAL FUNCTION DELETE-INSTRUCTION
- INSTRUCTION
Delete an instruction. It must not be a terminator.
-
EXTERNAL FUNCTION DELETE-PHI
- PHI
No documentation provided. -
EXTERNAL FUNCTION DELETE-THEI
- THEI
Remove a THEI by forwarding its input to its use.
-
EXTERNAL FUNCTION FUNCTION-CELL-IN-MODULE
- FUNCTION-NAME
- MODULE
Find the FUNCTION-CELL for the given name in MODULE, or allocate a new one in the module if necessary. See FUNCTION-CELL
-
EXTERNAL FUNCTION IMMUTABLEP
- VARIABLE
Return true iff this variable has only one definition statically.
-
EXTERNAL FUNCTION INSERT-INSTRUCTION-AFTER
- NEW
- EXISTING
Insert a NEW instruction immediatley after an EXISTING instruction, which must not be a terminator.
-
EXTERNAL FUNCTION INSERT-INSTRUCTION-BEFORE
- NEW
- EXISTING
No documentation provided. -
EXTERNAL FUNCTION LOAD-TIME-VALUE-IN-MODULE
- FORM
- READ-ONLY-P
- MODULE
Find the L-T-V object for the given cl:load-time-value form, allocating a new one in the module if necessary.
-
EXTERNAL FUNCTION MAP-FUNCTIONS
- F
- MODULE
Call F on each function in MODULE. Arbitrary order.
-
EXTERNAL FUNCTION MAP-IBLOCK-INSTRUCTIONS
- F
- IBLOCK
Call F on each instruction in IBLOCK, in forward order.
-
EXTERNAL FUNCTION MAP-IBLOCK-INSTRUCTIONS-BACKWARDS
- F
- IBLOCK
Call F on each instruction in IBLOCK, in backwards order.
-
EXTERNAL FUNCTION MAP-IBLOCKS
- F
- FUNCTION
Call F on each iblock in FUNCTION, in forward flow order.
-
EXTERNAL FUNCTION MAP-LAMBDA-LIST
- FUNCTION
- LAMBDA-LIST
This utility parses BIR lambda lists. FUNCTION takes three arguments: The state of the parse (e.g. &OPTIONAL), the current lambda-list item being parsed, and the index of the item.
-
EXTERNAL FUNCTION MAP-LOCAL-INSTRUCTIONS
- F
- FUNCTION
Call F on all instructions owned by FUNCTION, in forward flow order.
-
EXTERNAL FUNCTION MAYBE-DELETE-IBLOCK
- IBLOCK
If IBLOCK is unreachable, delete it.
-
EXTERNAL FUNCTION MERGE-SUCCESSOR-IF-POSSIBLE
- IBLOCK
Merge IBLOCK to its unique successor if possible. If it is possible, return true, otherwise false.
-
EXTERNAL FUNCTION MOVE-INSTRUCTION-AFTER
- MOVANT
- EXISTING
No documentation provided. -
EXTERNAL FUNCTION MOVE-INSTRUCTION-BEFORE
- MOVANT
- EXISTING
No documentation provided. -
EXTERNAL FUNCTION PARENT
- DYNAMIC-ENVIRONMENT
Return the parent dynamic environment of this dynamic environment. If this dynamic environment is a function, its parent is conceptually variable, and NIL is returned.
-
EXTERNAL FUNCTION PHI-INPUTS
- PHI
Return the set of DATA that can provide values for this PHI.
-
EXTERNAL FUNCTION RECORD-VARIABLE-REF
- VARIABLE
Mark that the program reads from the given variable.
-
EXTERNAL FUNCTION RECORD-VARIABLE-SET
- VARIABLE
Mark that the program writes the given variable.
-
EXTERNAL FUNCTION SPLIT-BLOCK-AFTER
- INST
No documentation provided. -
EXTERNAL FUNCTION TRANSITIVE-USE
- LINEAR-DATUM
The eventual use of a datum after considering its transfer through JUMP instructions. See JUMP
-
EXTERNAL FUNCTION VARIABLE-CELL-IN-MODULE
- VARIABLE-NAME
- MODULE
Find the VARIABLE-CELL for the given name in MODULE, or allocate a new one in the module if necessary. See VARIABLE-CELL
-
EXTERNAL GENERIC-FUNCTION ASSERTED-TYPE
- LINEAR-DATUM
The type of the datum that the code declares. While it would be unsafe to use this for inference, it can be used for example to report statically detectable type errors. See CTYPE
-
EXTERNAL GENERIC-FUNCTION (SETF ASSERTED-TYPE)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION ATTRIBUTES
- OBJECT
Retrieve flow information for OBJECT beyond its type.
-
EXTERNAL GENERIC-FUNCTION (SETF ATTRIBUTES)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION BINDER
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF BINDER)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION CALLEE
- INSTRUCTION
Given an ABSTRACT-CALL, return the function being called. For a local call, this will be the FUNCTION. Otherwise it is a VALUE representing the function.
-
EXTERNAL GENERIC-FUNCTION CLEAN-UP-IBLOCK
- IBLOCK
Clean up links to IBLOCK without removing it from control flow.
-
EXTERNAL GENERIC-FUNCTION CODE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION COME-FROM
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION COME-FROMS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF COME-FROMS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION COMPAREES
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION CONSTANT-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION CONSTANTS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF CONSTANTS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION CTYPE
- LINEAR-DATUM
The type of the datum that we can assume when making inferences. See ASSERTED-TYPE
-
EXTERNAL GENERIC-FUNCTION DATUM
- CONDITION
No documentation provided. -
EXTERNAL GENERIC-FUNCTION DEFINITION
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION DEFINITIONS
- DATUM
Return the set of definitions of a DATUM.
-
EXTERNAL GENERIC-FUNCTION DERIVED-TYPE
- CONDITION
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF DERIVED-TYPE)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION DESTINATION
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION DOCSTRING
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION DYNAMIC-ENVIRONMENT
- IR
Return the DYNAMIC-ENVIRONMENT this BIR object belongs to. See DYNAMIC-ENVIRONMENT
-
EXTERNAL GENERIC-FUNCTION (SETF DYNAMIC-ENVIRONMENT)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION ENCLOSE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF ENCLOSE)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION END
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF END)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION ENTRANCES
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF ENTRANCES)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION ENVIRONMENT
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF ENVIRONMENT)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION EXTENT
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF EXTENT)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION FORM
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION FUNCTION
- IR
Return the FUNCTION this BIR object belongs to. See FUNCTION
-
EXTERNAL GENERIC-FUNCTION (SETF FUNCTION)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION FUNCTION-NAME
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION FUNCTIONS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF FUNCTIONS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION IBLOCK
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF IBLOCK)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION IGNORE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION INFO
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION INPUT
- INSTRUCTION
Shortcut to get the sole input of an instruction.
-
EXTERNAL GENERIC-FUNCTION INPUTS
- INSTRUCTION
Return an instruction's input data as a sequence. Direct modification of the sequence is not permitted. Go through (SETF INPUTS) instead, or higher level operators. See DATUM See REPLACE-USES
-
EXTERNAL GENERIC-FUNCTION (SETF INPUTS)
- NEW-INPUTS
- INSTRUCTION
Set an instruction's input data.
-
EXTERNAL GENERIC-FUNCTION LAMBDA-LIST
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF LAMBDA-LIST)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION LOCAL-CALLS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF LOCAL-CALLS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION MODULE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION NAME
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION NEXT
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF NEXT)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION NVALUES
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION ORIGIN
- BIR
Return the source position of a BIR object. The nature of this source position is up to the producer of the BIR.
-
EXTERNAL GENERIC-FUNCTION ORIGINAL-LAMBDA-LIST
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION OTHER-USES
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF OTHER-USES)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION OUTPUT
- INSTRUCTION
Shortcut to get the sole output of an instruction.
-
EXTERNAL GENERIC-FUNCTION OUTPUTS
- INSTRUCTION
Return an instruction's output data as a sequence. Direct modification of the sequence is not permitted. In almost all cases, the list will have zero or one outputs.
-
EXTERNAL GENERIC-FUNCTION (SETF OUTPUTS)
- NEW-OUTPUTS
- INSTRUCTION
set an instruction's output data.
-
EXTERNAL GENERIC-FUNCTION POLICY
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION PREDECESSOR
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF PREDECESSOR)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION PREDECESSORS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF PREDECESSORS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION READ-ONLY-P
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION READERS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF READERS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION REPLACE-TERMINATOR
- NEW
- OLD
No documentation provided. -
EXTERNAL GENERIC-FUNCTION REPLACE-USES
- NEW
- OLD
No documentation provided. -
EXTERNAL GENERIC-FUNCTION RETURNI
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF RETURNI)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION SCOPE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF SCOPE)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION START
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF START)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION STARTEDP
- IR
Return true iff the IR has begun being generated, i.e. has any instructions in it.
-
EXTERNAL GENERIC-FUNCTION SUCCESSOR
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF SUCCESSOR)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION TERMINATEDP
- IR
Return true iff the IR has a terminator.
-
EXTERNAL GENERIC-FUNCTION TEST-CTYPE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION TYPE-CHECK-FUNCTION
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF TYPE-CHECK-FUNCTION)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION UNUSED-P
- DATUM
Return true iff the datum is unused.
-
EXTERNAL GENERIC-FUNCTION UNWINDP
- INSTRUCTION
No documentation provided. -
EXTERNAL GENERIC-FUNCTION UNWINDS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF UNWINDS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION USE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION USE-STATUS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION VARIABLE
- CONDITION
No documentation provided. -
EXTERNAL GENERIC-FUNCTION VARIABLE-NAME
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION VARIABLES
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF VARIABLES)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION VERIFY
- BIR
Verify the syntactic correctness of the given BIR object (generally a module). If there are problems, a VERIFICATION-FAILED is signaled. If the verification process ran into an unexpected error, VERIFICATION-ERROR is signaled. If there are no problems, returns normally.
-
EXTERNAL GENERIC-FUNCTION WRITERS
- OBJECT
No documentation provided. -
EXTERNAL GENERIC-FUNCTION (SETF WRITERS)
- NEW-VALUE
- OBJECT
No documentation provided. -
EXTERNAL MACRO DO-FUNCTIONS
- FUNCTION
- MODULE
- &BODY
- BODY
Execute the BODY with FUNCTION bound to each function in MODULE. Arbitrary order.
-
EXTERNAL MACRO DO-IBLOCK-INSTRUCTIONS
- INSTRUCTION
- IBLOCK
- &OPTIONAL
- DIRECTION
- &BODY
- BODY
Execute the BODY with INSTRUCTION bound to each instruction in IBLOCK. DIRECTION may be :FORWARD or :BACKWARD.
-
EXTERNAL MACRO DO-IBLOCKS
- IBLOCK
- FUNCTION
- &OPTIONAL
- DIRECTION
- &BODY
- BODY
Execute the BODY with IBLOCK bound to each iblock in FUNCTION. DIRECTION may be :FORWARD for forward flow order, or :BACKWARD for reverse flow order.
-
-
CLEAVIR-BIR-DISASSEMBLER
A disassembler for displaying BIR in a human-readable format. This is primarily text-based and aims for brevity and simplicity. For a more visual way to understand BIR, try the BIR visualizer in Visualizer/.
-
EXTERNAL SPECIAL-VARIABLE *SHOW-CTYPE*
When true, the disassembler will display the inferred ctypes of data.
-
EXTERNAL SPECIAL-VARIABLE *SHOW-DYNENV*
When true, the disassembler will display the dynamic environments of iblocks.
-
EXTERNAL FUNCTION DISPLAY-FUNCTION-DISASSEMBLY
- FUNCTION-DISASM
- &KEY
- SHOW-DYNENV
- SHOW-CTYPE
Given the s-expression representation of a BIR function (obtained via DISASSEMBLE), print a textual representation to standard output.
-
EXTERNAL FUNCTION DISPLAY-IBLOCK-DISASSEMBLY
- IBLOCK-DISASM
- &KEY
- SHOW-DYNENV
- SHOW-CTYPE
Given the s-expression representation of a BIR iblock (obtained via DISASSEMBLE), print a textual representation to standard output.
-
EXTERNAL FUNCTION DISPLAY-INSTRUCTION-DISASSEMBLY
- INST-DISASM
- &KEY
- SHOW-CTYPE
Given the s-expression representation of a BIR instruction (obtained via DISASSEMBLE), print a textual representation to standard output.
-
EXTERNAL FUNCTION DISPLAY-MODULE-DISASSEMBLY
- DISASM
- &KEY
- SHOW-DYNENV
- SHOW-CTYPE
Given the s-expression representation of a BIR module (obtained via DISASSEMBLE), print a textual representation to standard output.
-
EXTERNAL GENERIC-FUNCTION DISASSEMBLE
- BIR
Return an s-expression representation of a BIR object.
-
EXTERNAL GENERIC-FUNCTION DISPLAY
- BIR
- &KEY
- SHOW-CTYPE
- SHOW-DYNENV
Print a textual representation of the BIR object to standard output. This is the main entry point to the disassembler.
-
EXTERNAL MACRO WITH-DISASSEMBLY
- &KEY
- OVERRIDE
- &BODY
- BODY
All disassemble operations in the dynamic extent of a WITH-DISASSEMBLY form will share names, etc. You can use this to display only particular regions of interest.
-