Safe Haskell | None |
---|---|
Language | Haskell98 |
Define types which correspond cleanly with some simple types on the C/C++ side. Encapsulate hsc macro weirdness here, supporting higher-level tricks elsewhere.
- newtype LLVMBool = LLVMBool CUInt
- newtype OwnerTransfered a = OwnerTransfered a
- newtype NothingAsMinusOne h = NothingAsMinusOne CInt
- newtype NothingAsEmptyString c = NothingAsEmptyString c
- newtype CPPOpcode = CPPOpcode CUInt
- newtype ICmpPredicate = ICmpPredicate CUInt
- iCmpPredEQ :: ICmpPredicate
- iCmpPredNE :: ICmpPredicate
- iCmpPredUGT :: ICmpPredicate
- iCmpPredUGE :: ICmpPredicate
- iCmpPredULT :: ICmpPredicate
- iCmpPredULE :: ICmpPredicate
- iCmpPredSGT :: ICmpPredicate
- iCmpPredSGE :: ICmpPredicate
- iCmpPredSLT :: ICmpPredicate
- iCmpPredSLE :: ICmpPredicate
- newtype FCmpPredicate = FCmpPredicate CUInt
- fCmpPredFalse :: FCmpPredicate
- fCmpPredOEQ :: FCmpPredicate
- 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 FastMathFlags = FastMathFlags CUInt
- fCmpPredULT :: FCmpPredicate
- fastMathFlagsUnsafeAlgebra :: FastMathFlags
- fCmpPredULE :: FCmpPredicate
- fastMathFlagsNoNaNs :: FastMathFlags
- newtype MemoryOrdering = MemoryOrdering CUInt
- fCmpPredUNE :: FCmpPredicate
- fastMathFlagsNoInfs :: FastMathFlags
- fcmpPredTrue :: FCmpPredicate
- memoryOrderingNotAtomic :: MemoryOrdering
- fastMathFlagsNoSignedZeros :: FastMathFlags
- memoryOrderingUnordered :: MemoryOrdering
- newtype UnnamedAddr = UnnamedAddr CUInt
- fastMathFlagsAllowReciprocal :: FastMathFlags
- memoryOrderingMonotonic :: MemoryOrdering
- unnamedAddrNone :: UnnamedAddr
- fastMathFlagsAllowContract :: FastMathFlags
- memoryOrderingAcquire :: MemoryOrdering
- fastMathFlagsP :: QuasiQuoter
- unnamedAddrLocal :: UnnamedAddr
- newtype SynchronizationScope = SynchronizationScope CUInt
- memoryOrderingRelease :: MemoryOrdering
- unnamedAddrGlobal :: UnnamedAddr
- memoryOrderingAcquireRelease :: MemoryOrdering
- synchronizationScopeSingleThread :: SynchronizationScope
- unnamedAddrP :: QuasiQuoter
- synchronizationScopeSystem :: SynchronizationScope
- memoryOrderingSequentiallyConsistent :: MemoryOrdering
- newtype TailCallKind = TailCallKind CUInt
- memoryOrderingP :: QuasiQuoter
- synchronizationScopeP :: QuasiQuoter
- tailCallKindNone :: TailCallKind
- tailCallKindTail :: TailCallKind
- newtype Linkage = Linkage CUInt
- tailCallKindMustTail :: TailCallKind
- linkageExternal :: Linkage
- tailCallKindNoTail :: TailCallKind
- linkageAvailableExternally :: Linkage
- newtype Visibility = Visibility CUInt
- tailCallKindP :: QuasiQuoter
- linkageLinkOnceAny :: Linkage
- visibilityDefault :: Visibility
- linkageLinkOnceODR :: Linkage
- visibilityHidden :: Visibility
- newtype COMDATSelectionKind = COMDATSelectionKind CUInt
- linkageWeakAny :: Linkage
- visibilityProtected :: Visibility
- linkageWeakODR :: Linkage
- comdatSelectionKindAny :: COMDATSelectionKind
- visibilityP :: QuasiQuoter
- linkageAppending :: Linkage
- comdatSelectionKindExactMatch :: COMDATSelectionKind
- newtype DLLStorageClass = DLLStorageClass CUInt
- linkageInternal :: Linkage
- comdatSelectionKindLargest :: COMDATSelectionKind
- dllStorageClassDefault :: DLLStorageClass
- linkagePrivate :: Linkage
- comdatSelectionKindNoDuplicates :: COMDATSelectionKind
- dllStorageClassDLLImport :: DLLStorageClass
- newtype CallingConvention = CallingConvention CUInt
- linkageExternalWeak :: Linkage
- comdatSelectionKindSameSize :: COMDATSelectionKind
- dllStorageClassDLLExport :: DLLStorageClass
- linkageCommon :: Linkage
- comdatSelectionKindP :: QuasiQuoter
- callingConventionC :: CallingConvention
- dllStorageClassP :: QuasiQuoter
- linkageP :: QuasiQuoter
- callingConventionFast :: CallingConvention
- newtype ThreadLocalMode = ThreadLocalMode CUInt
- callingConventionCold :: CallingConvention
- threadLocalModeNotThreadLocal :: ThreadLocalMode
- callingConventionGHC :: CallingConvention
- threadLocalModeGeneralDynamicTLSModel :: ThreadLocalMode
- newtype ValueSubclassId = ValueSubclassId CUInt
- callingConventionHiPE :: CallingConvention
- threadLocalModeLocalDynamicTLSModel :: ThreadLocalMode
- 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
- libFunc__ZdlPv :: LibFunc
- parameterAttributeKindStructRet :: ParameterAttributeKind
- jitSymbolFlagsExported :: JITSymbolFlags
- functionAttributeKindNoBuiltin :: FunctionAttributeKind
- libFunc__ZdlPvRKSt9nothrow_t :: LibFunc
- parameterAttributeKindSwiftError :: ParameterAttributeKind
- jitSymbolFlagsP :: QuasiQuoter
- functionAttributeKindNoDuplicate :: FunctionAttributeKind
- libFunc__Znaj :: LibFunc
- parameterAttributeKindSwiftSelf :: ParameterAttributeKind
- functionAttributeKindNoImplicitFloat :: FunctionAttributeKind
- libFunc__ZnajRKSt9nothrow_t :: LibFunc
- parameterAttributeKindWriteOnly :: ParameterAttributeKind
- functionAttributeKindNoInline :: FunctionAttributeKind
- libFunc__Znam :: LibFunc
- parameterAttributeKindZExt :: ParameterAttributeKind
- functionAttributeKindNoRecurse :: FunctionAttributeKind
- libFunc__ZnamRKSt9nothrow_t :: LibFunc
- parameterAttributeKindP :: QuasiQuoter
- functionAttributeKindNoRedZone :: FunctionAttributeKind
- libFunc__Znwj :: LibFunc
- functionAttributeKindNoReturn :: FunctionAttributeKind
- libFunc__ZnwjRKSt9nothrow_t :: LibFunc
- functionAttributeKindNoUnwind :: FunctionAttributeKind
- libFunc__Znwm :: LibFunc
- 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
- functionAttributeKindSanitizeMemory :: FunctionAttributeKind
- libFunc__dunder_isoc99_sscanf :: LibFunc
- functionAttributeKindSanitizeThread :: FunctionAttributeKind
- libFunc__memcpy_chk :: LibFunc
- functionAttributeKindSpeculatable :: FunctionAttributeKind
- libFunc__sincospi_stret :: LibFunc
- functionAttributeKindStackAlignment :: FunctionAttributeKind
- libFunc__sincospif_stret :: LibFunc
- functionAttributeKindStackProtect :: FunctionAttributeKind
- libFunc__sinpi :: LibFunc
- functionAttributeKindStackProtectReq :: FunctionAttributeKind
- libFunc__sinpif :: LibFunc
- functionAttributeKindStackProtectStrong :: FunctionAttributeKind
- libFunc__sqrt_finite :: LibFunc
- functionAttributeKindUWTable :: FunctionAttributeKind
- libFunc__sqrtf_finite :: LibFunc
- functionAttributeKindWriteOnly :: FunctionAttributeKind
- libFunc__sqrtl_finite :: LibFunc
- functionAttributeKindP :: QuasiQuoter
- libFunc__dunder_strdup :: LibFunc
- libFunc__dunder_strndup :: LibFunc
- 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
newtype OwnerTransfered a 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.
(MonadThrow m, MonadIO m, MonadAnyCont IO m) => EncodeM m Specification (OwnerTransfered (Ptr MemoryBuffer)) Source # | |
Storable a => Storable (OwnerTransfered a) Source # | |
newtype NothingAsMinusOne h Source #
newtype NothingAsEmptyString c Source #
Storable c => Storable (NothingAsEmptyString c) Source # | |
newtype ICmpPredicate Source #
newtype FCmpPredicate Source #
newtype FastMathFlags Source #
newtype MemoryOrdering Source #
newtype UnnamedAddr Source #
newtype SynchronizationScope Source #
newtype TailCallKind Source #
newtype Visibility Source #
newtype COMDATSelectionKind Source #
newtype DLLStorageClass Source #
newtype CallingConvention Source #
newtype ThreadLocalMode Source #
newtype ValueSubclassId Source #
newtype DiagnosticKind Source #
newtype AsmDialect Source #
newtype RMWOperation Source #
newtype RelocModel Source #
newtype CodeGenOptLevel Source #
newtype CodeGenFileType Source #
newtype FloatABIType Source #
newtype FPOpFusionMode Source #
newtype ThreadModel Source #
newtype DebuggerKind Source #
newtype FPDenormalMode Source #
newtype ExceptionHandling Source #
newtype TargetOptionFlag Source #
newtype MCTargetOptionFlag Source #
newtype DebugCompressionType Source #
newtype ParameterAttributeKind Source #
newtype FunctionAttributeKind Source #
newtype FloatSemantics Source #
newtype VerifierFailureAction Source #
Eq LibFunc Source # | |
Data LibFunc Source # | |
Num LibFunc Source # | |
Read LibFunc Source # | |
Show LibFunc Source # | |
Generic LibFunc Source # | |
Storable LibFunc Source # | |
Bits LibFunc Source # | |
Monad m => DecodeM m LibraryFunction LibFunc Source # | |
Monad m => EncodeM m LibraryFunction LibFunc Source # | |
type Rep LibFunc Source # | |
newtype JITSymbolFlags Source #