Safe Haskell | None |
---|---|
Language | Haskell2010 |
Define types which correspond cleanly with some simple types on the C/C++ side. Encapsulate hsc macro weirdness here, supporting higher-level tricks elsewhere.
Synopsis
- pattern DwOp_LLVM_fragment :: Word64
- pattern DwOp_stack_value :: Word64
- pattern DwOp_swap :: Word64
- pattern DwOp_constu :: Word64
- pattern DwOp_plus_uconst :: Word64
- pattern DwOp_plus :: Word64
- pattern DwOp_minus :: Word64
- pattern DwOp_mul :: Word64
- pattern DwOp_deref :: Word64
- pattern DwOp_xderef :: Word64
- newtype Encoding = Encoding CUInt
- pattern DwAtE_address :: Encoding
- pattern DwAtE_boolean :: Encoding
- newtype DwTag = DwTag Word16
- pattern DwAtE_complex_float :: Encoding
- pattern DwAtE_float :: Encoding
- pattern DwTag_imported_module :: DwTag
- pattern DwAtE_signed :: Encoding
- pattern DwTag_imported_declaration :: DwTag
- newtype DwVirtuality = DwVirtuality Word8
- pattern DwTag_typedef :: DwTag
- pattern DwAtE_signed_char :: Encoding
- pattern DwAtE_unsigned :: Encoding
- pattern DwTag_pointer_type :: DwTag
- pattern DwVirtuality_none :: DwVirtuality
- pattern DwAtE_unsigned_char :: Encoding
- pattern DwTag_ptr_to_member_type :: DwTag
- pattern DwVirtuality_virtual :: DwVirtuality
- newtype LLVMBool = LLVMBool CUInt
- pattern DwTag_reference_type :: DwTag
- pattern DwAtE_imaginary_float :: Encoding
- pattern DwVirtuality_pure_virtual :: DwVirtuality
- pattern DwAtE_packed_decimal :: Encoding
- pattern DwTag_rvalue_reference_type :: DwTag
- pattern DwTag_const_type :: DwTag
- pattern DwAtE_numeric_string :: Encoding
- newtype OwnerTransfered a = OwnerTransfered a
- pattern DwAtE_edited :: Encoding
- pattern DwTag_volatile_type :: DwTag
- pattern DwTag_restrict_type :: DwTag
- pattern DwAtE_signed_fixed :: Encoding
- newtype NothingAsMinusOne h = NothingAsMinusOne CInt
- pattern DwTag_atomic_type :: DwTag
- pattern DwAtE_unsigned_fixed :: Encoding
- newtype NothingAsEmptyString c = NothingAsEmptyString c
- pattern DwTag_member :: DwTag
- pattern DwAtE_decimal_float :: Encoding
- pattern DwAtE_UTF :: Encoding
- pattern DwTag_inheritance :: DwTag
- newtype CPPOpcode = CPPOpcode CUInt
- pattern DwTag_friend :: DwTag
- pattern DwAtE_UCS :: Encoding
- newtype ICmpPredicate = ICmpPredicate CUInt
- pattern DwAtE_ASCII :: Encoding
- pattern DwTag_base_type :: DwTag
- iCmpPredEQ :: ICmpPredicate
- pattern DwTag_unspecified_type :: DwTag
- iCmpPredNE :: ICmpPredicate
- pattern DwTag_template_value_parameter :: DwTag
- iCmpPredUGT :: ICmpPredicate
- pattern DwTag_GNU_template_template_param :: DwTag
- iCmpPredUGE :: ICmpPredicate
- pattern DwTag_GNU_template_parameter_pack :: DwTag
- iCmpPredULT :: ICmpPredicate
- pattern DwTag_array_type :: DwTag
- iCmpPredULE :: ICmpPredicate
- pattern DwTag_enumeration_type :: DwTag
- iCmpPredSGT :: ICmpPredicate
- pattern DwTag_structure_type :: DwTag
- newtype FCmpPredicate = FCmpPredicate CUInt
- iCmpPredSGE :: ICmpPredicate
- fCmpPredFalse :: FCmpPredicate
- pattern DwTag_class_type :: DwTag
- iCmpPredSLT :: ICmpPredicate
- fCmpPredOEQ :: FCmpPredicate
- pattern DwTag_union_type :: DwTag
- iCmpPredSLE :: ICmpPredicate
- fCmpPredOGT :: FCmpPredicate
- fCmpPredOGE :: FCmpPredicate
- fCmpPredOLT :: FCmpPredicate
- fCmpPredOLE :: FCmpPredicate
- fCmpPredONE :: FCmpPredicate
- fCmpPredORD :: FCmpPredicate
- fCmpPredUNO :: FCmpPredicate
- fCmpPredUEQ :: FCmpPredicate
- newtype MDKindID = MDKindID CUInt
- fCmpPredUGT :: FCmpPredicate
- fCmpPredUGE :: FCmpPredicate
- newtype MDSubclassID = MDSubclassID CUInt
- fCmpPredULT :: FCmpPredicate
- mdSubclassIdMDString :: MDSubclassID
- fCmpPredULE :: FCmpPredicate
- mdSubclassIdConstantAsMetadata :: MDSubclassID
- newtype FastMathFlags = FastMathFlags CUInt
- fCmpPredUNE :: FCmpPredicate
- mdSubclassIdLocalAsMetadata :: MDSubclassID
- fcmpPredTrue :: FCmpPredicate
- fastMathFlagsAllowReassoc :: FastMathFlags
- mdSubclassIdDistinctMDOperandPlaceholder :: MDSubclassID
- fastMathFlagsNoNaNs :: FastMathFlags
- newtype MemoryOrdering = MemoryOrdering CUInt
- mdSubclassIdMDTuple :: MDSubclassID
- fastMathFlagsNoInfs :: FastMathFlags
- mdSubclassIdDILocation :: MDSubclassID
- memoryOrderingNotAtomic :: MemoryOrdering
- fastMathFlagsNoSignedZeros :: FastMathFlags
- mdSubclassIdDIExpression :: MDSubclassID
- memoryOrderingUnordered :: MemoryOrdering
- newtype UnnamedAddr = UnnamedAddr CUInt
- fastMathFlagsAllowReciprocal :: FastMathFlags
- memoryOrderingMonotonic :: MemoryOrdering
- mdSubclassIdDIGlobalVariableExpression :: MDSubclassID
- unnamedAddrNone :: UnnamedAddr
- fastMathFlagsAllowContract :: FastMathFlags
- memoryOrderingAcquire :: MemoryOrdering
- mdSubclassIdGenericDINode :: MDSubclassID
- unnamedAddrLocal :: UnnamedAddr
- fastMathFlagsApproxFunc :: FastMathFlags
- newtype SynchronizationScope = SynchronizationScope CUInt
- mdSubclassIdDISubrange :: MDSubclassID
- memoryOrderingRelease :: MemoryOrdering
- fastMathFlagsP :: QuasiQuoter
- unnamedAddrGlobal :: UnnamedAddr
- mdSubclassIdDIEnumerator :: MDSubclassID
- memoryOrderingAcquireRelease :: MemoryOrdering
- synchronizationScopeSingleThread :: SynchronizationScope
- unnamedAddrP :: QuasiQuoter
- mdSubclassIdDIBasicType :: MDSubclassID
- synchronizationScopeSystem :: SynchronizationScope
- memoryOrderingSequentiallyConsistent :: MemoryOrdering
- newtype TailCallKind = TailCallKind CUInt
- memoryOrderingP :: QuasiQuoter
- synchronizationScopeP :: QuasiQuoter
- mdSubclassIdDIDerivedType :: MDSubclassID
- tailCallKindNone :: TailCallKind
- mdSubclassIdDICompositeType :: MDSubclassID
- tailCallKindTail :: TailCallKind
- newtype Linkage = Linkage CUInt
- mdSubclassIdDISubroutineType :: MDSubclassID
- tailCallKindMustTail :: TailCallKind
- linkageExternal :: Linkage
- mdSubclassIdDIFile :: MDSubclassID
- tailCallKindNoTail :: TailCallKind
- linkageAvailableExternally :: Linkage
- mdSubclassIdDICompileUnit :: MDSubclassID
- newtype Visibility = Visibility CUInt
- tailCallKindP :: QuasiQuoter
- linkageLinkOnceAny :: Linkage
- mdSubclassIdDISubprogram :: MDSubclassID
- visibilityDefault :: Visibility
- linkageLinkOnceODR :: Linkage
- mdSubclassIdDILexicalBlock :: MDSubclassID
- visibilityHidden :: Visibility
- newtype COMDATSelectionKind = COMDATSelectionKind CUInt
- linkageWeakAny :: Linkage
- mdSubclassIdDILexicalBlockFile :: MDSubclassID
- visibilityProtected :: Visibility
- linkageWeakODR :: Linkage
- mdSubclassIdDINamespace :: MDSubclassID
- comdatSelectionKindAny :: COMDATSelectionKind
- visibilityP :: QuasiQuoter
- linkageAppending :: Linkage
- mdSubclassIdDIModule :: MDSubclassID
- comdatSelectionKindExactMatch :: COMDATSelectionKind
- newtype DLLStorageClass = DLLStorageClass CUInt
- linkageInternal :: Linkage
- comdatSelectionKindLargest :: COMDATSelectionKind
- mdSubclassIdDITemplateTypeParameter :: MDSubclassID
- dllStorageClassDefault :: DLLStorageClass
- linkagePrivate :: Linkage
- mdSubclassIdDITemplateValueParameter :: MDSubclassID
- comdatSelectionKindNoDuplicates :: COMDATSelectionKind
- dllStorageClassDLLImport :: DLLStorageClass
- newtype CallingConvention = CallingConvention CUInt
- linkageExternalWeak :: Linkage
- mdSubclassIdDIGlobalVariable :: MDSubclassID
- comdatSelectionKindSameSize :: COMDATSelectionKind
- dllStorageClassDLLExport :: DLLStorageClass
- linkageCommon :: Linkage
- comdatSelectionKindP :: QuasiQuoter
- callingConventionC :: CallingConvention
- mdSubclassIdDILocalVariable :: MDSubclassID
- dllStorageClassP :: QuasiQuoter
- linkageP :: QuasiQuoter
- callingConventionFast :: CallingConvention
- mdSubclassIdDIObjCProperty :: MDSubclassID
- newtype ThreadLocalMode = ThreadLocalMode CUInt
- callingConventionCold :: CallingConvention
- mdSubclassIdDIImportedEntity :: MDSubclassID
- threadLocalModeNotThreadLocal :: ThreadLocalMode
- mdSubclassIdDIMacro :: MDSubclassID
- callingConventionGHC :: CallingConvention
- threadLocalModeGeneralDynamicTLSModel :: ThreadLocalMode
- newtype ValueSubclassId = ValueSubclassId CUInt
- mdSubclassIdDIMacroFile :: MDSubclassID
- callingConventionHiPE :: CallingConvention
- threadLocalModeLocalDynamicTLSModel :: ThreadLocalMode
- mdSubclassIdP :: QuasiQuoter
- valueSubclassIdArgument :: ValueSubclassId
- callingConventionWebKit_JS :: CallingConvention
- threadLocalModeInitialExecTLSModel :: ThreadLocalMode
- valueSubclassIdBasicBlock :: ValueSubclassId
- callingConventionAnyReg :: CallingConvention
- newtype DiagnosticKind = DiagnosticKind CUInt
- threadLocalModeLocalExecTLSModel :: ThreadLocalMode
- valueSubclassIdFunction :: ValueSubclassId
- callingConventionPreserveMost :: CallingConvention
- threadLocalModeP :: QuasiQuoter
- diagnosticKindError :: DiagnosticKind
- valueSubclassIdGlobalAlias :: ValueSubclassId
- callingConventionPreserveAll :: CallingConvention
- diagnosticKindWarning :: DiagnosticKind
- newtype AsmDialect = AsmDialect CUInt
- callingConventionSwift :: CallingConvention
- valueSubclassIdGlobalVariable :: ValueSubclassId
- diagnosticKindNote :: DiagnosticKind
- asmDialectATT :: AsmDialect
- valueSubclassIdUndefValue :: ValueSubclassId
- callingConventionCXX_FAST_TLS :: CallingConvention
- diagnosticKindP :: QuasiQuoter
- asmDialectIntel :: AsmDialect
- valueSubclassIdBlockAddress :: ValueSubclassId
- callingConventionX86_StdCall :: CallingConvention
- newtype RMWOperation = RMWOperation CUInt
- asmDialectP :: QuasiQuoter
- valueSubclassIdConstantExpr :: ValueSubclassId
- callingConventionX86_FastCall :: CallingConvention
- rmwOperationXchg :: RMWOperation
- callingConventionARM_APCS :: CallingConvention
- valueSubclassIdConstantAggregateZero :: ValueSubclassId
- rmwOperationAdd :: RMWOperation
- newtype RelocModel = RelocModel CUInt
- callingConventionARM_AAPCS :: CallingConvention
- valueSubclassIdConstantDataArray :: ValueSubclassId
- rmwOperationSub :: RMWOperation
- relocModelDefault :: RelocModel
- callingConventionARM_AAPCS_VFP :: CallingConvention
- valueSubclassIdConstantDataVector :: ValueSubclassId
- rmwOperationAnd :: RMWOperation
- relocModelStatic :: RelocModel
- valueSubclassIdConstantInt :: ValueSubclassId
- callingConventionMSP430_INTR :: CallingConvention
- newtype CodeModel = CodeModel CUInt
- rmwOperationNand :: RMWOperation
- relocModelPIC :: RelocModel
- valueSubclassIdConstantFP :: ValueSubclassId
- callingConventionX86_ThisCall :: CallingConvention
- codeModelDefault :: CodeModel
- rmwOperationOr :: RMWOperation
- relocModelDynamicNoPic :: RelocModel
- valueSubclassIdConstantArray :: ValueSubclassId
- callingConventionPTX_Kernel :: CallingConvention
- rmwOperationXor :: RMWOperation
- codeModelJITDefault :: CodeModel
- newtype CodeGenOptLevel = CodeGenOptLevel CUInt
- relocModelP :: QuasiQuoter
- valueSubclassIdConstantStruct :: ValueSubclassId
- callingConventionPTX_Device :: CallingConvention
- codeModelSmall :: CodeModel
- rmwOperationMax :: RMWOperation
- codeGenOptLevelNone :: CodeGenOptLevel
- callingConventionSPIR_FUNC :: CallingConvention
- valueSubclassIdConstantTokenNone :: ValueSubclassId
- codeModelKernel :: CodeModel
- rmwOperationMin :: RMWOperation
- codeGenOptLevelLess :: CodeGenOptLevel
- valueSubclassIdConstantVector :: ValueSubclassId
- callingConventionSPIR_KERNEL :: CallingConvention
- newtype CodeGenFileType = CodeGenFileType CUInt
- codeModelMedium :: CodeModel
- rmwOperationUMax :: RMWOperation
- codeGenOptLevelDefault :: CodeGenOptLevel
- callingConventionIntel_OCL_BI :: CallingConvention
- valueSubclassIdConstantPointerNull :: ValueSubclassId
- codeModelLarge :: CodeModel
- rmwOperationUMin :: RMWOperation
- codeGenFileTypeAssembly :: CodeGenFileType
- valueSubclassIdInlineAsm :: ValueSubclassId
- codeGenOptLevelAggressive :: CodeGenOptLevel
- callingConventionX86_64_SysV :: CallingConvention
- codeModelP :: QuasiQuoter
- rmwOperationP :: QuasiQuoter
- codeGenFileTypeObject :: CodeGenFileType
- newtype FloatABIType = FloatABIType CUInt
- codeGenOptLevelP :: QuasiQuoter
- callingConventionWin64 :: CallingConvention
- valueSubclassIdInstruction :: ValueSubclassId
- codeGenFileTypeP :: QuasiQuoter
- floatABIDefault :: FloatABIType
- valueSubclassIdP :: QuasiQuoter
- callingConventionX86_VectorCall :: CallingConvention
- floatABISoft :: FloatABIType
- callingConventionHHVM :: CallingConvention
- newtype FPOpFusionMode = FPOpFusionMode CUInt
- floatABIHard :: FloatABIType
- callingConventionHHVM_C :: CallingConvention
- fpOpFusionModeFast :: FPOpFusionMode
- floatABIP :: QuasiQuoter
- callingConventionX86_INTR :: CallingConvention
- fpOpFusionModeStandard :: FPOpFusionMode
- newtype ThreadModel = ThreadModel CUInt
- callingConventionAVR_INTR :: CallingConvention
- fpOpFusionModeStrict :: FPOpFusionMode
- threadModelPOSIX :: ThreadModel
- callingConventionAVR_SIGNAL :: CallingConvention
- fpOpFusionModeP :: QuasiQuoter
- threadModelSingle :: ThreadModel
- callingConventionAVR_BUILTIN :: CallingConvention
- newtype EABI = EABI CUInt
- threadModelP :: QuasiQuoter
- callingConventionAMDGPU_VS :: CallingConvention
- eabiVersionUnknown :: EABI
- callingConventionAMDGPU_GS :: CallingConvention
- eabiVersionDefault :: EABI
- newtype DebuggerKind = DebuggerKind CUInt
- callingConventionAMDGPU_PS :: CallingConvention
- eabiVersionEABI4 :: EABI
- debuggerKindDefault :: DebuggerKind
- callingConventionAMDGPU_CS :: CallingConvention
- eabiVersionEABI5 :: EABI
- debuggerKindGDB :: DebuggerKind
- callingConventionAMDGPU_KERNEL :: CallingConvention
- newtype FPDenormalMode = FPDenormalMode CUInt
- eabiVersionGNU :: EABI
- debuggerKindLLDB :: DebuggerKind
- callingConventionX86_RegCall :: CallingConvention
- eabiVersionP :: QuasiQuoter
- fpDenormalModeIEEE :: FPDenormalMode
- debuggerKindSCE :: DebuggerKind
- callingConventionAMDGPU_HS :: CallingConvention
- fpDenormalModePreserveSign :: FPDenormalMode
- newtype ExceptionHandling = ExceptionHandling CUInt
- debuggerKindP :: QuasiQuoter
- callingConventionMSP430_BUILTIN :: CallingConvention
- fpDenormalModePositiveZero :: FPDenormalMode
- callingConventionP :: QuasiQuoter
- exceptionHandlingNone :: ExceptionHandling
- fpDenormalModeP :: QuasiQuoter
- exceptionHandlingDwarfCFI :: ExceptionHandling
- newtype TargetOptionFlag = TargetOptionFlag CUInt
- exceptionHandlingSjLj :: ExceptionHandling
- targetOptionFlagPrintMachineCode :: TargetOptionFlag
- exceptionHandlingARM :: ExceptionHandling
- targetOptionFlagUnsafeFPMath :: TargetOptionFlag
- newtype MCTargetOptionFlag = MCTargetOptionFlag CUInt
- exceptionHandlingWinEH :: ExceptionHandling
- targetOptionFlagNoInfsFPMath :: TargetOptionFlag
- exceptionHandlingP :: QuasiQuoter
- mcTargetOptionFlagSanitizeAddress :: MCTargetOptionFlag
- targetOptionFlagNoNaNsFPMath :: TargetOptionFlag
- mcTargetOptionFlagMCRelaxAll :: MCTargetOptionFlag
- newtype DebugCompressionType = DebugCompressionType CUInt
- targetOptionFlagNoTrappingFPMath :: TargetOptionFlag
- mcTargetOptionFlagMCNoExecStack :: MCTargetOptionFlag
- debugCompressionTypeNone :: DebugCompressionType
- targetOptionFlagNoSignedZerosFPMath :: TargetOptionFlag
- mcTargetOptionFlagMCFatalWarnings :: MCTargetOptionFlag
- debugCompressionTypeGNU :: DebugCompressionType
- targetOptionFlagHonorSignDependentRoundingFPMathOption :: TargetOptionFlag
- newtype TypeKind = TypeKind CUInt
- mcTargetOptionFlagMCNoWarn :: MCTargetOptionFlag
- debugCompressionTypeZ :: DebugCompressionType
- targetOptionFlagNoZerosInBSS :: TargetOptionFlag
- typeKindVoid :: TypeKind
- mcTargetOptionFlagMCNoDeprecatedWarn :: MCTargetOptionFlag
- debugCompressionTypeP :: QuasiQuoter
- targetOptionFlagGuaranteedTailCallOpt :: TargetOptionFlag
- typeKindHalf :: TypeKind
- mcTargetOptionFlagMCSaveTempLabels :: MCTargetOptionFlag
- targetOptionFlagStackSymbolOrdering :: TargetOptionFlag
- typeKindFloat :: TypeKind
- mcTargetOptionFlagMCUseDwarfDirectory :: MCTargetOptionFlag
- targetOptionFlagEnableFastISel :: TargetOptionFlag
- typeKindDouble :: TypeKind
- mcTargetOptionFlagMCIncrementalLinkerCompatible :: MCTargetOptionFlag
- targetOptionFlagUseInitArray :: TargetOptionFlag
- typeKindX86_FP80 :: TypeKind
- mcTargetOptionFlagMCPIECopyRelocations :: MCTargetOptionFlag
- targetOptionFlagDisableIntegratedAS :: TargetOptionFlag
- typeKindFP128 :: TypeKind
- mcTargetOptionFlagShowMCEncoding :: MCTargetOptionFlag
- targetOptionFlagRelaxELFRelocations :: TargetOptionFlag
- typeKindPPC_FP128 :: TypeKind
- mcTargetOptionFlagShowMCInst :: MCTargetOptionFlag
- newtype ParameterAttributeKind = ParameterAttributeKind CUInt
- targetOptionFlagFunctionSections :: TargetOptionFlag
- typeKindLabel :: TypeKind
- mcTargetOptionFlagAsmVerbose :: MCTargetOptionFlag
- targetOptionFlagDataSections :: TargetOptionFlag
- parameterAttributeKindAlignment :: ParameterAttributeKind
- typeKindInteger :: TypeKind
- mcTargetOptionFlagPreserveAsmComments :: MCTargetOptionFlag
- parameterAttributeKindByVal :: ParameterAttributeKind
- targetOptionFlagUniqueSectionNames :: TargetOptionFlag
- newtype FunctionAttributeKind = FunctionAttributeKind CUInt
- typeKindFunction :: TypeKind
- mcTargetOptionFlagP :: QuasiQuoter
- targetOptionFlagTrapUnreachable :: TargetOptionFlag
- parameterAttributeKindDereferenceable :: ParameterAttributeKind
- typeKindStruct :: TypeKind
- functionAttributeKindAllocSize :: FunctionAttributeKind
- targetOptionFlagEmulatedTLS :: TargetOptionFlag
- parameterAttributeKindDereferenceableOrNull :: ParameterAttributeKind
- typeKindArray :: TypeKind
- functionAttributeKindAlwaysInline :: FunctionAttributeKind
- newtype FloatSemantics = FloatSemantics CUInt
- targetOptionFlagEnableIPRA :: TargetOptionFlag
- parameterAttributeKindInAlloca :: ParameterAttributeKind
- typeKindPointer :: TypeKind
- functionAttributeKindArgMemOnly :: FunctionAttributeKind
- targetOptionFlagP :: QuasiQuoter
- floatSemanticsIEEEhalf :: FloatSemantics
- parameterAttributeKindInReg :: ParameterAttributeKind
- typeKindVector :: TypeKind
- functionAttributeKindBuiltin :: FunctionAttributeKind
- floatSemanticsIEEEsingle :: FloatSemantics
- parameterAttributeKindNest :: ParameterAttributeKind
- newtype VerifierFailureAction = VerifierFailureAction CUInt
- typeKindMetadata :: TypeKind
- functionAttributeKindCold :: FunctionAttributeKind
- floatSemanticsIEEEdouble :: FloatSemantics
- parameterAttributeKindNoAlias :: ParameterAttributeKind
- typeKindX86_MMX :: TypeKind
- functionAttributeKindConvergent :: FunctionAttributeKind
- verifierFailureActionAbortProcess :: VerifierFailureAction
- floatSemanticsIEEEquad :: FloatSemantics
- parameterAttributeKindNoCapture :: ParameterAttributeKind
- typeKindToken :: TypeKind
- verifierFailureActionPrintMessage :: VerifierFailureAction
- functionAttributeKindInaccessibleMemOnly :: FunctionAttributeKind
- newtype LibFunc = LibFunc CUInt
- floatSemanticsPPCDoubleDouble :: FloatSemantics
- parameterAttributeKindNonNull :: ParameterAttributeKind
- typeKindP :: QuasiQuoter
- verifierFailureActionReturnStatus :: VerifierFailureAction
- functionAttributeKindInaccessibleMemOrArgMemOnly :: FunctionAttributeKind
- libFunc__under_IO_getc :: LibFunc
- floatSemanticsx87DoubleExtended :: FloatSemantics
- parameterAttributeKindReadNone :: ParameterAttributeKind
- verifierFailureActionP :: QuasiQuoter
- functionAttributeKindInlineHint :: FunctionAttributeKind
- libFunc__under_IO_putc :: LibFunc
- floatSemanticsBogus :: FloatSemantics
- parameterAttributeKindReadOnly :: ParameterAttributeKind
- newtype JITSymbolFlags = JITSymbolFlags CUInt
- functionAttributeKindJumpTable :: FunctionAttributeKind
- libFunc__ZdaPv :: LibFunc
- floatSemanticsP :: QuasiQuoter
- parameterAttributeKindReturned :: ParameterAttributeKind
- jitSymbolFlagsNone :: JITSymbolFlags
- functionAttributeKindMinSize :: FunctionAttributeKind
- libFunc__ZdaPvRKSt9nothrow_t :: LibFunc
- parameterAttributeKindSExt :: ParameterAttributeKind
- jitSymbolFlagsWeak :: JITSymbolFlags
- functionAttributeKindNaked :: FunctionAttributeKind
- newtype ChecksumKind = ChecksumKind CUInt
- libFunc__ZdlPv :: LibFunc
- parameterAttributeKindStructRet :: ParameterAttributeKind
- jitSymbolFlagsExported :: JITSymbolFlags
- functionAttributeKindNoBuiltin :: FunctionAttributeKind
- libFunc__ZdlPvRKSt9nothrow_t :: LibFunc
- parameterAttributeKindSwiftError :: ParameterAttributeKind
- newtype Macinfo = Macinfo CUInt
- jitSymbolFlagsP :: QuasiQuoter
- functionAttributeKindNoDuplicate :: FunctionAttributeKind
- libFunc__Znaj :: LibFunc
- parameterAttributeKindSwiftSelf :: ParameterAttributeKind
- pattern DW_Macinfo_Define :: Macinfo
- functionAttributeKindNoImplicitFloat :: FunctionAttributeKind
- libFunc__ZnajRKSt9nothrow_t :: LibFunc
- parameterAttributeKindWriteOnly :: ParameterAttributeKind
- pattern DW_Macinfo_Undef :: Macinfo
- functionAttributeKindNoInline :: FunctionAttributeKind
- libFunc__Znam :: LibFunc
- parameterAttributeKindZExt :: ParameterAttributeKind
- functionAttributeKindNoRecurse :: FunctionAttributeKind
- libFunc__ZnamRKSt9nothrow_t :: LibFunc
- parameterAttributeKindP :: QuasiQuoter
- newtype DebugEmissionKind = DebugEmissionKind CUInt
- functionAttributeKindNoRedZone :: FunctionAttributeKind
- libFunc__Znwj :: LibFunc
- pattern NoDebug :: DebugEmissionKind
- functionAttributeKindNoReturn :: FunctionAttributeKind
- libFunc__ZnwjRKSt9nothrow_t :: LibFunc
- pattern FullDebug :: DebugEmissionKind
- functionAttributeKindNoUnwind :: FunctionAttributeKind
- libFunc__Znwm :: LibFunc
- pattern LineTablesOnly :: DebugEmissionKind
- functionAttributeKindNonLazyBind :: FunctionAttributeKind
- libFunc__ZnwmRKSt9nothrow_t :: LibFunc
- functionAttributeKindOptimizeForSize :: FunctionAttributeKind
- libFunc__cospi :: LibFunc
- functionAttributeKindOptimizeNone :: FunctionAttributeKind
- libFunc__cospif :: LibFunc
- functionAttributeKindReadNone :: FunctionAttributeKind
- libFunc__cxa_atexit :: LibFunc
- functionAttributeKindReadOnly :: FunctionAttributeKind
- libFunc__cxa_guard_abort :: LibFunc
- functionAttributeKindReturnsTwice :: FunctionAttributeKind
- libFunc__cxa_guard_acquire :: LibFunc
- functionAttributeKindSafeStack :: FunctionAttributeKind
- libFunc__cxa_guard_release :: LibFunc
- functionAttributeKindSanitizeAddress :: FunctionAttributeKind
- libFunc__dunder_isoc99_scanf :: LibFunc
- functionAttributeKindSanitizeHWAddress :: FunctionAttributeKind
- libFunc__dunder_isoc99_sscanf :: LibFunc
- functionAttributeKindSanitizeMemory :: FunctionAttributeKind
- libFunc__memcpy_chk :: LibFunc
- functionAttributeKindSanitizeThread :: FunctionAttributeKind
- libFunc__sincospi_stret :: LibFunc
- functionAttributeKindSpeculatable :: FunctionAttributeKind
- libFunc__sincospif_stret :: LibFunc
- functionAttributeKindStackAlignment :: FunctionAttributeKind
- libFunc__sinpi :: LibFunc
- functionAttributeKindStackProtect :: FunctionAttributeKind
- libFunc__sinpif :: LibFunc
- functionAttributeKindStackProtectReq :: FunctionAttributeKind
- libFunc__sqrt_finite :: LibFunc
- functionAttributeKindStackProtectStrong :: FunctionAttributeKind
- libFunc__sqrtf_finite :: LibFunc
- functionAttributeKindStrictFP :: FunctionAttributeKind
- libFunc__sqrtl_finite :: LibFunc
- functionAttributeKindUWTable :: FunctionAttributeKind
- libFunc__dunder_strdup :: LibFunc
- functionAttributeKindWriteOnly :: FunctionAttributeKind
- libFunc__dunder_strndup :: LibFunc
- functionAttributeKindP :: QuasiQuoter
- libFunc__dunder_strtok_r :: LibFunc
- libFunc__abs :: LibFunc
- libFunc__access :: LibFunc
- libFunc__acos :: LibFunc
- libFunc__acosf :: LibFunc
- libFunc__acosh :: LibFunc
- libFunc__acoshf :: LibFunc
- libFunc__acoshl :: LibFunc
- libFunc__acosl :: LibFunc
- libFunc__asin :: LibFunc
- libFunc__asinf :: LibFunc
- libFunc__asinh :: LibFunc
- libFunc__asinhf :: LibFunc
- libFunc__asinhl :: LibFunc
- libFunc__asinl :: LibFunc
- libFunc__atan :: LibFunc
- libFunc__atan2 :: LibFunc
- libFunc__atan2f :: LibFunc
- libFunc__atan2l :: LibFunc
- libFunc__atanf :: LibFunc
- libFunc__atanh :: LibFunc
- libFunc__atanhf :: LibFunc
- libFunc__atanhl :: LibFunc
- libFunc__atanl :: LibFunc
- libFunc__atof :: LibFunc
- libFunc__atoi :: LibFunc
- libFunc__atol :: LibFunc
- libFunc__atoll :: LibFunc
- libFunc__bcmp :: LibFunc
- libFunc__bcopy :: LibFunc
- libFunc__bzero :: LibFunc
- libFunc__calloc :: LibFunc
- libFunc__cbrt :: LibFunc
- libFunc__cbrtf :: LibFunc
- libFunc__cbrtl :: LibFunc
- libFunc__ceil :: LibFunc
- libFunc__ceilf :: LibFunc
- libFunc__ceill :: LibFunc
- libFunc__chmod :: LibFunc
- libFunc__chown :: LibFunc
- libFunc__clearerr :: LibFunc
- libFunc__closedir :: LibFunc
- libFunc__copysign :: LibFunc
- libFunc__copysignf :: LibFunc
- libFunc__copysignl :: LibFunc
- libFunc__cos :: LibFunc
- libFunc__cosf :: LibFunc
- libFunc__cosh :: LibFunc
- libFunc__coshf :: LibFunc
- libFunc__coshl :: LibFunc
- libFunc__cosl :: LibFunc
- libFunc__ctermid :: LibFunc
- libFunc__exp :: LibFunc
- libFunc__exp10 :: LibFunc
- libFunc__exp10f :: LibFunc
- libFunc__exp10l :: LibFunc
- libFunc__exp2 :: LibFunc
- libFunc__exp2f :: LibFunc
- libFunc__exp2l :: LibFunc
- libFunc__expf :: LibFunc
- libFunc__expl :: LibFunc
- libFunc__expm1 :: LibFunc
- libFunc__expm1f :: LibFunc
- libFunc__expm1l :: LibFunc
- libFunc__fabs :: LibFunc
- libFunc__fabsf :: LibFunc
- libFunc__fabsl :: LibFunc
- libFunc__fclose :: LibFunc
- libFunc__fdopen :: LibFunc
- libFunc__feof :: LibFunc
- libFunc__ferror :: LibFunc
- libFunc__fflush :: LibFunc
- libFunc__ffs :: LibFunc
- libFunc__ffsl :: LibFunc
- libFunc__ffsll :: LibFunc
- libFunc__fgetc :: LibFunc
- libFunc__fgetpos :: LibFunc
- libFunc__fgets :: LibFunc
- libFunc__fileno :: LibFunc
- libFunc__fiprintf :: LibFunc
- libFunc__flockfile :: LibFunc
- libFunc__floor :: LibFunc
- libFunc__floorf :: LibFunc
- libFunc__floorl :: LibFunc
- libFunc__fmax :: LibFunc
- libFunc__fmaxf :: LibFunc
- libFunc__fmaxl :: LibFunc
- libFunc__fmin :: LibFunc
- libFunc__fminf :: LibFunc
- libFunc__fminl :: LibFunc
- libFunc__fmod :: LibFunc
- libFunc__fmodf :: LibFunc
- libFunc__fmodl :: LibFunc
- libFunc__fopen :: LibFunc
- libFunc__fopen64 :: LibFunc
- libFunc__fprintf :: LibFunc
- libFunc__fputc :: LibFunc
- libFunc__fputs :: LibFunc
- libFunc__fread :: LibFunc
- libFunc__free :: LibFunc
- libFunc__frexp :: LibFunc
- libFunc__frexpf :: LibFunc
- libFunc__frexpl :: LibFunc
- libFunc__fscanf :: LibFunc
- libFunc__fseek :: LibFunc
- libFunc__fseeko :: LibFunc
- libFunc__fseeko64 :: LibFunc
- libFunc__fsetpos :: LibFunc
- libFunc__fstat :: LibFunc
- libFunc__fstat64 :: LibFunc
- libFunc__fstatvfs :: LibFunc
- libFunc__fstatvfs64 :: LibFunc
- libFunc__ftell :: LibFunc
- libFunc__ftello :: LibFunc
- libFunc__ftello64 :: LibFunc
- libFunc__ftrylockfile :: LibFunc
- libFunc__funlockfile :: LibFunc
- libFunc__fwrite :: LibFunc
- libFunc__getc :: LibFunc
- libFunc__getc_unlocked :: LibFunc
- libFunc__getchar :: LibFunc
- libFunc__getenv :: LibFunc
- libFunc__getitimer :: LibFunc
- libFunc__getlogin_r :: LibFunc
- libFunc__getpwnam :: LibFunc
- libFunc__gets :: LibFunc
- libFunc__gettimeofday :: LibFunc
- libFunc__htonl :: LibFunc
- libFunc__htons :: LibFunc
- libFunc__iprintf :: LibFunc
- libFunc__isascii :: LibFunc
- libFunc__isdigit :: LibFunc
- libFunc__labs :: LibFunc
- libFunc__lchown :: LibFunc
- libFunc__ldexp :: LibFunc
- libFunc__ldexpf :: LibFunc
- libFunc__ldexpl :: LibFunc
- libFunc__llabs :: LibFunc
- libFunc__log :: LibFunc
- libFunc__log10 :: LibFunc
- libFunc__log10f :: LibFunc
- libFunc__log10l :: LibFunc
- libFunc__log1p :: LibFunc
- libFunc__log1pf :: LibFunc
- libFunc__log1pl :: LibFunc
- libFunc__log2 :: LibFunc
- libFunc__log2f :: LibFunc
- libFunc__log2l :: LibFunc
- libFunc__logb :: LibFunc
- libFunc__logbf :: LibFunc
- libFunc__logbl :: LibFunc
- libFunc__logf :: LibFunc
- libFunc__logl :: LibFunc
- libFunc__lstat :: LibFunc
- libFunc__lstat64 :: LibFunc
- libFunc__malloc :: LibFunc
- libFunc__memalign :: LibFunc
- libFunc__memccpy :: LibFunc
- libFunc__memchr :: LibFunc
- libFunc__memcmp :: LibFunc
- libFunc__memcpy :: LibFunc
- libFunc__memmove :: LibFunc
- libFunc__memrchr :: LibFunc
- libFunc__memset :: LibFunc
- libFunc__memset_pattern16 :: LibFunc
- libFunc__mkdir :: LibFunc
- libFunc__mktime :: LibFunc
- libFunc__modf :: LibFunc
- libFunc__modff :: LibFunc
- libFunc__modfl :: LibFunc
- libFunc__nearbyint :: LibFunc
- libFunc__nearbyintf :: LibFunc
- libFunc__nearbyintl :: LibFunc
- libFunc__ntohl :: LibFunc
- libFunc__ntohs :: LibFunc
- libFunc__open :: LibFunc
- libFunc__open64 :: LibFunc
- libFunc__opendir :: LibFunc
- libFunc__pclose :: LibFunc
- libFunc__perror :: LibFunc
- libFunc__popen :: LibFunc
- libFunc__posix_memalign :: LibFunc
- libFunc__pow :: LibFunc
- libFunc__powf :: LibFunc
- libFunc__powl :: LibFunc
- libFunc__pread :: LibFunc
- libFunc__printf :: LibFunc
- libFunc__putc :: LibFunc
- libFunc__putchar :: LibFunc
- libFunc__puts :: LibFunc
- libFunc__pwrite :: LibFunc
- libFunc__qsort :: LibFunc
- libFunc__read :: LibFunc
- libFunc__readlink :: LibFunc
- libFunc__realloc :: LibFunc
- libFunc__reallocf :: LibFunc
- libFunc__realpath :: LibFunc
- libFunc__remove :: LibFunc
- libFunc__rename :: LibFunc
- libFunc__rewind :: LibFunc
- libFunc__rint :: LibFunc
- libFunc__rintf :: LibFunc
- libFunc__rintl :: LibFunc
- libFunc__rmdir :: LibFunc
- libFunc__round :: LibFunc
- libFunc__roundf :: LibFunc
- libFunc__roundl :: LibFunc
- libFunc__scanf :: LibFunc
- libFunc__setbuf :: LibFunc
- libFunc__setitimer :: LibFunc
- libFunc__setvbuf :: LibFunc
- libFunc__sin :: LibFunc
- libFunc__sinf :: LibFunc
- libFunc__sinh :: LibFunc
- libFunc__sinhf :: LibFunc
- libFunc__sinhl :: LibFunc
- libFunc__sinl :: LibFunc
- libFunc__siprintf :: LibFunc
- libFunc__snprintf :: LibFunc
- libFunc__sprintf :: LibFunc
- libFunc__sqrt :: LibFunc
- libFunc__sqrtf :: LibFunc
- libFunc__sqrtl :: LibFunc
- libFunc__sscanf :: LibFunc
- libFunc__stat :: LibFunc
- libFunc__stat64 :: LibFunc
- libFunc__statvfs :: LibFunc
- libFunc__statvfs64 :: LibFunc
- libFunc__stpcpy :: LibFunc
- libFunc__stpncpy :: LibFunc
- libFunc__strcasecmp :: LibFunc
- libFunc__strcat :: LibFunc
- libFunc__strchr :: LibFunc
- libFunc__strcmp :: LibFunc
- libFunc__strcoll :: LibFunc
- libFunc__strcpy :: LibFunc
- libFunc__strcspn :: LibFunc
- libFunc__strdup :: LibFunc
- libFunc__strlen :: LibFunc
- libFunc__strncasecmp :: LibFunc
- libFunc__strncat :: LibFunc
- libFunc__strncmp :: LibFunc
- libFunc__strncpy :: LibFunc
- libFunc__strndup :: LibFunc
- libFunc__strnlen :: LibFunc
- libFunc__strpbrk :: LibFunc
- libFunc__strrchr :: LibFunc
- libFunc__strspn :: LibFunc
- libFunc__strstr :: LibFunc
- libFunc__strtod :: LibFunc
- libFunc__strtof :: LibFunc
- libFunc__strtok :: LibFunc
- libFunc__strtok_r :: LibFunc
- libFunc__strtol :: LibFunc
- libFunc__strtold :: LibFunc
- libFunc__strtoll :: LibFunc
- libFunc__strtoul :: LibFunc
- libFunc__strtoull :: LibFunc
- libFunc__strxfrm :: LibFunc
- libFunc__system :: LibFunc
- libFunc__tan :: LibFunc
- libFunc__tanf :: LibFunc
- libFunc__tanh :: LibFunc
- libFunc__tanhf :: LibFunc
- libFunc__tanhl :: LibFunc
- libFunc__tanl :: LibFunc
- libFunc__times :: LibFunc
- libFunc__tmpfile :: LibFunc
- libFunc__tmpfile64 :: LibFunc
- libFunc__toascii :: LibFunc
- libFunc__trunc :: LibFunc
- libFunc__truncf :: LibFunc
- libFunc__truncl :: LibFunc
- libFunc__uname :: LibFunc
- libFunc__ungetc :: LibFunc
- libFunc__unlink :: LibFunc
- libFunc__unsetenv :: LibFunc
- libFunc__utime :: LibFunc
- libFunc__utimes :: LibFunc
- libFunc__valloc :: LibFunc
- libFunc__vfprintf :: LibFunc
- libFunc__vfscanf :: LibFunc
- libFunc__vprintf :: LibFunc
- libFunc__vscanf :: LibFunc
- libFunc__vsnprintf :: LibFunc
- libFunc__vsprintf :: LibFunc
- libFunc__vsscanf :: LibFunc
- libFunc__write :: LibFunc
- libFunc__P :: QuasiQuoter
Documentation
pattern DwOp_LLVM_fragment :: Word64 Source #
pattern DwOp_stack_value :: Word64 Source #
pattern DwOp_constu :: Word64 Source #
pattern DwOp_plus_uconst :: Word64 Source #
pattern DwOp_minus :: Word64 Source #
pattern DwOp_deref :: Word64 Source #
pattern DwOp_xderef :: Word64 Source #
Instances
Data Encoding Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Encoding -> c Encoding # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Encoding # toConstr :: Encoding -> Constr # dataTypeOf :: Encoding -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Encoding) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding) # gmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQ :: (forall d. Data d => d -> u) -> Encoding -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Encoding -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # | |
Show Encoding Source # | |
Monad m => DecodeM m Encoding Encoding Source # | |
Monad m => EncodeM m Encoding Encoding Source # | |
DecodeM DecodeAST (Maybe Encoding) Encoding Source # | |
EncodeM EncodeAST (Maybe Encoding) Encoding Source # | |
pattern DwAtE_address :: Encoding Source #
pattern DwAtE_boolean :: Encoding Source #
Instances
pattern DwAtE_complex_float :: Encoding Source #
pattern DwAtE_float :: Encoding Source #
pattern DwTag_imported_module :: DwTag Source #
pattern DwAtE_signed :: Encoding Source #
pattern DwTag_imported_declaration :: DwTag Source #
newtype DwVirtuality Source #
Instances
pattern DwTag_typedef :: DwTag Source #
pattern DwAtE_signed_char :: Encoding Source #
pattern DwAtE_unsigned :: Encoding Source #
pattern DwTag_pointer_type :: DwTag Source #
pattern DwVirtuality_none :: DwVirtuality Source #
pattern DwAtE_unsigned_char :: Encoding Source #
pattern DwTag_ptr_to_member_type :: DwTag Source #
pattern DwVirtuality_virtual :: DwVirtuality Source #
pattern DwTag_reference_type :: DwTag Source #
pattern DwAtE_imaginary_float :: Encoding Source #
pattern DwVirtuality_pure_virtual :: DwVirtuality Source #
pattern DwAtE_packed_decimal :: Encoding Source #
If an FFI function returns a value wrapped in OwnerTransfered
,
this value needs to be freed after it has been processed. Usually
this is done automatically in the DecodeM
instance.
pattern DwTag_rvalue_reference_type :: DwTag Source #
pattern DwTag_const_type :: DwTag Source #
pattern DwAtE_numeric_string :: Encoding Source #
newtype OwnerTransfered a Source #
Instances
pattern DwAtE_edited :: Encoding Source #
pattern DwTag_volatile_type :: DwTag Source #
pattern DwTag_restrict_type :: DwTag Source #
pattern DwAtE_signed_fixed :: Encoding Source #
newtype NothingAsMinusOne h Source #
Instances
Monad m => EncodeM m (Maybe Word) (NothingAsMinusOne Word) Source # | |
Defined in LLVM.Internal.Coding | |
Monad m => EncodeM m (Maybe Bool) (NothingAsMinusOne Bool) Source # | |
Defined in LLVM.Internal.Coding | |
Storable (NothingAsMinusOne h) Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes sizeOf :: NothingAsMinusOne h -> Int # alignment :: NothingAsMinusOne h -> Int # peekElemOff :: Ptr (NothingAsMinusOne h) -> Int -> IO (NothingAsMinusOne h) # pokeElemOff :: Ptr (NothingAsMinusOne h) -> Int -> NothingAsMinusOne h -> IO () # peekByteOff :: Ptr b -> Int -> IO (NothingAsMinusOne h) # pokeByteOff :: Ptr b -> Int -> NothingAsMinusOne h -> IO () # peek :: Ptr (NothingAsMinusOne h) -> IO (NothingAsMinusOne h) # poke :: Ptr (NothingAsMinusOne h) -> NothingAsMinusOne h -> IO () # |
pattern DwTag_atomic_type :: DwTag Source #
pattern DwAtE_unsigned_fixed :: Encoding Source #
newtype NothingAsEmptyString c Source #
Instances
(Monad e, EncodeM e String c) => EncodeM e (Maybe String) (NothingAsEmptyString c) Source # | |
Defined in LLVM.Internal.String | |
Storable c => Storable (NothingAsEmptyString c) Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes sizeOf :: NothingAsEmptyString c -> Int # alignment :: NothingAsEmptyString c -> Int # peekElemOff :: Ptr (NothingAsEmptyString c) -> Int -> IO (NothingAsEmptyString c) # pokeElemOff :: Ptr (NothingAsEmptyString c) -> Int -> NothingAsEmptyString c -> IO () # peekByteOff :: Ptr b -> Int -> IO (NothingAsEmptyString c) # pokeByteOff :: Ptr b -> Int -> NothingAsEmptyString c -> IO () # peek :: Ptr (NothingAsEmptyString c) -> IO (NothingAsEmptyString c) # poke :: Ptr (NothingAsEmptyString c) -> NothingAsEmptyString c -> IO () # |
pattern DwTag_member :: DwTag Source #
pattern DwAtE_decimal_float :: Encoding Source #
pattern DwTag_inheritance :: DwTag Source #
Instances
Eq CPPOpcode Source # | |
Data CPPOpcode Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CPPOpcode -> c CPPOpcode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CPPOpcode # toConstr :: CPPOpcode -> Constr # dataTypeOf :: CPPOpcode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CPPOpcode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CPPOpcode) # gmapT :: (forall b. Data b => b -> b) -> CPPOpcode -> CPPOpcode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CPPOpcode -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CPPOpcode -> r # gmapQ :: (forall d. Data d => d -> u) -> CPPOpcode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CPPOpcode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CPPOpcode -> m CPPOpcode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CPPOpcode -> m CPPOpcode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CPPOpcode -> m CPPOpcode # | |
Ord CPPOpcode Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes | |
Show CPPOpcode Source # | |
Generic CPPOpcode Source # | |
type Rep CPPOpcode Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes |
pattern DwTag_friend :: DwTag Source #
newtype ICmpPredicate Source #
Instances
pattern DwAtE_ASCII :: Encoding Source #
pattern DwTag_base_type :: DwTag Source #
pattern DwTag_unspecified_type :: DwTag Source #
pattern DwTag_template_value_parameter :: DwTag Source #
pattern DwTag_GNU_template_template_param :: DwTag Source #
pattern DwTag_GNU_template_parameter_pack :: DwTag Source #
pattern DwTag_array_type :: DwTag Source #
pattern DwTag_enumeration_type :: DwTag Source #
pattern DwTag_structure_type :: DwTag Source #
newtype FCmpPredicate Source #
Instances
pattern DwTag_class_type :: DwTag Source #
pattern DwTag_union_type :: DwTag Source #
Instances
Storable MDKindID Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes | |
DecodeM DecodeAST ShortByteString MDKindID Source # | |
Defined in LLVM.Internal.Metadata | |
EncodeM EncodeAST ShortByteString MDKindID Source # | |
Defined in LLVM.Internal.Metadata |
newtype MDSubclassID Source #
Instances
newtype FastMathFlags Source #
Instances
newtype MemoryOrdering Source #
Instances
newtype UnnamedAddr Source #
Instances
newtype SynchronizationScope Source #
Instances
newtype TailCallKind Source #
Instances
Instances
Eq Linkage Source # | |
Data Linkage Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Linkage -> c Linkage # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Linkage # toConstr :: Linkage -> Constr # dataTypeOf :: Linkage -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Linkage) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Linkage) # gmapT :: (forall b. Data b => b -> b) -> Linkage -> Linkage # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Linkage -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Linkage -> r # gmapQ :: (forall d. Data d => d -> u) -> Linkage -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Linkage -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage # | |
Read Linkage Source # | |
Show Linkage Source # | |
Generic Linkage Source # | |
Monad m => DecodeM m Linkage Linkage Source # | |
Monad m => EncodeM m Linkage Linkage Source # | |
type Rep Linkage Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes |
newtype Visibility Source #
Instances
newtype COMDATSelectionKind Source #
Instances
newtype DLLStorageClass Source #
Instances
newtype CallingConvention Source #
Instances
newtype ThreadLocalMode Source #
Instances
newtype ValueSubclassId Source #
Instances
newtype DiagnosticKind Source #
Instances
newtype AsmDialect Source #
Instances
newtype RMWOperation Source #
Instances
newtype RelocModel Source #
Instances
Instances
Eq CodeModel Source # | |
Data CodeModel Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CodeModel -> c CodeModel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CodeModel # toConstr :: CodeModel -> Constr # dataTypeOf :: CodeModel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CodeModel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CodeModel) # gmapT :: (forall b. Data b => b -> b) -> CodeModel -> CodeModel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CodeModel -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CodeModel -> r # gmapQ :: (forall d. Data d => d -> u) -> CodeModel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CodeModel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CodeModel -> m CodeModel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeModel -> m CodeModel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeModel -> m CodeModel # | |
Read CodeModel Source # | |
Show CodeModel Source # | |
Generic CodeModel Source # | |
Monad m => DecodeM m Model CodeModel Source # | |
Monad m => EncodeM m Model CodeModel Source # | |
type Rep CodeModel Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes |
newtype CodeGenOptLevel Source #
Instances
newtype CodeGenFileType Source #
Instances
newtype FloatABIType Source #
Instances
newtype FPOpFusionMode Source #
Instances
newtype ThreadModel Source #
Instances
Instances
Eq EABI Source # | |
Data EABI Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EABI -> c EABI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EABI # dataTypeOf :: EABI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EABI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EABI) # gmapT :: (forall b. Data b => b -> b) -> EABI -> EABI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EABI -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EABI -> r # gmapQ :: (forall d. Data d => d -> u) -> EABI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EABI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EABI -> m EABI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EABI -> m EABI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EABI -> m EABI # | |
Read EABI Source # | |
Show EABI Source # | |
Generic EABI Source # | |
Monad m => DecodeM m EABIVersion EABI Source # | |
Defined in LLVM.Internal.Target decodeM :: EABI -> m EABIVersion Source # | |
Monad m => EncodeM m EABIVersion EABI Source # | |
Defined in LLVM.Internal.Target encodeM :: EABIVersion -> m EABI Source # | |
type Rep EABI Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes |
newtype DebuggerKind Source #
Instances
newtype FPDenormalMode Source #
Instances
newtype ExceptionHandling Source #
Instances
newtype TargetOptionFlag Source #
Instances
newtype MCTargetOptionFlag Source #
Instances
newtype DebugCompressionType Source #
Instances
Instances
Eq TypeKind Source # | |
Data TypeKind Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeKind -> c TypeKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeKind # toConstr :: TypeKind -> Constr # dataTypeOf :: TypeKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeKind) # gmapT :: (forall b. Data b => b -> b) -> TypeKind -> TypeKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeKind -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeKind -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeKind -> m TypeKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeKind -> m TypeKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeKind -> m TypeKind # | |
Read TypeKind Source # | |
Show TypeKind Source # | |
Generic TypeKind Source # | |
type Rep TypeKind Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes |
newtype ParameterAttributeKind Source #
Instances
newtype FunctionAttributeKind Source #
Instances
newtype FloatSemantics Source #
Instances
newtype VerifierFailureAction Source #
Instances
Instances
newtype JITSymbolFlags Source #
Instances
newtype ChecksumKind Source #
Instances
Instances
Data Macinfo Source # | |
Defined in LLVM.Internal.FFI.LLVMCTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Macinfo -> c Macinfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Macinfo # toConstr :: Macinfo -> Constr # dataTypeOf :: Macinfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Macinfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Macinfo) # gmapT :: (forall b. Data b => b -> b) -> Macinfo -> Macinfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Macinfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Macinfo -> r # gmapQ :: (forall d. Data d => d -> u) -> Macinfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Macinfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Macinfo -> m Macinfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Macinfo -> m Macinfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Macinfo -> m Macinfo # | |
Show Macinfo Source # | |
Monad m => DecodeM m DIMacroInfo Macinfo Source # | |
Defined in LLVM.Internal.Operand decodeM :: Macinfo -> m DIMacroInfo Source # | |
Monad m => EncodeM m DIMacroInfo Macinfo Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIMacroInfo -> m Macinfo Source # |
pattern DW_Macinfo_Define :: Macinfo Source #
pattern DW_Macinfo_Undef :: Macinfo Source #
newtype DebugEmissionKind Source #
Instances
pattern NoDebug :: DebugEmissionKind Source #
pattern FullDebug :: DebugEmissionKind Source #
pattern LineTablesOnly :: DebugEmissionKind Source #
Orphan instances
Data CUInt Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CUInt -> c CUInt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CUInt # dataTypeOf :: CUInt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CUInt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CUInt) # gmapT :: (forall b. Data b => b -> b) -> CUInt -> CUInt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CUInt -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CUInt -> r # gmapQ :: (forall d. Data d => d -> u) -> CUInt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CUInt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CUInt -> m CUInt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CUInt -> m CUInt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CUInt -> m CUInt # |