• Home
  • History
  • Annotate
  • Raw
  • Download
  • only in /macosx-10.10/llvmCore-3425.0.34/bindings/ocaml/llvm/

Lines Matching +refs:default +refs:value

28 (** Each value in the LLVM IR has a type, an instance of [lltype]. See the
32 (** Any value in the LLVM IR. Functions, instructions, global variables,
72 (** The linkage of a global value, accessed with {!linkage} and
93 (** The linker visibility of a global value, accessed with {!visibility} and
288 through the various value lists maintained by the LLVM IR. *)
294 of [a]. [llrev_pos] is used for reverse iteration through the various value
517 [ty] in the default address space (0).
551 value in the context [c]. See [llvm::Type::VoidTy]. *)
565 (** [type_of v] returns the type of the value [v].
571 (** [value_name v] returns the name of the value [v]. For global values, this is
577 (** [set_value_name n v] sets the name of the value [v] to [n]. See the method
581 (** [dump_value v] prints the .ll representation of the value [v] to standard
585 (** [replace_all_uses_with old new] replaces all uses of the value [old]
586 * with the value [new]. See the method [llvm::Value::replaceAllUsesWith]. *)
593 (** [use_begin v] returns the first position in the use list for the value [v].
610 (** [iter_uses f v] applies function [f] to each of the users of the value [v]
615 [u1,...,uN] are the users of the value [v]. Tail recursive. *)
619 [u1,...,uN] are the users of the value [v]. Not tail recursive. *)
625 (** [operand v i] returns the operand at index [i] for the value [v]. See the
629 (** [set_operand v i o] sets the operand of the value [v] at the index [i] to
630 the value [o].
634 (** [num_operands v] returns the number of operands for the value [v].
640 (** [is_constant v] returns [true] if the value [v] is a constant, [false]
656 (** [undef ty] returns the undefined value of the type [ty].
660 (** [is_null v] returns [true] if the value [v] is the null (zero) value.
664 (** [is_undef v] returns [true] if the value [v] is an undefined value, [false]
712 (** [const_int ty i] returns the integer constant of type [ty] and value [i].
716 (** [const_of_int64 ty i] returns the integer constant of type [ty] and value
720 (** [int64_of_const c] returns the int64 value of the [c] constant integer.
726 * value [s], with the radix [r]. See the method [llvm::ConstantInt::get]. *)
731 value [n]. See the method [llvm::ConstantFP::get]. *)
735 [ty] and value [n]. See the method [llvm::ConstantFP::get]. *)
744 null-terminated (but see {!const_stringz}). This value can in turn be used
751 value can in turn be used as the initializer for a global variable.
757 This value can in turn be used as the initializer for a global variable.
763 in the context [context]. This value can in turn be used as the initializer
769 This value can in turn be used as the initializer
775 values [elts] in the context [context]. This value can in turn be used as
1061 (** [const_select cond t f] returns the constant conditional which returns value
1062 [t] if the boolean constant [cond] is true and the value [f] otherwise.
1068 constant vector [vec]. [i] must be a constant [i32] value unsigned less than
1076 constant [v]. [v] must be a constant value with the type of the vector
1077 elements. [i] must be a constant [i32] value unsigned less than the size
1090 (** [const_extractvalue agg idxs] returns the constant [idxs]th value of
1096 (** [const_insertvalue agg val idxs] inserts the value [val] in the specified
1115 (** [global_parent g] is the enclosing module of the global value [g].
1119 (** [is_declaration g] returns [true] if the global value [g] is a declaration
1124 (** [linkage g] returns the linkage of the global value [g].
1128 (** [set_linkage l g] sets the linkage of the global value [g] to [l].
1132 (** [section g] returns the linker section of the global value [g].
1136 (** [set_section s g] sets the linker section of the global value [g] to [s].
1140 (** [visibility g] returns the linker visibility of the global value [g].
1144 (** [set_visibility v g] sets the linker visibility of the global value [g] to
1149 (** [alignment g] returns the required alignment of the global value [g].
1153 (** [set_alignment n g] sets the required alignment of the global value [g] to
1161 with name [name] in module [m] in the default address space (0). If such a
1177 initializer [init] in module [m] in the default address space (0). If the
1532 (** [value_is_block v] returns [true] if the value [v] is a basic block and
1606 value. *)
1611 return value. *)
1628 (** [add_incoming (v, bb) pn] adds the value [v] to the phi node [pn] for use
1633 (** [incoming pn] returns the list of value-block pairs for phi node [pn].
1773 (** [switch_default_dest sw] returns the default destination of the [switch]
2038 [-1] is the correct "all ones" value for the type of [x].