Home | History | Annotate | Download | only in llvm

Lines Matching refs:See

6  * License. See LICENSE.TXT for details.
20 (** The top-level container for all LLVM global data. See the
25 objects. See the [llvm::Module] class. *)
28 (** Each value in the LLVM IR has a type, an instance of [lltype]. See the
33 constants, and much more are all [llvalues]. See the [llvm::Value] class.
37 (** Used to store users and usees of values. See the [llvm::Use] class. *)
40 (** A basic block in LLVM IR. See the [llvm::BasicBlock] class. *)
43 (** Used to generate instructions in the LLVM IR. See the [llvm::LLVMBuilder]
48 See the [llvm::MemoryBuffer] class. *)
54 (** The kind of an [lltype], the result of [classify_type ty]. See the
77 {!set_linkage}. See [llvm::GlobalValue::LinkageTypes]. *)
100 {!set_visibility}. See [llvm::GlobalValue::VisibilityTypes]. *)
109 {!set_dll_storage_class}. See [llvm::GlobalValue::DLLStorageClassTypes]. *)
134 See [llvm::Attribute::AttrKind]. *)
166 See the [llvm::ICmpInst::Predicate] enumeration. *)
184 See the [llvm::FCmpInst::Predicate] enumeration. *)
277 See [llvm::LandingPadInst::ClauseType]. *)
286 See [llvm::GlobalVariable::ThreadLocalMode]. *)
297 [fence] instruction. See [llvm::AtomicOrdering]. *)
311 See [llvm::AtomicRMWInst::BinOp]. *)
328 See the various [LLVMIsA*] functions. *)
398 See the function [llvm::cl::ParseCommandLineOptions()]. *)
404 LLVM. See the constructor [llvm::LLVMContext]. *)
407 (** [destroy_context ()] destroys a context. See the destructor
411 (** See the function [llvm::getGlobalContext]. *)
415 name [name] in the context [context]. See the function
424 to call {!dispose_module} to free memory. See the constructor
430 referencing them will invoke undefined behavior. See the destructor
435 [i686-apple-darwin8]. See the method [llvm::Module::getTargetTriple]. *)
439 the string [triple]. See the method [llvm::Module::setTargetTriple]. *)
443 like [e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-...-a0:0:64-f80:128:128]. See the
448 to the string [s]. See the method [llvm::Module::setDataLayout]. *)
452 error. See the method [llvm::Module::dump]. *)
456 to file [f]. See the method [llvm::Module::print]. *)
460 as a string. See the method [llvm::Module::print]. *)
463 (** [set_module_inline_asm m asm] sets the inline assembler for the module. See
468 See the method [llvm::Module::getContext] *)
475 See the method [llvm::Type::getTypeID]. *)
484 See the method [llvm::Type::getContext]. *)
488 error. See the method [llvm::Type::dump]. *)
497 (** [i1_type c] returns an integer type of bitwidth 1 in the context [c]. See
501 (** [i8_type c] returns an integer type of bitwidth 8 in the context [c]. See
505 (** [i16_type c] returns an integer type of bitwidth 16 in the context [c]. See
509 (** [i32_type c] returns an integer type of bitwidth 32 in the context [c]. See
513 (** [i64_type c] returns an integer type of bitwidth 64 in the context [c]. See
518 [c]. See the method [llvm::IntegerType::get]. *)
522 in the context [c]. See the method [llvm::IntegerType::getBitWidth]. *)
529 [c]. See [llvm::Type::FloatTy]. *)
533 [c]. See [llvm::Type::DoubleTy]. *)
537 [c]. See [llvm::Type::X86_FP80Ty]. *)
541 [c]. See [llvm::Type::FP128Ty]. *)
545 context [c]. See [llvm::Type::PPC_FP128Ty]. *)
553 See the method [llvm::FunctionType::get]. *)
559 See the method [llvm::FunctionType::get]. *)
563 otherwise. See the method [llvm::FunctionType::isVarArg]. *)
567 See the method [llvm::FunctionType::getReturnType]. *)
571 See the method [llvm::FunctionType::getParamType]. *)
578 [context] containing in the types in the array [tys]. See the method
583 context [context] containing in the types in the array [tys]. See the method
593 See the method [llvm::StructType::get]. *)
598 See the moethd [llvm::StructType::setBody]. *)
602 [sty]. See the method [llvm::StructType::getElementType]. *)
606 [false] otherwise. See the method [llvm::StructType::isPacked]. *)
610 [false] otherwise. See the method [llvm::StructType::isOpaque]. *)
617 [ty]. See the method [llvm::ArrayType::get]. *)
622 See the method [llvm::PointerType::getUnqual]. *)
627 See the method [llvm::PointerType::get]. *)
631 primitive type [ty]. See the method [llvm::ArrayType::get]. *)
635 type [ty]. See the method [llvm::SequentialType::get]. *)
639 See the method [llvm::ArrayType::getNumElements]. *)
643 [pty]. See the method [llvm::PointerType::getAddressSpace]. *)
647 See the method [llvm::VectorType::getNumElements]. *)
654 value in the context [c]. See [llvm::Type::VoidTy]. *)
657 (** [label_type c] creates a type of a basic block in the context [c]. See
662 context [c]. See [llvm::Type::X86_MMXTy]. *)
667 See the method [llvm::Module::getTypeByName] *)
674 See the method [llvm::Value::getType]. *)
683 See the method [llvm::Value::getName]. *)
686 (** [set_value_name n v] sets the name of the value [v] to [n]. See the method
691 error. See the method [llvm::Value::dump]. *)
698 with the value [new]. See the method [llvm::Value::replaceAllUsesWith]. *)
706 See the method [llvm::Value::use_begin]. *)
710 See the method [llvm::use_value_iterator::operator++]. *)
714 See the method [llvm::Use::getUser]. *)
718 See the method [llvm::Use::getUsedValue]. *)
736 (** [operand v i] returns the operand at index [i] for the value [v]. See the
740 (** [operand_use v i] returns the use of the operand at index [i] for the value [v]. See the
747 See the method [llvm::User::setOperand]. *)
751 See the method [llvm::User::getNumOperands]. *)
762 See the method [llvm::Constant::getNullValue]. *)
766 [ty]. See the method [llvm::Constant::getAllOnesValue]. *)
770 [ty]. See the method [llvm::ConstantPointerNull::get]. *)
774 See the method [llvm::UndefValue::get]. *)
778 See the method [llvm::Constant::isNullValue]. *)
793 metadata attached to it. See the function
798 kind [kind] in the instruction [i] See the function
803 instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
807 instruction [i]. See the function [llvm::Instruction::setMetadata]. *)
814 See the method [llvm::MDNode::get]. *)
819 See the method [llvm::MDNode::get]. *)
826 See the method [llvm::MDString::getString] *)
831 See the method [llvm::NamedMDNode::getOperand]. *)
837 See the methods [llvm::Module::getNamedMetadata()] and
845 See the method [llvm::ConstantInt::get]. *)
849 [i]. See the method [llvm::ConstantInt::get]. *)
854 See the method [llvm::ConstantInt::getSExtValue].*)
858 value [s], with the radix [r]. See the method [llvm::ConstantInt::get]. *)
862 value [n]. See the method [llvm::ConstantFP::get]. *)
867 See the method [llvm::ConstantFP::getDoubleValue].*)
871 [ty] and value [n]. See the method [llvm::ConstantFP::get]. *)
878 null-terminated (but see {!const_stringz}). This value can in turn be used
879 as the initializer for a global variable. See the method
886 See the method [llvm::ConstantArray::get]. *)
892 See the method [llvm::ConstantArray::get]. *)
898 for a global variable. See the method [llvm::ConstantStruct::getAnon]. *)
904 for a global variable. See the method [llvm::ConstantStruct::get]. *)
910 the initializer for a global variable. See the method
916 values [elts]. See the method [llvm::ConstantVector::get]. *)
924 See the method ConstantDataSequential::getElementAsConstant. *)
933 more readable. See the method [llvm::ConstantExpr::getAlignOf]. *)
939 See the method [llvm::ConstantExpr::getSizeOf]. *)
943 See the method [llvm::ConstantExpr::getNeg]. *)
948 See the method [llvm::ConstantExpr::getNSWNeg]. *)
953 See the method [llvm::ConstantExpr::getNUWNeg]. *)
957 See the method [llvm::ConstantExpr::getFNeg]. *)
961 See the method [llvm::ConstantExpr::getNot]. *)
965 See the method [llvm::ConstantExpr::getAdd]. *)
970 See the method [llvm::ConstantExpr::getNSWAdd]. *)
975 See the method [llvm::ConstantExpr::getNSWAdd]. *)
979 See the method [llvm::ConstantExpr::getFAdd]. *)
983 constants. See the method [llvm::ConstantExpr::getSub]. *)
988 See the method [llvm::ConstantExpr::getNSWSub]. *)
993 See the method [llvm::ConstantExpr::getNSWSub]. *)
997 constant floats. See the method [llvm::ConstantExpr::getFSub]. *)
1001 See the method [llvm::ConstantExpr::getMul]. *)
1006 See the method [llvm::ConstantExpr::getNSWMul]. *)
1011 See the method [llvm::ConstantExpr::getNSWMul]. *)
1015 See the method [llvm::ConstantExpr::getFMul]. *)
1020 See the method [llvm::ConstantExpr::getUDiv]. *)
1025 See the method [llvm::ConstantExpr::getSDiv]. *)
1030 or overflows. See the method [llvm::ConstantExpr::getExactSDiv]. *)
1035 See the method [llvm::ConstantExpr::getFDiv]. *)
1040 See the method [llvm::ConstantExpr::getURem]. *)
1045 See the method [llvm::ConstantExpr::getSRem]. *)
1050 See the method [llvm::ConstantExpr::getFRem]. *)
1055 See the method [llvm::ConstantExpr::getAnd]. *)
1060 See the method [llvm::ConstantExpr::getOr]. *)
1065 See the method [llvm::ConstantExpr::getXor]. *)
1070 See the method [llvm::ConstantExpr::getICmp]. *)
1075 See the method [llvm::ConstantExpr::getFCmp]. *)
1080 See the method [llvm::ConstantExpr::getShl]. *)
1085 See the method [llvm::ConstantExpr::getLShr]. *)
1090 See the method [llvm::ConstantExpr::getAShr]. *)
1095 See the method [llvm::ConstantExpr::getGetElementPtr]. *)
1100 See the method [llvm::ConstantExpr::getInBoundsGetElementPtr]. *)
1105 See the method [llvm::ConstantExpr::getTrunc]. *)
1110 See the method [llvm::ConstantExpr::getSExt]. *)
1115 See the method [llvm::ConstantExpr::getZExt]. *)
1120 See the method [llvm::ConstantExpr::getFPTrunc]. *)
1125 See the method [llvm::ConstantExpr::getFPExt]. *)
1130 See the method [llvm::ConstantExpr::getUIToFP]. *)
1135 See the method [llvm::ConstantExpr::getSIToFP]. *)
1140 See the method [llvm::ConstantExpr::getFPToUI]. *)
1145 See the method [llvm::ConstantExpr::getFPToSI]. *)
1150 See the method [llvm::ConstantExpr::getPtrToInt]. *)
1155 See the method [llvm::ConstantExpr::getIntToPtr]. *)
1160 See the method [llvm::ConstantExpr::getBitCast]. *)
1165 See the method [llvm::ConstantExpr::getZExtOrBitCast]. *)
1170 See the method [llvm::ConstantExpr::getSExtOrBitCast]. *)
1175 See the method [llvm::ConstantExpr::getTruncOrBitCast]. *)
1180 See the method [llvm::ConstantExpr::getPointerCast]. *)
1187 See the method [llvm::ConstantExpr::getIntegerCast]. *)
1192 See the method [llvm::ConstantExpr::getFPCast]. *)
1197 See the method [llvm::ConstantExpr::getSelect]. *)
1203 See the method [llvm::ConstantExpr::getExtractElement]. *)
1211 See the method [llvm::ConstantExpr::getInsertElement]. *)
1215 See the LLVM Language Reference for details on the [shufflevector]
1217 See the method [llvm::ConstantExpr::getShuffleVector]. *)
1222 aggregate. See the method [llvm::ConstantExpr::getExtractValue]. *)
1227 of the aggregate. See the method [llvm::ConstantExpr::getInsertValue]. *)
1231 See the method [llvm::InlineAsm::get]. *)
1235 function [f]. See the method [llvm::BasicBlock::get]. *)
1242 See the method [llvm::GlobalValue::getParent]. *)
1247 See the method [llvm::GlobalValue::isDeclaration]. *)
1251 See the method [llvm::GlobalValue::getLinkage]. *)
1255 See the method [llvm::GlobalValue::setLinkage]. *)
1259 See the method [llvm::GlobalValue::getSection]. *)
1263 See the method [llvm::GlobalValue::setSection]. *)
1267 See the method [llvm::GlobalValue::getVisibility]. *)
1271 [v]. See the method [llvm::GlobalValue::setVisibility]. *)
1275 See the method [llvm::GlobalValue::getDLLStorageClass]. *)
1279 [v]. See the method [llvm::GlobalValue::setDLLStorageClass]. *)
1283 See the method [llvm::GlobalValue::getAlignment]. *)
1287 [n] bytes. See the method [llvm::GlobalValue::setAlignment]. *)
1309 See the constructor of [llvm::GlobalVariable]. *)
1315 See the constructor of [llvm::GlobalVariable]. *)
1320 See the [llvm::GlobalVariable] constructor. *)
1324 See the method [llvm::GlobalVariable::eraseFromParent]. *)
1330 See the method [llvm::Module::global_begin]. *)
1335 See the method [llvm::Module::global_iterator::operator++]. *)
1349 See the method [llvm::Module::global_end]. *)
1354 See the method [llvm::Module::global_iterator::operator--]. *)
1367 See the method [llvm::GlobalVariable::isConstant]. *)
1372 See the method [llvm::GlobalVariable::setConstant]. *)
1376 [gv]. See the method [llvm::GlobalVariable::getInitializer]. *)
1381 See the method [llvm::GlobalVariable::setInitializer]. *)
1386 See the method [llvm::GlobalVariable::setInitializer]. *)
1391 See the method [llvm::GlobalVariable::isThreadLocal]. *)
1396 See the method [llvm::GlobalVariable::setThreadLocal]. *)
1401 See the method [llvm::GlobalVariable::getThreadLocalMode]. *)
1406 See the method [llvm::GlobalVariable::setThreadLocalMode]. *)
1411 See the method [llvm::GlobalVariable::isExternallyInitialized]. *)
1416 See the method [llvm::GlobalVariable::setExternallyInitialized]. *)
1424 See the constructor for [llvm::GlobalAlias]. *)
1439 See the constructor of [llvm::GlobalVariable]. *)
1444 See the method [llvm::Module] constructor. *)
1448 See the method [llvm::Function::eraseFromParent]. *)
1454 See the method [llvm::Module::begin]. *)
1459 See the method [llvm::Module::iterator::operator++]. *)
1473 See the method [llvm::Module::end]. *)
1477 See the method [llvm::Module::iterator::operator--]. *)
1489 See the method [llvm::Function::isIntrinsic]. *)
1493 See the method [llvm::Function::getCallingConv]. *)
1498 See the method [llvm::Function::setCallingConv]. *)
1503 See the method [llvm::Function::getGC]. *)
1507 [gc]. See the method [llvm::Function::setGC]. *)
1519 See the method [llvm::Function::getAttributes] *)
1530 See the method [llvm::Function::getArgumentList]. *)
1534 See the method [llvm::Function::getArgumentList]. *)
1538 See the methods [llvm::Function::getAttributes] and
1543 See the method [llvm::Argument::getParent]. *)
1549 See the method [llvm::Function::arg_begin]. *)
1554 See the method [llvm::Function::arg_iterator::operator++]. *)
1568 See the method [llvm::Function::arg_end]. *)
1572 See the method [llvm::Function::arg_iterator::operator--]. *)
1596 See the method [llvm::Function::getBasicBlockList]. *)
1600 See the method [llvm::Function::getEntryBlock]. *)
1604 See the method [llvm::BasicBlock::eraseFromParent]. *)
1608 See the method [llvm::BasicBlock::removeFromParent]. *)
1612 See the method [llvm::BasicBlock::moveBefore]. *)
1616 See the method [llvm::BasicBlock::moveAfter]. *)
1621 See the constructor of [llvm::BasicBlock]. *)
1626 See the constructor of [llvm::BasicBlock]. *)
1630 See the method [llvm::BasicBlock::getParent]. *)
1636 See the method [llvm::Function::begin]. *)
1641 See the method [llvm::Function::iterator::operator++]. *)
1655 See the method [llvm::Function::end]. *)
1659 See the method [llvm::Function::iterator::operator--]. *)
1688 See the method [llvm::Instruction::getParent]. *)
1692 * See the method [llvm::Instruction::eraseFromParent]. *)
1698 See the method [llvm::BasicBlock::begin]. *)
1702 See the method [llvm::BasicBlock::iterator::operator++]. *)
1716 See the method [llvm::BasicBlock::end]. *)
1720 See the method [llvm::BasicBlock::iterator::operator--]. *)
1741 See the method [llvm::Instruction::clone]. *)
1749 {!CallConv}. See the method [llvm::CallInst::getCallingConv] and
1756 See the method [llvm::CallInst::setCallingConv]
1775 See the method [llvm::CallInst::isTailCall]. *)
1780 See the method [llvm::CallInst::setTailCall]. *)
1788 See the methods [llvm::LoadInst::isVolatile] and
1794 See the methods [llvm::LoadInst::setVolatile] and
1804 See the method [llvm::TerminatorInst::getSuccessor]. *)
1809 See the method [llvm::TerminatorInst::setSuccessor]. *)
1813 See the method [llvm::TerminatorInst::getNumSuccessors]. *)
1828 See the method [llvm::BranchInst::isConditional]. *)
1832 See the method [llvm::BranchInst::getCondition]. *)
1836 See the method [llvm::BranchInst::setCondition]. *)
1848 with branches from [bb]. See the method [llvm::PHINode::addIncoming]. *)
1852 See the method [llvm::PHINode::getIncomingValue]. *)
1861 is set with {!position_before} or {!position_at_end}. See the constructor
1866 See the constructor for [llvm::LLVMBuilder]. *)
1870 instruction [isn]. See the constructor for [llvm::LLVMBuilder]. *)
1874 the basic block [bb]. See the constructor for [llvm::LLVMBuilder]. *)
1879 See the constructor for [llvm::LLVMBuilder]. *)
1883 instruction [isn]. See the method [llvm::LLVMBuilder::SetInsertPoint]. *)
1887 basic block [bb]. See the method [llvm::LLVMBuilder::SetInsertPoint]. *)
1893 See the method [llvm::LLVMBuilder::GetInsertBlock]. *)
1898 See the method [llvm::LLVMBuilder::Insert]. *)
1906 See the method [llvm::IRBuilder::SetDebugLocation]. *)
1915 See the method [llvm::IRBuilder::GetDebugLocation]. *)
1920 See the method [llvm::IRBuilder::SetInstDebugLocation]. *)
1929 See the method [llvm::LLVMBuilder::CreateRetVoid]. *)
1935 See the method [llvm::LLVMBuilder::CreateRet]. *)
1941 See the method [llvm::LLVMBuilder::CreateAggregateRet]. *)
1947 See the method [llvm::LLVMBuilder::CreateBr]. *)
1953 See the method [llvm::LLVMBuilder::CreateCondBr]. *)
1961 See the method [llvm::LLVMBuilder::CreateSwitch]. *)
1966 See the method [llvm::CallInst::CreateMalloc]. *)
1971 See the method [llvm::CallInst::CreateArrayMalloc]. *)
1976 See the method [llvm::LLVMBuilder::CreateFree]. *)
1981 See the method [llvm::SwitchInst::addCase]. **)
1986 See the method [llvm:;SwitchInst::getDefaultDest]. **)
1993 See the method [llvm::LLVMBuilder::CreateIndirectBr]. *)
1998 See the method [llvm::IndirectBrInst::addDestination]. **)
2004 See the method [llvm::LLVMBuilder::CreateInvoke]. *)
2011 See the method [llvm::LLVMBuilder::CreateLandingPad]. *)
2016 See the method [llvm::LandingPadInst::setCleanup]. *)
2020 See the method [llvm::LandingPadInst::addClause]. *)
2025 See the method [llvm::LLVMBuilder::CreateResume] *)
2031 See the method [llvm::LLVMBuilder::CreateUnwind]. *)
2040 See the method [llvm::LLVMBuilder::CreateAdd]. *)
2046 See the method [llvm::LLVMBuilder::CreateNSWAdd]. *)
2052 See the method [llvm::LLVMBuilder::CreateNUWAdd]. *)
2058 See the method [llvm::LLVMBuilder::CreateFAdd]. *)
2064 See the method [llvm::LLVMBuilder::CreateSub]. *)
2070 See the method [llvm::LLVMBuilder::CreateNSWSub]. *)
2076 See the method [llvm::LLVMBuilder::CreateNUWSub]. *)
2082 See the method [llvm::LLVMBuilder::CreateFSub]. *)
2088 See the method [llvm::LLVMBuilder::CreateMul]. *)
2094 See the method [llvm::LLVMBuilder::CreateNSWMul]. *)
2100 See the method [llvm::LLVMBuilder::CreateNUWMul]. *)
2106 See the method [llvm::LLVMBuilder::CreateFMul]. *)
2112 See the method [llvm::LLVMBuilder::CreateUDiv]. *)
2118 See the method [llvm::LLVMBuilder::CreateSDiv]. *)
2124 See the method [llvm::LLVMBuilder::CreateExactSDiv]. *)
2130 See the method [llvm::LLVMBuilder::CreateFDiv]. *)
2136 See the method [llvm::LLVMBuilder::CreateURem]. *)
2142 See the method [llvm::LLVMBuilder::CreateSRem]. *)
2148 See the method [llvm::LLVMBuilder::CreateFRem]. *)
2154 See the method [llvm::LLVMBuilder::CreateShl]. *)
2160 See the method [llvm::LLVMBuilder::CreateLShr]. *)
2166 See the method [llvm::LLVMBuilder::CreateAShr]. *)
2172 See the method [llvm::LLVMBuilder::CreateAnd]. *)
2178 See the method [llvm::LLVMBuilder::CreateOr]. *)
2184 See the method [llvm::LLVMBuilder::CreateXor]. *)
2191 See the method [llvm::LLVMBuilder::CreateNeg]. *)
2198 See the method [llvm::LLVMBuilder::CreateNeg]. *)
2205 See the method [llvm::LLVMBuilder::CreateNeg]. *)
2212 See the method [llvm::LLVMBuilder::CreateFNeg]. *)
2219 See the method [llvm::LLVMBuilder::CreateXor]. *)
2228 See the method [llvm::LLVMBuilder::CreateAlloca]. *)
2234 See the method [llvm::LLVMBuilder::CreateAlloca]. *)
2241 See the method [llvm::LLVMBuilder::CreateLoad]. *)
2247 See the method [llvm::LLVMBuilder::CreateStore]. *)
2254 See the method [llvm::IRBuilder::CreateAtomicRMW]. *)
2261 See the method [llvm::LLVMBuilder::CreateGetElementPtr]. *)
2267 See the method [llvm::LLVMBuilder::CreateInBoundsGetElementPtr]. *)
2274 See the method [llvm::LLVMBuilder::CreateStructGetElementPtr]. *)
2280 See the method [llvm::LLVMBuilder::CreateGlobalString]. *)
2286 See the method [llvm::LLVMBuilder::CreateGlobalStringPtr]. *)
2295 See the method [llvm::LLVMBuilder::CreateTrunc]. *)
2301 See the method [llvm::LLVMBuilder::CreateZExt]. *)
2307 See the method [llvm::LLVMBuilder::CreateSExt]. *)
2313 See the method [llvm::LLVMBuilder::CreateFPToUI]. *)
2319 See the method [llvm::LLVMBuilder::CreateFPToSI]. *)
2325 See the method [llvm::LLVMBuilder::CreateUIToFP]. *)
2331 See the method [llvm::LLVMBuilder::CreateSIToFP]. *)
2337 See the method [llvm::LLVMBuilder::CreateFPTrunc]. *)
2343 See the method [llvm::LLVMBuilder::CreateFPExt]. *)
2349 See the method [llvm::LLVMBuilder::CreatePtrToInt]. *)
2355 See the method [llvm::LLVMBuilder::CreateIntToPtr]. *)
2361 See the method [llvm::LLVMBuilder::CreateBitCast]. *)
2366 See the method [llvm::LLVMBuilder::CreateZExtOrBitCast]. *)
2372 See the method [llvm::LLVMBuilder::CreateSExtOrBitCast]. *)
2378 See the method [llvm::LLVMBuilder::CreateZExtOrBitCast]. *)
2384 See the method [llvm::LLVMBuilder::CreatePointerCast]. *)
2389 See the method [llvm::LLVMBuilder::CreateIntCast]. *)
2394 See the method [llvm::LLVMBuilder::CreateFPCast]. *)
2403 See the method [llvm::LLVMBuilder::CreateICmp]. *)
2410 See the method [llvm::LLVMBuilder::CreateFCmp]. *)
2421 See the method [llvm::LLVMBuilder::CreatePHI]. *)
2428 See the method [llvm::LLVMBuilder::CreatePHI]. *)
2434 See the method [llvm::LLVMBuilder::CreateCall]. *)
2440 See the method [llvm::LLVMBuilder::CreateSelect]. *)
2447 See the method [llvm::LLVMBuilder::CreateVAArg]. *)
2453 See the method [llvm::LLVMBuilder::CreateExtractElement]. *)
2460 See the method [llvm::LLVMBuilder::CreateInsertElement]. *)
2467 See the method [llvm::LLVMBuilder::CreateShuffleVector]. *)
2474 See the method [llvm::LLVMBuilder::CreateExtractValue]. *)
2481 See the method [llvm::LLVMBuilder::CreateInsertValue]. *)
2488 See the method [llvm::LLVMBuilder::CreateIsNull]. *)
2494 See the method [llvm::LLVMBuilder::CreateIsNotNull]. *)
2500 See the method [llvm::LLVMBuilder::CreatePtrDiff]. *)
2538 See the constructor of [llvm::PassManager]. *)
2545 See the constructor of [llvm::FunctionPassManager]. *)
2551 See the [llvm::PassManager::run] method. *)
2557 See the [llvm::FunctionPassManager::doInitialization] method. *)
2563 See the [llvm::FunctionPassManager::run] method. *)
2569 See the [llvm::FunctionPassManager::doFinalization] method. *)
2574 See the destructor of [llvm::BasePassManager]. *)