Copyright | (c) The University of Glasgow 2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | ghc-devs@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Note: no other base module should import this module.
Synopsis
- data Ptr a = Ptr Addr#
- data FunPtr a = FunPtr Addr#
- data Word = W# Word#
- data Float = F# Float#
- data Int = I# Int#
- data TYPE (a :: RuntimeRep)
- data CONSTRAINT (a :: RuntimeRep)
- data WordBox (a :: TYPE 'WordRep) = MkWordBox a
- data IntBox (a :: TYPE 'IntRep) = MkIntBox a
- data FloatBox (a :: TYPE 'FloatRep) = MkFloatBox a
- data DoubleBox (a :: TYPE 'DoubleRep) = MkDoubleBox a
- data DictBox a = a => MkDictBox
- data Bool
- data Char = C# Char#
- data Double = D# Double#
- data List a
- data Ordering
- class a ~# b => (a :: k0) ~~ (b :: k1)
- class a ~# b => (a :: k) ~ (b :: k)
- class a ~R# b => Coercible (a :: k) (b :: k)
- data Symbol
- data RuntimeRep
- data Levity
- data VecCount
- data VecElem
- data Multiplicity
- data SPEC
- pattern TypeLitChar :: TypeLitSort
- pattern TypeLitNat :: TypeLitSort
- pattern TypeLitSymbol :: TypeLitSort
- pattern KindRepTypeLitD :: TypeLitSort -> [Char] -> KindRep
- pattern KindRepTypeLitS :: TypeLitSort -> Addr# -> KindRep
- pattern KindRepTYPE :: !RuntimeRep -> KindRep
- pattern KindRepFun :: KindRep -> KindRep -> KindRep
- pattern KindRepApp :: KindRep -> KindRep -> KindRep
- pattern KindRepVar :: !KindBndr -> KindRep
- pattern KindRepTyConApp :: TyCon -> [KindRep] -> KindRep
- pattern TrNameD :: [Char] -> TrName
- pattern TrNameS :: Addr# -> TrName
- type ZeroBitType = TYPE ZeroBitRep
- type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep])
- type UnliftedRep = 'BoxedRep 'Unlifted
- type LiftedRep = 'BoxedRep 'Lifted
- type UnliftedType = TYPE UnliftedRep
- type Constraint = CONSTRAINT LiftedRep
- type family Any :: k where ...
- type Void# = (# #)
- type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ...
- isTrue# :: Int# -> Bool
- module GHC.Internal.ArrayArray
- data Word# :: TYPE 'WordRep
- data Int# :: TYPE 'IntRep
- data Addr# :: TYPE 'AddrRep
- data Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data ByteArray# :: UnliftedType
- data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data Char# :: TYPE 'WordRep
- data Double# :: TYPE 'DoubleRep
- data Float# :: TYPE 'FloatRep
- data Int8# :: TYPE 'Int8Rep
- data Int16# :: TYPE 'Int16Rep
- data Int32# :: TYPE 'Int32Rep
- data Int64# :: TYPE 'Int64Rep
- data BCO
- data Weak# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableByteArray# a :: UnliftedType
- data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data RealWorld
- data StablePtr# (a :: TYPE ('BoxedRep l)) :: TYPE 'AddrRep
- data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data Compact# :: UnliftedType
- data State# a :: ZeroBitType
- data Proxy# (a :: k) :: ZeroBitType
- data ThreadId# :: UnliftedType
- data Word8# :: TYPE 'Word8Rep
- data Word16# :: TYPE 'Word16Rep
- data Word32# :: TYPE 'Word32Rep
- data Word64# :: TYPE 'Word64Rep
- data StackSnapshot# :: UnliftedType
- data PromptTag# a :: UnliftedType
- data FUN
- data TYPE (a :: RuntimeRep)
- data CONSTRAINT (a :: RuntimeRep)
- data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep)
- data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep)
- data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep)
- data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep)
- data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep)
- data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep)
- data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep)
- data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep)
- data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep)
- data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep)
- data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep)
- data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep)
- data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep)
- data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep)
- data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep)
- data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep)
- data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep)
- data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep)
- data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep)
- data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep)
- data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep)
- data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep)
- data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep)
- data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep)
- data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep)
- data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep)
- data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep)
- data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep)
- data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep)
- data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep)
- prefetchValue0# :: a -> State# d -> State# d
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt8X64# :: Int8X64# -> Int8X64#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8#
- insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16#
- insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32#
- insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64#
- insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4#
- insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8#
- insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16#
- insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32#
- insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2#
- insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4#
- insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8#
- insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16#
- insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8#
- insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16#
- insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32#
- insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64#
- insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4#
- insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8#
- insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16#
- insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32#
- insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2#
- insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4#
- insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8#
- insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16#
- unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #)
- unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #)
- unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #)
- unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #)
- unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #)
- unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #)
- unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #)
- unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #)
- unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #)
- unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #)
- unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #)
- unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #)
- unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #)
- unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #)
- unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8#
- packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16#
- packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4#
- packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8#
- packDoubleX2# :: (# Double#, Double# #) -> DoubleX2#
- packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4#
- packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8#
- packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16#
- packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32#
- packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64#
- packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4#
- packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8#
- packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16#
- packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32#
- packWord64X2# :: (# Word64#, Word64# #) -> Word64X2#
- packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4#
- packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8#
- packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16#
- packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8#
- packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16#
- packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32#
- packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64#
- packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4#
- packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8#
- packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16#
- packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32#
- packInt64X2# :: (# Int64#, Int64# #) -> Int64X2#
- packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4#
- packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8#
- packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastWord64X8# :: Word64# -> Word64X8#
- broadcastWord32X16# :: Word32# -> Word32X16#
- broadcastWord16X32# :: Word16# -> Word16X32#
- broadcastWord8X64# :: Word8# -> Word8X64#
- broadcastWord64X4# :: Word64# -> Word64X4#
- broadcastWord32X8# :: Word32# -> Word32X8#
- broadcastWord16X16# :: Word16# -> Word16X16#
- broadcastWord8X32# :: Word8# -> Word8X32#
- broadcastWord64X2# :: Word64# -> Word64X2#
- broadcastWord32X4# :: Word32# -> Word32X4#
- broadcastWord16X8# :: Word16# -> Word16X8#
- broadcastWord8X16# :: Word8# -> Word8X16#
- broadcastInt64X8# :: Int64# -> Int64X8#
- broadcastInt32X16# :: Int32# -> Int32X16#
- broadcastInt16X32# :: Int16# -> Int16X32#
- broadcastInt8X64# :: Int8# -> Int8X64#
- broadcastInt64X4# :: Int64# -> Int64X4#
- broadcastInt32X8# :: Int32# -> Int32X8#
- broadcastInt16X16# :: Int16# -> Int16X16#
- broadcastInt8X32# :: Int8# -> Int8X32#
- broadcastInt64X2# :: Int64# -> Int64X2#
- broadcastInt32X4# :: Int32# -> Int32X4#
- broadcastInt16X8# :: Int16# -> Int16X8#
- broadcastInt8X16# :: Int8# -> Int8X16#
- setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld
- traceMarker# :: Addr# -> State# d -> State# d
- traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d
- traceEvent# :: Addr# -> State# d -> State# d
- clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #)
- getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #)
- getCCSOf# :: a -> State# d -> (# State# d, Addr# #)
- getApStackVal# :: a -> Int# -> (# Int#, b #)
- closureSize# :: a -> Int#
- unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
- mkApUpd0# :: BCO -> (# a #)
- anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #)
- addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #)
- tagToEnum# :: Int# -> a
- keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) d (b :: TYPE r). a -> State# d -> (State# d -> b) -> b
- numSparks# :: State# d -> (# State# d, Int# #)
- getSpark# :: State# d -> (# State# d, Int#, a #)
- seq# :: a -> State# d -> (# State# d, a #)
- spark# :: a -> State# d -> (# State# d, a #)
- par# :: a -> Int#
- reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int#
- compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #)
- compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #)
- compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #)
- compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld
- compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #)
- stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int#
- makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
- eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int#
- deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #)
- makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #)
- touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d
- finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
- deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #)
- addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #)
- mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #)
- threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #)
- threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #)
- noDuplicate# :: State# d -> State# d
- isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #)
- labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld
- myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #)
- yield# :: State# RealWorld -> State# RealWorld
- killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
- forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- waitWrite# :: Int# -> State# d -> State# d
- waitRead# :: Int# -> State# d -> State# d
- delay# :: Int# -> State# d -> State# d
- writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #)
- readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #)
- newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
- isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #)
- tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #)
- putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d
- tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #)
- writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d
- readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #)
- catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #)
- atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- control0# :: forall {r :: RuntimeRep} a (b :: TYPE r). PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #)
- prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #)
- getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #)
- unmaskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #)
- raiseDivZero# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raiseOverflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raiseUnderflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> b
- catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #)
- atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #)
- atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
- atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #)
- writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d
- readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #)
- newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #)
- atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d
- atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #)
- fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #)
- atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #)
- atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #)
- atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #)
- atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64#
- indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64#
- indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32#
- indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32#
- indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16#
- indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16#
- indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a
- indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double#
- indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float#
- indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr#
- indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word#
- indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int#
- indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char#
- indexWord64OffAddr# :: Addr# -> Int# -> Word64#
- indexInt64OffAddr# :: Addr# -> Int# -> Int64#
- indexWord32OffAddr# :: Addr# -> Int# -> Word32#
- indexInt32OffAddr# :: Addr# -> Int# -> Int32#
- indexWord16OffAddr# :: Addr# -> Int# -> Word16#
- indexInt16OffAddr# :: Addr# -> Int# -> Int16#
- indexWord8OffAddr# :: Addr# -> Int# -> Word8#
- indexInt8OffAddr# :: Addr# -> Int# -> Int8#
- indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
- indexDoubleOffAddr# :: Addr# -> Int# -> Double#
- indexFloatOffAddr# :: Addr# -> Int# -> Float#
- indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- indexWordOffAddr# :: Addr# -> Int# -> Word#
- indexIntOffAddr# :: Addr# -> Int# -> Int#
- indexWideCharOffAddr# :: Addr# -> Int# -> Char#
- indexCharOffAddr# :: Addr# -> Int# -> Char#
- leAddr# :: Addr# -> Addr# -> Int#
- ltAddr# :: Addr# -> Addr# -> Int#
- neAddr# :: Addr# -> Addr# -> Int#
- eqAddr# :: Addr# -> Addr# -> Int#
- geAddr# :: Addr# -> Addr# -> Int#
- gtAddr# :: Addr# -> Addr# -> Int#
- int2Addr# :: Int# -> Addr#
- addr2Int# :: Addr# -> Int#
- remAddr# :: Addr# -> Int# -> Int#
- minusAddr# :: Addr# -> Addr# -> Int#
- plusAddr# :: Addr# -> Int# -> Addr#
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #)
- casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #)
- casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #)
- casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #)
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord64Array# :: ByteArray# -> Int# -> Word64#
- indexInt64Array# :: ByteArray# -> Int# -> Int64#
- indexWord32Array# :: ByteArray# -> Int# -> Word32#
- indexInt32Array# :: ByteArray# -> Int# -> Int32#
- indexWord16Array# :: ByteArray# -> Int# -> Word16#
- indexInt16Array# :: ByteArray# -> Int# -> Int16#
- indexWord8Array# :: ByteArray# -> Int# -> Word8#
- indexInt8Array# :: ByteArray# -> Int# -> Int8#
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexCharArray# :: ByteArray# -> Int# -> Char#
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #)
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- sizeofByteArray# :: ByteArray# -> Int#
- unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- mutableByteArrayContents# :: MutableByteArray# d -> Addr#
- byteArrayContents# :: ByteArray# -> Addr#
- isByteArrayPinned# :: ByteArray# -> Int#
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #)
- cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a
- copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #)
- unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #)
- indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #)
- getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #)
- sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int#
- sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int#
- writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d
- newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #)
- casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #)
- cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a
- copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #)
- unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #)
- indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #)
- sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int#
- sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int#
- writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d
- readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
- fnmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fnmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fnmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fnmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fmaddFloat# :: Float# -> Float# -> Float# -> Float#
- castWord32ToFloat# :: Word32# -> Float#
- castFloatToWord32# :: Float# -> Word32#
- decodeFloat_Int# :: Float# -> (# Int#, Int# #)
- float2Double# :: Float# -> Double#
- powerFloat# :: Float# -> Float# -> Float#
- atanhFloat# :: Float# -> Float#
- acoshFloat# :: Float# -> Float#
- asinhFloat# :: Float# -> Float#
- tanhFloat# :: Float# -> Float#
- coshFloat# :: Float# -> Float#
- sinhFloat# :: Float# -> Float#
- atanFloat# :: Float# -> Float#
- acosFloat# :: Float# -> Float#
- asinFloat# :: Float# -> Float#
- tanFloat# :: Float# -> Float#
- cosFloat# :: Float# -> Float#
- sinFloat# :: Float# -> Float#
- sqrtFloat# :: Float# -> Float#
- log1pFloat# :: Float# -> Float#
- logFloat# :: Float# -> Float#
- expm1Float# :: Float# -> Float#
- expFloat# :: Float# -> Float#
- float2Int# :: Float# -> Int#
- fabsFloat# :: Float# -> Float#
- negateFloat# :: Float# -> Float#
- divideFloat# :: Float# -> Float# -> Float#
- timesFloat# :: Float# -> Float# -> Float#
- minusFloat# :: Float# -> Float# -> Float#
- plusFloat# :: Float# -> Float# -> Float#
- leFloat# :: Float# -> Float# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- gtFloat# :: Float# -> Float# -> Int#
- castWord64ToDouble# :: Word64# -> Double#
- castDoubleToWord64# :: Double# -> Word64#
- decodeDouble_Int64# :: Double# -> (# Int64#, Int# #)
- decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #)
- (**##) :: Double# -> Double# -> Double#
- atanhDouble# :: Double# -> Double#
- acoshDouble# :: Double# -> Double#
- asinhDouble# :: Double# -> Double#
- tanhDouble# :: Double# -> Double#
- coshDouble# :: Double# -> Double#
- sinhDouble# :: Double# -> Double#
- atanDouble# :: Double# -> Double#
- acosDouble# :: Double# -> Double#
- asinDouble# :: Double# -> Double#
- tanDouble# :: Double# -> Double#
- cosDouble# :: Double# -> Double#
- sinDouble# :: Double# -> Double#
- sqrtDouble# :: Double# -> Double#
- log1pDouble# :: Double# -> Double#
- logDouble# :: Double# -> Double#
- expm1Double# :: Double# -> Double#
- expDouble# :: Double# -> Double#
- double2Float# :: Double# -> Float#
- double2Int# :: Double# -> Int#
- fabsDouble# :: Double# -> Double#
- negateDouble# :: Double# -> Double#
- (/##) :: Double# -> Double# -> Double#
- (*##) :: Double# -> Double# -> Double#
- (-##) :: Double# -> Double# -> Double#
- (+##) :: Double# -> Double# -> Double#
- (<=##) :: Double# -> Double# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- (>##) :: Double# -> Double# -> Int#
- narrow32Word# :: Word# -> Word#
- narrow16Word# :: Word# -> Word#
- narrow8Word# :: Word# -> Word#
- narrow32Int# :: Int# -> Int#
- narrow16Int# :: Int# -> Int#
- narrow8Int# :: Int# -> Int#
- bitReverse# :: Word# -> Word#
- bitReverse64# :: Word64# -> Word64#
- bitReverse32# :: Word# -> Word#
- bitReverse16# :: Word# -> Word#
- bitReverse8# :: Word# -> Word#
- byteSwap# :: Word# -> Word#
- byteSwap64# :: Word64# -> Word64#
- byteSwap32# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- ctz# :: Word# -> Word#
- ctz64# :: Word64# -> Word#
- ctz32# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz8# :: Word# -> Word#
- clz# :: Word# -> Word#
- clz64# :: Word64# -> Word#
- clz32# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz8# :: Word# -> Word#
- pext# :: Word# -> Word# -> Word#
- pext64# :: Word64# -> Word64# -> Word64#
- pext32# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext8# :: Word# -> Word# -> Word#
- pdep# :: Word# -> Word# -> Word#
- pdep64# :: Word64# -> Word64# -> Word64#
- pdep32# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep8# :: Word# -> Word# -> Word#
- popCnt# :: Word# -> Word#
- popCnt64# :: Word64# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt8# :: Word# -> Word#
- leWord# :: Word# -> Word# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- neWord# :: Word# -> Word# -> Int#
- eqWord# :: Word# -> Word# -> Int#
- geWord# :: Word# -> Word# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- word2Int# :: Word# -> Int#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- not# :: Word# -> Word#
- xor# :: Word# -> Word# -> Word#
- or# :: Word# -> Word# -> Word#
- and# :: Word# -> Word# -> Word#
- quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
- quotRemWord# :: Word# -> Word# -> (# Word#, Word# #)
- remWord# :: Word# -> Word# -> Word#
- quotWord# :: Word# -> Word# -> Word#
- timesWord2# :: Word# -> Word# -> (# Word#, Word# #)
- timesWord# :: Word# -> Word# -> Word#
- minusWord# :: Word# -> Word# -> Word#
- plusWord2# :: Word# -> Word# -> (# Word#, Word# #)
- subWordC# :: Word# -> Word# -> (# Word#, Int# #)
- addWordC# :: Word# -> Word# -> (# Word#, Int# #)
- plusWord# :: Word# -> Word# -> Word#
- uncheckedIShiftRL# :: Int# -> Int# -> Int#
- uncheckedIShiftRA# :: Int# -> Int# -> Int#
- uncheckedIShiftL# :: Int# -> Int# -> Int#
- word2Double# :: Word# -> Double#
- word2Float# :: Word# -> Float#
- int2Double# :: Int# -> Double#
- int2Float# :: Int# -> Float#
- int2Word# :: Int# -> Word#
- chr# :: Int# -> Char#
- (<=#) :: Int# -> Int# -> Int#
- (<#) :: Int# -> Int# -> Int#
- (/=#) :: Int# -> Int# -> Int#
- (==#) :: Int# -> Int# -> Int#
- (>=#) :: Int# -> Int# -> Int#
- (>#) :: Int# -> Int# -> Int#
- subIntC# :: Int# -> Int# -> (# Int#, Int# #)
- addIntC# :: Int# -> Int# -> (# Int#, Int# #)
- negateInt# :: Int# -> Int#
- notI# :: Int# -> Int#
- xorI# :: Int# -> Int# -> Int#
- orI# :: Int# -> Int# -> Int#
- andI# :: Int# -> Int# -> Int#
- quotRemInt# :: Int# -> Int# -> (# Int#, Int# #)
- remInt# :: Int# -> Int# -> Int#
- quotInt# :: Int# -> Int# -> Int#
- mulIntMayOflo# :: Int# -> Int# -> Int#
- timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #)
- (*#) :: Int# -> Int# -> Int#
- (-#) :: Int# -> Int# -> Int#
- (+#) :: Int# -> Int# -> Int#
- neWord64# :: Word64# -> Word64# -> Int#
- ltWord64# :: Word64# -> Word64# -> Int#
- leWord64# :: Word64# -> Word64# -> Int#
- gtWord64# :: Word64# -> Word64# -> Int#
- geWord64# :: Word64# -> Word64# -> Int#
- eqWord64# :: Word64# -> Word64# -> Int#
- word64ToInt64# :: Word64# -> Int64#
- uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftL64# :: Word64# -> Int# -> Word64#
- not64# :: Word64# -> Word64#
- xor64# :: Word64# -> Word64# -> Word64#
- or64# :: Word64# -> Word64# -> Word64#
- and64# :: Word64# -> Word64# -> Word64#
- remWord64# :: Word64# -> Word64# -> Word64#
- quotWord64# :: Word64# -> Word64# -> Word64#
- timesWord64# :: Word64# -> Word64# -> Word64#
- subWord64# :: Word64# -> Word64# -> Word64#
- plusWord64# :: Word64# -> Word64# -> Word64#
- wordToWord64# :: Word# -> Word64#
- word64ToWord# :: Word64# -> Word#
- neInt64# :: Int64# -> Int64# -> Int#
- ltInt64# :: Int64# -> Int64# -> Int#
- leInt64# :: Int64# -> Int64# -> Int#
- gtInt64# :: Int64# -> Int64# -> Int#
- geInt64# :: Int64# -> Int64# -> Int#
- eqInt64# :: Int64# -> Int64# -> Int#
- int64ToWord64# :: Int64# -> Word64#
- uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- remInt64# :: Int64# -> Int64# -> Int64#
- quotInt64# :: Int64# -> Int64# -> Int64#
- timesInt64# :: Int64# -> Int64# -> Int64#
- subInt64# :: Int64# -> Int64# -> Int64#
- plusInt64# :: Int64# -> Int64# -> Int64#
- negateInt64# :: Int64# -> Int64#
- intToInt64# :: Int# -> Int64#
- int64ToInt# :: Int64# -> Int#
- neWord32# :: Word32# -> Word32# -> Int#
- ltWord32# :: Word32# -> Word32# -> Int#
- leWord32# :: Word32# -> Word32# -> Int#
- gtWord32# :: Word32# -> Word32# -> Int#
- geWord32# :: Word32# -> Word32# -> Int#
- eqWord32# :: Word32# -> Word32# -> Int#
- word32ToInt32# :: Word32# -> Int32#
- uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
- uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
- notWord32# :: Word32# -> Word32#
- xorWord32# :: Word32# -> Word32# -> Word32#
- orWord32# :: Word32# -> Word32# -> Word32#
- andWord32# :: Word32# -> Word32# -> Word32#
- quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #)
- remWord32# :: Word32# -> Word32# -> Word32#
- quotWord32# :: Word32# -> Word32# -> Word32#
- timesWord32# :: Word32# -> Word32# -> Word32#
- subWord32# :: Word32# -> Word32# -> Word32#
- plusWord32# :: Word32# -> Word32# -> Word32#
- wordToWord32# :: Word# -> Word32#
- word32ToWord# :: Word32# -> Word#
- neInt32# :: Int32# -> Int32# -> Int#
- ltInt32# :: Int32# -> Int32# -> Int#
- leInt32# :: Int32# -> Int32# -> Int#
- gtInt32# :: Int32# -> Int32# -> Int#
- geInt32# :: Int32# -> Int32# -> Int#
- eqInt32# :: Int32# -> Int32# -> Int#
- int32ToWord32# :: Int32# -> Word32#
- uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
- quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
- remInt32# :: Int32# -> Int32# -> Int32#
- quotInt32# :: Int32# -> Int32# -> Int32#
- timesInt32# :: Int32# -> Int32# -> Int32#
- subInt32# :: Int32# -> Int32# -> Int32#
- plusInt32# :: Int32# -> Int32# -> Int32#
- negateInt32# :: Int32# -> Int32#
- intToInt32# :: Int# -> Int32#
- int32ToInt# :: Int32# -> Int#
- neWord16# :: Word16# -> Word16# -> Int#
- ltWord16# :: Word16# -> Word16# -> Int#
- leWord16# :: Word16# -> Word16# -> Int#
- gtWord16# :: Word16# -> Word16# -> Int#
- geWord16# :: Word16# -> Word16# -> Int#
- eqWord16# :: Word16# -> Word16# -> Int#
- word16ToInt16# :: Word16# -> Int16#
- uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
- uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
- notWord16# :: Word16# -> Word16#
- xorWord16# :: Word16# -> Word16# -> Word16#
- orWord16# :: Word16# -> Word16# -> Word16#
- andWord16# :: Word16# -> Word16# -> Word16#
- quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #)
- remWord16# :: Word16# -> Word16# -> Word16#
- quotWord16# :: Word16# -> Word16# -> Word16#
- timesWord16# :: Word16# -> Word16# -> Word16#
- subWord16# :: Word16# -> Word16# -> Word16#
- plusWord16# :: Word16# -> Word16# -> Word16#
- wordToWord16# :: Word# -> Word16#
- word16ToWord# :: Word16# -> Word#
- neInt16# :: Int16# -> Int16# -> Int#
- ltInt16# :: Int16# -> Int16# -> Int#
- leInt16# :: Int16# -> Int16# -> Int#
- gtInt16# :: Int16# -> Int16# -> Int#
- geInt16# :: Int16# -> Int16# -> Int#
- eqInt16# :: Int16# -> Int16# -> Int#
- int16ToWord16# :: Int16# -> Word16#
- uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
- quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
- remInt16# :: Int16# -> Int16# -> Int16#
- quotInt16# :: Int16# -> Int16# -> Int16#
- timesInt16# :: Int16# -> Int16# -> Int16#
- subInt16# :: Int16# -> Int16# -> Int16#
- plusInt16# :: Int16# -> Int16# -> Int16#
- negateInt16# :: Int16# -> Int16#
- intToInt16# :: Int# -> Int16#
- int16ToInt# :: Int16# -> Int#
- neWord8# :: Word8# -> Word8# -> Int#
- ltWord8# :: Word8# -> Word8# -> Int#
- leWord8# :: Word8# -> Word8# -> Int#
- gtWord8# :: Word8# -> Word8# -> Int#
- geWord8# :: Word8# -> Word8# -> Int#
- eqWord8# :: Word8# -> Word8# -> Int#
- word8ToInt8# :: Word8# -> Int8#
- uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
- uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
- notWord8# :: Word8# -> Word8#
- xorWord8# :: Word8# -> Word8# -> Word8#
- orWord8# :: Word8# -> Word8# -> Word8#
- andWord8# :: Word8# -> Word8# -> Word8#
- quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #)
- remWord8# :: Word8# -> Word8# -> Word8#
- quotWord8# :: Word8# -> Word8# -> Word8#
- timesWord8# :: Word8# -> Word8# -> Word8#
- subWord8# :: Word8# -> Word8# -> Word8#
- plusWord8# :: Word8# -> Word8# -> Word8#
- wordToWord8# :: Word# -> Word8#
- word8ToWord# :: Word8# -> Word#
- neInt8# :: Int8# -> Int8# -> Int#
- ltInt8# :: Int8# -> Int8# -> Int#
- leInt8# :: Int8# -> Int8# -> Int#
- gtInt8# :: Int8# -> Int8# -> Int#
- geInt8# :: Int8# -> Int8# -> Int#
- eqInt8# :: Int8# -> Int8# -> Int#
- int8ToWord8# :: Int8# -> Word8#
- uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
- quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
- remInt8# :: Int8# -> Int8# -> Int8#
- quotInt8# :: Int8# -> Int8# -> Int8#
- timesInt8# :: Int8# -> Int8# -> Int8#
- subInt8# :: Int8# -> Int8# -> Int8#
- plusInt8# :: Int8# -> Int8# -> Int8#
- negateInt8# :: Int8# -> Int8#
- intToInt8# :: Int# -> Int8#
- int8ToInt# :: Int8# -> Int#
- ord# :: Char# -> Int#
- leChar# :: Char# -> Char# -> Int#
- ltChar# :: Char# -> Char# -> Int#
- neChar# :: Char# -> Char# -> Int#
- eqChar# :: Char# -> Char# -> Int#
- geChar# :: Char# -> Char# -> Int#
- gtChar# :: Char# -> Char# -> Int#
- rightSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {s :: RuntimeRep} {n :: Multiplicity} {o :: Multiplicity} (a :: TYPE q) (b :: TYPE r) (c :: TYPE s). (a %n -> b %o -> c) -> b %o -> a %n -> c
- leftSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {n :: Multiplicity} (a :: TYPE q) (b :: TYPE r). (a %n -> b) -> a %n -> b
- proxy# :: forall {k} (a :: k). Proxy# a
- seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b
- nullAddr# :: Addr#
- void# :: (# #)
- realWorld# :: State# RealWorld
- module GHC.Prim.Ext
- runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- reallyUnsafePtrEquality :: a -> a -> Int#
- unsafePtrEquality# :: forall (a :: UnliftedType) (b :: UnliftedType). a -> b -> Int#
- eqStableName# :: forall {k :: Levity} {l :: Levity} (a :: TYPE ('BoxedRep k)) (b :: TYPE ('BoxedRep l)). StableName# a -> StableName# b -> Int#
- sameArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Array# a -> Int#
- sameMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutableArray# s a -> MutableArray# s a -> Int#
- sameSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> SmallArray# a -> Int#
- sameSmallMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). SmallMutableArray# s a -> SmallMutableArray# s a -> Int#
- sameByteArray# :: ByteArray# -> ByteArray# -> Int#
- sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int#
- sameMVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MVar# s a -> MVar# s a -> Int#
- sameMutVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutVar# s a -> MutVar# s a -> Int#
- sameTVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). TVar# s a -> TVar# s a -> Int#
- sameIOPort# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). IOPort# s a -> IOPort# s a -> Int#
- samePromptTag# :: PromptTag# a -> PromptTag# a -> Int#
- atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #)
- resizeSmallMutableArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> (# State# s, SmallMutableArray# s a #)
- build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- class IsList l where
- newtype Down a = Down {
- getDown :: a
- groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
- the :: Eq a => [a] -> a
- class IsString a where
- fromString :: String -> a
- unpackCString# :: Addr# -> [Char]
- unpackAppendCString# :: Addr# -> [Char] -> [Char]
- unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a
- unpackCStringUtf8# :: Addr# -> [Char]
- unpackNBytes# :: Addr# -> Int# -> [Char]
- cstringLength# :: Addr# -> Int#
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- traceEvent :: String -> IO ()
- currentCallStack :: IO [String]
- inline :: a -> a
- noinline :: a -> a
- lazy :: a -> a
- oneShot :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b
- considerAccessible :: Bool
- data SpecConstrAnnotation
- data SPEC
- coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
- unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b
- class WithDict cls meth where
- withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r
- class DataToTag (a :: TYPE ('BoxedRep lev)) where
- dataToTag# :: a -> Int#
- maxTupleSize :: Int
Pointer types
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
The type a
will often be an instance of class
Storable
which provides the marshalling operations.
However this is not essential, and you can provide your own operations
to access the pointer. For example you might write small foreign
functions to get or set the fields of a C struct
.
Instances
Generic1 (URec (Ptr ()) :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Data a => Data (Ptr a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source # toConstr :: Ptr a -> Constr Source # dataTypeOf :: Ptr a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # | |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Storable (Ptr a) Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Ptr a -> Int Source # alignment :: Ptr a -> Int Source # peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source # pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source # pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source # | |||||
Show (Ptr a) Source # | Since: base-2.1 | ||||
Eq (Ptr a) Source # | Since: base-2.1 | ||||
Ord (Ptr a) Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Ptr | |||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec (Ptr ()) p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |||||
data URec (Ptr ()) (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec (Ptr ()) :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
A value of type
is a pointer to a function callable
from foreign code. The type FunPtr
aa
will normally be a foreign type,
a function type with zero or more arguments where
- the argument types are marshallable foreign types,
i.e.
Char
,Int
,Double
,Float
,Bool
,Int8
,Int16
,Int32
,Int64
,Word8
,Word16
,Word32
,Word64
,
,Ptr
a
,FunPtr
a
or a renaming of any of these usingStablePtr
anewtype
. - the return type is either a marshallable foreign type or has the form
whereIO
tt
is a marshallable foreign type or()
.
A value of type
may be a pointer to a foreign function,
either returned by another foreign function or imported with a
a static address import likeFunPtr
a
foreign import ccall "stdlib.h &free" p_free :: FunPtr (Ptr a -> IO ())
or a pointer to a Haskell function created using a wrapper stub
declared to produce a FunPtr
of the correct type. For example:
type Compare = Int -> Int -> Bool foreign import ccall "wrapper" mkCompare :: Compare -> IO (FunPtr Compare)
Calls to wrapper stubs like mkCompare
allocate storage, which
should be released with freeHaskellFunPtr
when no
longer required.
To convert FunPtr
values to corresponding Haskell functions, one
can define a dynamic stub for the specific foreign type, e.g.
type IntFunction = CInt -> IO () foreign import ccall "dynamic" mkFun :: FunPtr IntFunction -> IntFunction
Instances
Storable (FunPtr a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: FunPtr a -> Int Source # alignment :: FunPtr a -> Int Source # peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) Source # pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source # pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source # | |
Show (FunPtr a) Source # | Since: base-2.1 |
Eq (FunPtr a) Source # | |
Ord (FunPtr a) Source # | |
Defined in GHC.Internal.Ptr |
Other primitive types
Instances
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
Data Float Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source # toConstr :: Float -> Constr Source # dataTypeOf :: Float -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source # gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # | |||||
Enum Float Source # |
List generators have extremely peculiar behavior, mandated by Haskell Report 2010:
Since: base-2.1 | ||||
Defined in GHC.Internal.Float succ :: Float -> Float Source # pred :: Float -> Float Source # toEnum :: Int -> Float Source # fromEnum :: Float -> Int Source # enumFrom :: Float -> [Float] Source # enumFromThen :: Float -> Float -> [Float] Source # enumFromTo :: Float -> Float -> [Float] Source # enumFromThenTo :: Float -> Float -> Float -> [Float] Source # | |||||
Floating Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float exp :: Float -> Float Source # log :: Float -> Float Source # sqrt :: Float -> Float Source # (**) :: Float -> Float -> Float Source # logBase :: Float -> Float -> Float Source # sin :: Float -> Float Source # cos :: Float -> Float Source # tan :: Float -> Float Source # asin :: Float -> Float Source # acos :: Float -> Float Source # atan :: Float -> Float Source # sinh :: Float -> Float Source # cosh :: Float -> Float Source # tanh :: Float -> Float Source # asinh :: Float -> Float Source # acosh :: Float -> Float Source # atanh :: Float -> Float Source # log1p :: Float -> Float Source # expm1 :: Float -> Float Source # | |||||
RealFloat Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float floatRadix :: Float -> Integer Source # floatDigits :: Float -> Int Source # floatRange :: Float -> (Int, Int) Source # decodeFloat :: Float -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Float Source # exponent :: Float -> Int Source # significand :: Float -> Float Source # scaleFloat :: Int -> Float -> Float Source # isNaN :: Float -> Bool Source # isInfinite :: Float -> Bool Source # isDenormalized :: Float -> Bool Source # isNegativeZero :: Float -> Bool Source # | |||||
Storable Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Float -> Int Source # alignment :: Float -> Int Source # peekElemOff :: Ptr Float -> Int -> IO Float Source # pokeElemOff :: Ptr Float -> Int -> Float -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Float Source # pokeByteOff :: Ptr b -> Int -> Float -> IO () Source # | |||||
Num Float Source # | This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:
Since: base-2.1 | ||||
Read Float Source # | Since: base-2.1 | ||||
Fractional Float Source # | This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.
Since: base-2.1 | ||||
Real Float Source # | Beware that
Since: base-2.1 | ||||
Defined in GHC.Internal.Float toRational :: Float -> Rational Source # | |||||
RealFrac Float Source # | Beware that results for non-finite arguments are garbage:
and get even more non-sensical if you ask for Since: base-2.1 | ||||
Show Float Source # | Since: base-2.1 | ||||
Eq Float | Note that due to the presence of
Also note that
| ||||
Ord Float | See | ||||
Defined in GHC.Classes | |||||
Generic1 (URec Float :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Float p) Source # | |||||
Eq (URec Float p) Source # | |||||
Ord (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |||||
data URec Float (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Float :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics |
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Bits Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Bits (.&.) :: Int -> Int -> Int Source # (.|.) :: Int -> Int -> Int Source # xor :: Int -> Int -> Int Source # complement :: Int -> Int Source # shift :: Int -> Int -> Int Source # rotate :: Int -> Int -> Int Source # setBit :: Int -> Int -> Int Source # clearBit :: Int -> Int -> Int Source # complementBit :: Int -> Int -> Int Source # testBit :: Int -> Int -> Bool Source # bitSizeMaybe :: Int -> Maybe Int Source # bitSize :: Int -> Int Source # isSigned :: Int -> Bool Source # shiftL :: Int -> Int -> Int Source # unsafeShiftL :: Int -> Int -> Int Source # shiftR :: Int -> Int -> Int Source # unsafeShiftR :: Int -> Int -> Int Source # rotateL :: Int -> Int -> Int Source # | |||||
FiniteBits Int Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Bits finiteBitSize :: Int -> Int Source # countLeadingZeros :: Int -> Int Source # countTrailingZeros :: Int -> Int Source # | |||||
Data Int Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source # toConstr :: Int -> Constr Source # dataTypeOf :: Int -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) Source # gmapT :: (forall b. Data b => b -> b) -> Int -> Int Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # | |||||
Bounded Int Source # | Since: base-2.1 | ||||
Enum Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Enum | |||||
Storable Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable | |||||
Ix Int Source # | Since: base-2.1 | ||||
Num Int Source # | Since: base-2.1 | ||||
Read Int Source # | Since: base-2.1 | ||||
Integral Int Source # | Since: base-2.0.1 | ||||
Real Int Source # | Since: base-2.0.1 | ||||
Defined in GHC.Internal.Real toRational :: Int -> Rational Source # | |||||
Show Int Source # | Since: base-2.1 | ||||
Eq Int | |||||
Ord Int | |||||
Generic1 (URec Int :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Int p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Int p -> URec Int p -> Ordering Source # (<) :: URec Int p -> URec Int p -> Bool Source # (<=) :: URec Int p -> URec Int p -> Bool Source # (>) :: URec Int p -> URec Int p -> Bool Source # (>=) :: URec Int p -> URec Int p -> Bool Source # | |||||
data URec Int (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Int :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
data TYPE (a :: RuntimeRep) Source #
Instances
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Identity Source # | |||||
Defined in GHC.Internal.Data.Functor.Identity
| |||||
Generic1 First Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Last Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 ZipList Source # | |||||
Defined in GHC.Internal.Functor.ZipList
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Solo Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source # | Since: base-3.0 | ||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Category (->) Source # | Since: base-3.0 | ||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Control.Arrow
| |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source # to1 :: Rep1 ((,,,,,,,,) a b c d e f g h) a0 -> (a, b, c, d, e, f, g, h, a0) Source # | |||||
Generic1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source # to1 :: Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 -> (a, b, c, d, e, f, g, h, i, a0) Source # | |||||
Generic1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, a0) -> Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 Source # to1 :: Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 -> (a, b, c, d, e, f, g, h, i, j, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, a0) -> Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 -> (a, b, c, d, e, f, g, h, i, j, k, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, a0) -> Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) Source # | |||||
Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Alternative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Applicative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Foldable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Proxy m -> m Source # foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source # foldr :: (a -> b -> b) -> b -> Proxy a -> b Source # foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source # foldl :: (b -> a -> b) -> b -> Proxy a -> b Source # foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source # foldr1 :: (a -> a -> a) -> Proxy a -> a Source # foldl1 :: (a -> a -> a) -> Proxy a -> a Source # toList :: Proxy a -> [a] Source # null :: Proxy a -> Bool Source # length :: Proxy a -> Int Source # elem :: Eq a => a -> Proxy a -> Bool Source # maximum :: Ord a => Proxy a -> a Source # minimum :: Ord a => Proxy a -> a Source # | |||||
Foldable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => U1 m -> m Source # foldMap :: Monoid m => (a -> m) -> U1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> U1 a -> m Source # foldr :: (a -> b -> b) -> b -> U1 a -> b Source # foldr' :: (a -> b -> b) -> b -> U1 a -> b Source # foldl :: (b -> a -> b) -> b -> U1 a -> b Source # foldl' :: (b -> a -> b) -> b -> U1 a -> b Source # foldr1 :: (a -> a -> a) -> U1 a -> a Source # foldl1 :: (a -> a -> a) -> U1 a -> a Source # toList :: U1 a -> [a] Source # length :: U1 a -> Int Source # elem :: Eq a => a -> U1 a -> Bool Source # maximum :: Ord a => U1 a -> a Source # minimum :: Ord a => U1 a -> a Source # | |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |||||
Foldable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => V1 m -> m Source # foldMap :: Monoid m => (a -> m) -> V1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> V1 a -> m Source # foldr :: (a -> b -> b) -> b -> V1 a -> b Source # foldr' :: (a -> b -> b) -> b -> V1 a -> b Source # foldl :: (b -> a -> b) -> b -> V1 a -> b Source # foldl' :: (b -> a -> b) -> b -> V1 a -> b Source # foldr1 :: (a -> a -> a) -> V1 a -> a Source # foldl1 :: (a -> a -> a) -> V1 a -> a Source # toList :: V1 a -> [a] Source # length :: V1 a -> Int Source # elem :: Eq a => a -> V1 a -> Bool Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # | |||||
Traversable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Alternative f => Alternative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Alternative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics empty :: Generically1 f a Source # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # some :: Generically1 f a -> Generically1 f [a] Source # many :: Generically1 f a -> Generically1 f [a] Source # | |||||
Alternative f => Alternative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Monoid m => Applicative (Const m :: Type -> Type) Source # | Since: base-2.0.1 | ||||
Defined in GHC.Internal.Data.Functor.Const | |||||
Applicative f => Applicative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Applicative f => Applicative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics pure :: a -> Generically1 f a Source # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source # | |||||
Applicative f => Applicative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (Const m :: Type -> Type) Source # | Since: base-2.1 | ||||
Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 | ||||
Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |||||
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 | ||||
Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 | ||||
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadFail f => MonadFail (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadFix f => MonadFix (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Data t => Data (Proxy t) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) Source # toConstr :: Proxy t -> Constr Source # dataTypeOf :: Proxy t -> DataType Source # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) Source # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # | |||||
Data p => Data (U1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) Source # toConstr :: U1 p -> Constr Source # dataTypeOf :: U1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # | |||||
Data p => Data (V1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) Source # toConstr :: V1 p -> Constr Source # dataTypeOf :: V1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # | |||||
Foldable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 Source # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldr :: (a -> b -> b) -> b -> Const m a -> b Source # foldr' :: (a -> b -> b) -> b -> Const m a -> b Source # foldl :: (b -> a -> b) -> b -> Const m a -> b Source # foldl' :: (b -> a -> b) -> b -> Const m a -> b Source # foldr1 :: (a -> a -> a) -> Const m a -> a Source # foldl1 :: (a -> a -> a) -> Const m a -> a Source # toList :: Const m a -> [a] Source # null :: Const m a -> Bool Source # length :: Const m a -> Int Source # elem :: Eq a => a -> Const m a -> Bool Source # maximum :: Ord a => Const m a -> a Source # minimum :: Ord a => Const m a -> a Source # | |||||
Foldable f => Foldable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Ap f m -> m Source # foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m Source # foldr :: (a -> b -> b) -> b -> Ap f a -> b Source # foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source # foldl :: (b -> a -> b) -> b -> Ap f a -> b Source # foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source # foldr1 :: (a -> a -> a) -> Ap f a -> a Source # foldl1 :: (a -> a -> a) -> Ap f a -> a Source # toList :: Ap f a -> [a] Source # null :: Ap f a -> Bool Source # length :: Ap f a -> Int Source # elem :: Eq a => a -> Ap f a -> Bool Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # | |||||
Foldable f => Foldable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |||||
Foldable f => Foldable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Rec1 f m -> m Source # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source # foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source # toList :: Rec1 f a -> [a] Source # null :: Rec1 f a -> Bool Source # length :: Rec1 f a -> Int Source # elem :: Eq a => a -> Rec1 f a -> Bool Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # | |||||
Traversable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Monoid c => Applicative (K1 i c :: Type -> Type) Source # | Since: base-4.12.0.0 | ||||
(Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Monoid a) => Monoid (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Monoid (Alt f a) Source # | Since: base-4.8.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Semigroup (Alt f a) Source # | Since: base-4.9.0.0 | ||||
(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) Source # toConstr :: Ap f a -> Constr Source # dataTypeOf :: Ap f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # | |||||
(Data (f a), Data a, Typeable f) => Data (Alt f a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |||||
(Coercible a b, Data a, Data b) => Data (Coercion a b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Coercion a b -> c (Coercion a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion a b) Source # toConstr :: Coercion a b -> Constr Source # dataTypeOf :: Coercion a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Coercion a b -> Coercion a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Coercion a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # | |||||
(a ~ b, Data a) => Data (a :~: b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) Source # toConstr :: (a :~: b) -> Constr Source # dataTypeOf :: (a :~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # | |||||
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) Source # toConstr :: Rec1 f p -> Constr Source # dataTypeOf :: Rec1 f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) Source # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # | |||||
(Foldable f, Foldable g) => Foldable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :*: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source # toList :: (f :*: g) a -> [a] Source # null :: (f :*: g) a -> Bool Source # length :: (f :*: g) a -> Int Source # elem :: Eq a => a -> (f :*: g) a -> Bool Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # | |||||
(Foldable f, Foldable g) => Foldable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :+: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source # toList :: (f :+: g) a -> [a] Source # null :: (f :+: g) a -> Bool Source # length :: (f :+: g) a -> Int Source # elem :: Eq a => a -> (f :+: g) a -> Bool Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # | |||||
Foldable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => K1 i c m -> m Source # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldr1 :: (a -> a -> a) -> K1 i c a -> a Source # foldl1 :: (a -> a -> a) -> K1 i c a -> a Source # toList :: K1 i c a -> [a] Source # null :: K1 i c a -> Bool Source # length :: K1 i c a -> Int Source # elem :: Eq a => a -> K1 i c a -> Bool Source # maximum :: Ord a => K1 i c a -> a Source # minimum :: Ord a => K1 i c a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Applicative f, Bounded a) => Bounded (Ap f a) Source # | Since: base-4.12.0.0 | ||||
(Applicative f, Num a) => Num (Ap f a) Source # | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
(Alternative f, Applicative g) => Alternative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Alternative f => Alternative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Applicative f => Applicative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
(Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadFix f => MonadFix (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) Source # toConstr :: (f :*: g) p -> Constr Source # dataTypeOf :: (f :*: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # | |||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) Source # toConstr :: (f :+: g) p -> Constr Source # dataTypeOf :: (f :+: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # | |||||
(Typeable i, Data p, Data c) => Data (K1 i c p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) Source # toConstr :: K1 i c p -> Constr Source # dataTypeOf :: K1 i c p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) Source # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # | |||||
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :.: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source # toList :: (f :.: g) a -> [a] Source # null :: (f :.: g) a -> Bool Source # length :: (f :.: g) a -> Int Source # elem :: Eq a => a -> (f :.: g) a -> Bool Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # | |||||
Foldable f => Foldable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => M1 i c f m -> m Source # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source # foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source # toList :: M1 i c f a -> [a] Source # null :: M1 i c f a -> Bool Source # length :: M1 i c f a -> Int Source # elem :: Eq a => a -> M1 i c f a -> Bool Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) Source # toConstr :: (f :.: g) p -> Constr Source # dataTypeOf :: (f :.: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # | |||||
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) Source # toConstr :: M1 i c f p -> Constr Source # dataTypeOf :: M1 i c f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) Source # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # | |||||
type Rep1 NonEmpty Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 Identity Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
type Rep1 First Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Last Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Down Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Dual Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Sum Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 ZipList Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Functor.ZipList | |||||
type Rep1 Par1 Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Maybe Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Solo Source # | Since: base-4.15 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 (Either a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 ((,) a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,) a :: Type -> Type) = D1 ('MetaData "Tuple2" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 (Kleisli m a :: Type -> Type) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Control.Arrow | |||||
type Rep1 ((,,) a b :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,) a b :: Type -> Type) = D1 ('MetaData "Tuple3" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,) a b c :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,) a b c :: Type -> Type) = D1 ('MetaData "Tuple4" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,,) a b c d :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,) a b c d :: Type -> Type) = D1 ('MetaData "Tuple5" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 (f :.: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 ((,,,,,) a b c d e :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,) a b c d e :: Type -> Type) = D1 ('MetaData "Tuple6" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) = D1 ('MetaData "Tuple7" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) = D1 ('MetaData "Tuple8" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) = D1 ('MetaData "Tuple9" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) = D1 ('MetaData "Tuple10" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) = D1 ('MetaData "Tuple11" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) = D1 ('MetaData "Tuple12" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "Tuple13" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "Tuple14" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "Tuple15" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) |
data CONSTRAINT (a :: RuntimeRep) Source #
Data type Dict
provides a simple way to wrap up a (lifted)
constraint as a type
a => MkDictBox |
Instances
Bits Bool Source # | Interpret Since: base-4.7.0.0 |
Defined in GHC.Internal.Bits (.&.) :: Bool -> Bool -> Bool Source # (.|.) :: Bool -> Bool -> Bool Source # xor :: Bool -> Bool -> Bool Source # complement :: Bool -> Bool Source # shift :: Bool -> Int -> Bool Source # rotate :: Bool -> Int -> Bool Source # setBit :: Bool -> Int -> Bool Source # clearBit :: Bool -> Int -> Bool Source # complementBit :: Bool -> Int -> Bool Source # testBit :: Bool -> Int -> Bool Source # bitSizeMaybe :: Bool -> Maybe Int Source # bitSize :: Bool -> Int Source # isSigned :: Bool -> Bool Source # shiftL :: Bool -> Int -> Bool Source # unsafeShiftL :: Bool -> Int -> Bool Source # shiftR :: Bool -> Int -> Bool Source # unsafeShiftR :: Bool -> Int -> Bool Source # rotateL :: Bool -> Int -> Bool Source # | |
FiniteBits Bool Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Bits finiteBitSize :: Bool -> Int Source # countLeadingZeros :: Bool -> Int Source # countTrailingZeros :: Bool -> Int Source # | |
Data Bool Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool Source # toConstr :: Bool -> Constr Source # dataTypeOf :: Bool -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) Source # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # | |
Bounded Bool Source # | Since: base-2.1 |
Enum Bool Source # | Since: base-2.1 |
Storable Bool Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: Bool -> Int Source # alignment :: Bool -> Int Source # peekElemOff :: Ptr Bool -> Int -> IO Bool Source # pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Bool Source # pokeByteOff :: Ptr b -> Int -> Bool -> IO () Source # | |
Generic Bool Source # | |
Defined in GHC.Internal.Generics | |
Ix Bool Source # | Since: base-2.1 |
Read Bool Source # | Since: base-2.1 |
Show Bool Source # | Since: base-2.1 |
Eq Bool | |
Ord Bool | |
type Rep Bool Source # | Since: base-4.6.0.0 |
The character type Char
represents Unicode codespace
and its elements are code points as in definitions
D9 and D10 of the Unicode Standard.
Character literals in Haskell are single-quoted: 'Q'
, 'Я'
or 'Ω'
.
To represent a single quote itself use '\''
, and to represent a backslash
use '\\'
. The full grammar can be found in the section 2.6 of the
Haskell 2010 Language Report.
To specify a character by its code point one can use decimal, hexadecimal
or octal notation: '\65'
, '\x41'
and '\o101'
are all alternative forms
of 'A'
. The largest code point is '\x10ffff'
.
There is a special escape syntax for ASCII control characters:
Escape | Alternatives | Meaning |
---|---|---|
'\NUL' | '\0' | null character |
'\SOH' | '\1' | start of heading |
'\STX' | '\2' | start of text |
'\ETX' | '\3' | end of text |
'\EOT' | '\4' | end of transmission |
'\ENQ' | '\5' | enquiry |
'\ACK' | '\6' | acknowledge |
'\BEL' | '\7' , '\a' | bell (alert) |
'\BS' | '\8' , '\b' | backspace |
'\HT' | '\9' , '\t' | horizontal tab |
'\LF' | '\10' , '\n' | line feed (new line) |
'\VT' | '\11' , '\v' | vertical tab |
'\FF' | '\12' , '\f' | form feed |
'\CR' | '\13' , '\r' | carriage return |
'\SO' | '\14' | shift out |
'\SI' | '\15' | shift in |
'\DLE' | '\16' | data link escape |
'\DC1' | '\17' | device control 1 |
'\DC2' | '\18' | device control 2 |
'\DC3' | '\19' | device control 3 |
'\DC4' | '\20' | device control 4 |
'\NAK' | '\21' | negative acknowledge |
'\SYN' | '\22' | synchronous idle |
'\ETB' | '\23' | end of transmission block |
'\CAN' | '\24' | cancel |
'\EM' | '\25' | end of medium |
'\SUB' | '\26' | substitute |
'\ESC' | '\27' | escape |
'\FS' | '\28' | file separator |
'\GS' | '\29' | group separator |
'\RS' | '\30' | record separator |
'\US' | '\31' | unit separator |
'\SP' | '\32' , ' ' | space |
'\DEL' | '\127' | delete |
Instances
Data Char Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source # toConstr :: Char -> Constr Source # dataTypeOf :: Char -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) Source # gmapT :: (forall b. Data b => b -> b) -> Char -> Char Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # | |||||
Bounded Char Source # | Since: base-2.1 | ||||
Enum Char Source # | Since: base-2.1 | ||||
Storable Char Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Char -> Int Source # alignment :: Char -> Int Source # peekElemOff :: Ptr Char -> Int -> IO Char Source # pokeElemOff :: Ptr Char -> Int -> Char -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Char Source # pokeByteOff :: Ptr b -> Int -> Char -> IO () Source # | |||||
Ix Char Source # | Since: base-2.1 | ||||
Read Char Source # | Since: base-2.1 | ||||
Show Char Source # | Since: base-2.1 | ||||
Eq Char | |||||
Ord Char | |||||
TestCoercion SChar Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
TestEquality SChar Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
Generic1 (URec Char :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Char p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Char p -> URec Char p -> Ordering Source # (<) :: URec Char p -> URec Char p -> Bool Source # (<=) :: URec Char p -> URec Char p -> Bool Source # (>) :: URec Char p -> URec Char p -> Bool Source # (>=) :: URec Char p -> URec Char p -> Bool Source # | |||||
data URec Char (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Compare (a :: Char) (b :: Char) Source # | |||||
Defined in GHC.Internal.Data.Type.Ord | |||||
type Rep1 (URec Char :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Data Double Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source # toConstr :: Double -> Constr Source # dataTypeOf :: Double -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source # gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # | |||||
Enum Double Source # |
List generators have extremely peculiar behavior, mandated by Haskell Report 2010:
Since: base-2.1 | ||||
Defined in GHC.Internal.Float succ :: Double -> Double Source # pred :: Double -> Double Source # toEnum :: Int -> Double Source # fromEnum :: Double -> Int Source # enumFrom :: Double -> [Double] Source # enumFromThen :: Double -> Double -> [Double] Source # enumFromTo :: Double -> Double -> [Double] Source # enumFromThenTo :: Double -> Double -> Double -> [Double] Source # | |||||
Floating Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float exp :: Double -> Double Source # log :: Double -> Double Source # sqrt :: Double -> Double Source # (**) :: Double -> Double -> Double Source # logBase :: Double -> Double -> Double Source # sin :: Double -> Double Source # cos :: Double -> Double Source # tan :: Double -> Double Source # asin :: Double -> Double Source # acos :: Double -> Double Source # atan :: Double -> Double Source # sinh :: Double -> Double Source # cosh :: Double -> Double Source # tanh :: Double -> Double Source # asinh :: Double -> Double Source # acosh :: Double -> Double Source # atanh :: Double -> Double Source # log1p :: Double -> Double Source # expm1 :: Double -> Double Source # | |||||
RealFloat Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float floatRadix :: Double -> Integer Source # floatDigits :: Double -> Int Source # floatRange :: Double -> (Int, Int) Source # decodeFloat :: Double -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Double Source # exponent :: Double -> Int Source # significand :: Double -> Double Source # scaleFloat :: Int -> Double -> Double Source # isNaN :: Double -> Bool Source # isInfinite :: Double -> Bool Source # isDenormalized :: Double -> Bool Source # isNegativeZero :: Double -> Bool Source # | |||||
Storable Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Double -> Int Source # alignment :: Double -> Int Source # peekElemOff :: Ptr Double -> Int -> IO Double Source # pokeElemOff :: Ptr Double -> Int -> Double -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Double Source # pokeByteOff :: Ptr b -> Int -> Double -> IO () Source # | |||||
Num Double Source # | This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:
Since: base-2.1 | ||||
Read Double Source # | Since: base-2.1 | ||||
Fractional Double Source # | This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.
Since: base-2.1 | ||||
Real Double Source # | Beware that
Since: base-2.1 | ||||
Defined in GHC.Internal.Float toRational :: Double -> Rational Source # | |||||
RealFrac Double Source # | Beware that results for non-finite arguments are garbage:
and get even more non-sensical if you ask for Since: base-2.1 | ||||
Show Double Source # | Since: base-2.1 | ||||
Eq Double | Note that due to the presence of
Also note that
| ||||
Ord Double | IEEE 754 IEEE 754-2008, section 5.11 requires that if at least one of arguments of
IEEE 754-2008, section 5.10 defines Thus, users must be extremely cautious when using Moving further, the behaviour of IEEE 754-2008 compliant | ||||
Defined in GHC.Classes | |||||
Generic1 (URec Double :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Double p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |||||
data URec Double (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Double :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
The builtin linked list type.
In Haskell, lists are one of the most important data types as they are often used analogous to loops in imperative programming languages. These lists are singly linked, which makes them unsuited for operations that require \(\mathcal{O}(1)\) access. Instead, they are intended to be traversed.
You can use List a
or [a]
in type signatures:
length :: [a] -> Int
or
length :: List a -> Int
They are fully equivalent, and List a
will be normalised to [a]
.
Usage
Lists are constructed recursively using the right-associative constructor operator (or cons)
(:) :: a -> [a] -> [a]
, which prepends an element to a list,
and the empty list []
.
(1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
Lists can also be constructed using list literals
of the form [x_1, x_2, ..., x_n]
which are syntactic sugar and, unless -XOverloadedLists
is enabled,
are translated into uses of (:)
and []
String
literals, like "I 💜 hs"
, are translated into
Lists of characters, ['I', ' ', '💜', ' ', 'h', 's']
.
Implementation
Internally and in memory, all the above are represented like this, with arrows being pointers to locations in memory.
╭───┬───┬──╮ ╭───┬───┬──╮ ╭───┬───┬──╮ ╭────╮ │(:)│ │ ─┼──>│(:)│ │ ─┼──>│(:)│ │ ─┼──>│ [] │ ╰───┴─┼─┴──╯ ╰───┴─┼─┴──╯ ╰───┴─┼─┴──╯ ╰────╯ v v v 1 2 3
Examples
>>> ['H', 'a', 's', 'k', 'e', 'l', 'l'] "Haskell"
>>> 1 : [4, 1, 5, 9] [1,4,1,5,9]
>>> [] : [] : [] [[],[]]
Since: ghc-prim-0.10.0
Instances
Alternative [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
Applicative [] Source # | Since: base-2.1 | ||||
Functor [] Source # | Since: base-2.1 | ||||
Monad [] Source # | Since: base-2.1 | ||||
MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
MonadFail [] Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Control.Monad.Fail | |||||
MonadFix [] Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
Foldable [] Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => [m] -> m Source # foldMap :: Monoid m => (a -> m) -> [a] -> m Source # foldMap' :: Monoid m => (a -> m) -> [a] -> m Source # foldr :: (a -> b -> b) -> b -> [a] -> b Source # foldr' :: (a -> b -> b) -> b -> [a] -> b Source # foldl :: (b -> a -> b) -> b -> [a] -> b Source # foldl' :: (b -> a -> b) -> b -> [a] -> b Source # foldr1 :: (a -> a -> a) -> [a] -> a Source # foldl1 :: (a -> a -> a) -> [a] -> a Source # elem :: Eq a => a -> [a] -> Bool Source # maximum :: Ord a => [a] -> a Source # minimum :: Ord a => [a] -> a Source # | |||||
Traversable [] Source # | Since: base-2.1 | ||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monoid [a] Source # | Since: base-2.1 | ||||
Semigroup [a] Source # | Since: base-4.9.0.0 | ||||
Data a => Data [a] Source # | For historical reasons, the constructor name used for Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> [a] -> c [a] Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c [a] Source # toConstr :: [a] -> Constr Source # dataTypeOf :: [a] -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c [a]) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c [a]) Source # gmapT :: (forall b. Data b => b -> b) -> [a] -> [a] Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQ :: (forall d. Data d => d -> u) -> [a] -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> [a] -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # | |||||
a ~ Char => IsString [a] Source # |
Since: base-2.1 | ||||
Defined in GHC.Internal.Data.String fromString :: String -> [a] Source # | |||||
Generic [a] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
IsList [a] Source # | Since: base-4.7.0.0 | ||||
Read a => Read [a] Source # | Since: base-2.1 | ||||
Show a => Show [a] Source # | Since: base-2.1 | ||||
Eq a => Eq [a] | |||||
Ord a => Ord [a] | |||||
type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep [a] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep [a] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
type Item [a] Source # | |||||
Defined in GHC.Internal.IsList type Item [a] = a |
Instances
Monoid Ordering Source # | Since: base-2.1 |
Semigroup Ordering Source # | Since: base-4.9.0.0 |
Data Ordering Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source # toConstr :: Ordering -> Constr Source # dataTypeOf :: Ordering -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) Source # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # | |
Bounded Ordering Source # | Since: base-2.1 |
Enum Ordering Source # | Since: base-2.1 |
Defined in GHC.Internal.Enum succ :: Ordering -> Ordering Source # pred :: Ordering -> Ordering Source # toEnum :: Int -> Ordering Source # fromEnum :: Ordering -> Int Source # enumFrom :: Ordering -> [Ordering] Source # enumFromThen :: Ordering -> Ordering -> [Ordering] Source # enumFromTo :: Ordering -> Ordering -> [Ordering] Source # enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source # | |
Generic Ordering Source # | |
Defined in GHC.Internal.Generics | |
Ix Ordering Source # | Since: base-2.1 |
Defined in GHC.Internal.Ix | |
Read Ordering Source # | Since: base-2.1 |
Show Ordering Source # | Since: base-2.1 |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
type Rep Ordering Source # | Since: base-4.6.0.0 |
class a ~# b => (a :: k0) ~~ (b :: k1) infix 4 Source #
Lifted, heterogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By heterogeneous, the two
types a
and b
might have different kinds. Because ~~
can
appear unexpectedly in error messages to users who do not care
about the difference between heterogeneous equality ~~
and
homogeneous equality ~
, this is printed as ~
unless
-fprint-equality-relations
is set.
In 0.7.0
, the fixity was set to infix 4
to match the fixity of :~~:
.
class a ~# b => (a :: k) ~ (b :: k) infix 4 Source #
Lifted, homogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By homogeneous, the two
types a
and b
must have the same kinds.
class a ~R# b => Coercible (a :: k) (b :: k) Source #
Coercible
is a two-parameter class that has instances for types a
and b
if
the compiler can infer that they have the same representation. This class
does not have regular instances; instead they are created on-the-fly during
type-checking. Trying to manually declare an instance of Coercible
is an error.
Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:
instance Coercible a a
Furthermore, for every type constructor there is
an instance that allows to coerce under the type constructor. For
example, let D
be a prototypical type constructor (data
or
newtype
) with three type arguments, which have roles nominal
,
representational
resp. phantom
. Then there is an instance of
the form
instance Coercible b b' => Coercible (D a b c) (D a b' c')
Note that the nominal
type arguments are equal, the
representational
type arguments can differ, but need to have a
Coercible
instance themself, and the phantom
type arguments can be
changed arbitrarily.
The third kind of instance exists for every newtype NT = MkNT T
and
comes in two variants, namely
instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b
This instance is only usable if the constructor MkNT
is in scope.
If, as a library author of a type constructor like Set a
, you
want to prevent a user of your module to write
coerce :: Set T -> Set NT
,
you need to set the role of Set
's type parameter to nominal
,
by writing
type role Set nominal
For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.
Since: ghc-prim-0.4.0
(Kind) This is the kind of type-level symbols.
Instances
TestCoercion SSymbol Source # | Since: base-4.18.0.0 |
Defined in GHC.Internal.TypeLits | |
TestEquality SSymbol Source # | Since: base-4.18.0.0 |
Defined in GHC.Internal.TypeLits | |
type Compare (a :: Symbol) (b :: Symbol) Source # | |
Defined in GHC.Internal.Data.Type.Ord |
data RuntimeRep Source #
GHC maintains a property that the kind of all inhabited types
(as distinct from type constructors or type-level data) tells us
the runtime representation of values of that type. This datatype
encodes the choice of runtime value.
Note that TYPE
is parameterised by RuntimeRep
; this is precisely
what we mean by the fact that a type's kind encodes the runtime
representation.
For boxed values (that is, values that are represented by a pointer), a further distinction is made, between lifted types (that contain ⊥), and unlifted ones (that don't).
VecRep VecCount VecElem | a SIMD vector type |
TupleRep [RuntimeRep] | An unboxed tuple of the given reps |
SumRep [RuntimeRep] | An unboxed sum of the given reps |
BoxedRep Levity | boxed; represented by a pointer |
IntRep | signed, word-sized value |
Int8Rep | signed, 8-bit value |
Int16Rep | signed, 16-bit value |
Int32Rep | signed, 32-bit value |
Int64Rep | signed, 64-bit value |
WordRep | unsigned, word-sized value |
Word8Rep | unsigned, 8-bit value |
Word16Rep | unsigned, 16-bit value |
Word32Rep | unsigned, 32-bit value |
Word64Rep | unsigned, 64-bit value |
AddrRep | A pointer, but not to a Haskell value |
FloatRep | a 32-bit floating point number |
DoubleRep | a 64-bit floating point number |
Instances
Show RuntimeRep Source # | Since: base-4.11.0.0 |
Defined in GHC.Internal.Show |
Whether a boxed type is lifted or unlifted.
Instances
Bounded Levity Source # | Since: base-4.16.0.0 |
Enum Levity Source # | Since: base-4.16.0.0 |
Defined in GHC.Internal.Enum succ :: Levity -> Levity Source # pred :: Levity -> Levity Source # toEnum :: Int -> Levity Source # fromEnum :: Levity -> Int Source # enumFrom :: Levity -> [Levity] Source # enumFromThen :: Levity -> Levity -> [Levity] Source # enumFromTo :: Levity -> Levity -> [Levity] Source # enumFromThenTo :: Levity -> Levity -> Levity -> [Levity] Source # | |
Show Levity Source # | Since: base-4.15.0.0 |
Length of a SIMD vector type
Instances
Bounded VecCount Source # | Since: base-4.10.0.0 |
Enum VecCount Source # | Since: base-4.10.0.0 |
Defined in GHC.Internal.Enum succ :: VecCount -> VecCount Source # pred :: VecCount -> VecCount Source # toEnum :: Int -> VecCount Source # fromEnum :: VecCount -> Int Source # enumFrom :: VecCount -> [VecCount] Source # enumFromThen :: VecCount -> VecCount -> [VecCount] Source # enumFromTo :: VecCount -> VecCount -> [VecCount] Source # enumFromThenTo :: VecCount -> VecCount -> VecCount -> [VecCount] Source # | |
Show VecCount Source # | Since: base-4.11.0.0 |
Element of a SIMD vector type
Int8ElemRep | |
Int16ElemRep | |
Int32ElemRep | |
Int64ElemRep | |
Word8ElemRep | |
Word16ElemRep | |
Word32ElemRep | |
Word64ElemRep | |
FloatElemRep | |
DoubleElemRep |
Instances
Bounded VecElem Source # | Since: base-4.10.0.0 |
Enum VecElem Source # | Since: base-4.10.0.0 |
Defined in GHC.Internal.Enum succ :: VecElem -> VecElem Source # pred :: VecElem -> VecElem Source # toEnum :: Int -> VecElem Source # fromEnum :: VecElem -> Int Source # enumFrom :: VecElem -> [VecElem] Source # enumFromThen :: VecElem -> VecElem -> [VecElem] Source # enumFromTo :: VecElem -> VecElem -> [VecElem] Source # enumFromThenTo :: VecElem -> VecElem -> VecElem -> [VecElem] Source # | |
Show VecElem Source # | Since: base-4.11.0.0 |
data Multiplicity Source #
SPEC
is used by GHC in the SpecConstr
pass in order to inform
the compiler when to be particularly aggressive. In particular, it
tells GHC to specialize regardless of size or the number of
specializations. However, not all loops fall into this category.
Libraries can specify this by using SPEC
data type to inform which
loops should be aggressively specialized. For example,
instead of
loop x where loop arg = ...
write
loop SPEC x where loop !_ arg = ...
There is no semantic difference between SPEC
and SPEC2
,
we just need a type with two constructors lest it is optimised away
before SpecConstr
.
This type is reexported from GHC.Exts since GHC 9.0 and base-4.15
.
For compatibility with earlier releases import it from GHC.Types
in ghc-prim
package.
Since: ghc-prim-0.3.1.0
pattern TypeLitChar :: TypeLitSort Source #
pattern TypeLitNat :: TypeLitSort Source #
pattern TypeLitSymbol :: TypeLitSort Source #
pattern KindRepTypeLitD :: TypeLitSort -> [Char] -> KindRep Source #
pattern KindRepTypeLitS :: TypeLitSort -> Addr# -> KindRep Source #
pattern KindRepTYPE :: !RuntimeRep -> KindRep Source #
pattern KindRepVar :: !KindBndr -> KindRep Source #
type ZeroBitType = TYPE ZeroBitRep Source #
The kind of the empty unboxed tuple type (# #)
type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep]) Source #
The runtime representation of a zero-width tuple, represented by no bits at all
type UnliftedRep = 'BoxedRep 'Unlifted Source #
The runtime representation of unlifted types.
type UnliftedType = TYPE UnliftedRep Source #
The kind of boxed, unlifted values, for example Array#
or a user-defined
unlifted data type, using -XUnliftedDataTypes
.
type Constraint = CONSTRAINT LiftedRep Source #
The kind of lifted constraints
type family Any :: k where ... Source #
The type constructor Any
is type to which you can unsafely coerce any
lifted type, and back. More concretely, for a lifted type t
and
value x :: t
, unsafeCoerce (unsafeCoerce x :: Any) :: t
is equivalent
to x
.
type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ... Source #
isTrue# :: Int# -> Bool Source #
Alias for tagToEnum#
. Returns True if its parameter is 1# and False
if it is 0#.
Legacy interface for arrays of arrays
module GHC.Internal.ArrayArray
Primitive operations
data Addr# :: TYPE 'AddrRep Source #
An arbitrary machine address assumed to point outside the garbage-collected heap.
data ByteArray# :: UnliftedType Source #
A boxed, unlifted datatype representing a region of raw memory in the garbage-collected heap, which is not scanned for pointers during garbage collection.
It is created by freezing a MutableByteArray#
with unsafeFreezeByteArray#
.
Freezing is essentially a no-op, as MutableByteArray#
and ByteArray#
share the same heap structure under the hood.
The immutable and mutable variants are commonly used for scenarios requiring high-performance data structures,
like Text
, Primitive Vector
, Unboxed Array
, and ShortByteString
.
Another application of fundamental importance is Integer
, which is backed by ByteArray#
.
The representation on the heap of a Byte Array is:
+------------+-----------------+-----------------------+ | | | | | HEADER | SIZE (in bytes) | PAYLOAD | | | | | +------------+-----------------+-----------------------+
To obtain a pointer to actual payload (e.g., for FFI purposes) use byteArrayContents#
or mutableByteArrayContents#
.
Alternatively, enabling the UnliftedFFITypes
extension
allows to mention ByteArray#
and MutableByteArray#
in FFI type signatures directly.
data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data MutableByteArray# a :: UnliftedType Source #
A mutable ByteAray#
. It can be created in three ways:
newByteArray#
: Create an unpinned array.newPinnedByteArray#
: This will create a pinned array,newAlignedPinnedByteArray#
: This will create a pinned array, with a custom alignment.
Unpinned arrays can be moved around during garbage collection, so you must not store or pass pointers to these values if there is a chance for the garbage collector to kick in. That said, even unpinned arrays can be passed to unsafe FFI calls, because no garbage collection happens during these unsafe calls (see Guaranteed Call Safety in the GHC Manual). For safe FFI calls, byte arrays must be not only pinned, but also kept alive by means of the keepAlive# function for the duration of a call (that's because garbage collection cannot move a pinned array, but is free to scrap it altogether).
data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
A shared I/O port is almost the same as an MVar#
.
The main difference is that IOPort has no deadlock detection or
deadlock breaking code that forcibly releases the lock.
data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
A MutVar#
behaves like a single-element mutable array.
data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data Compact# :: UnliftedType Source #
data State# a :: ZeroBitType Source #
data Proxy# (a :: k) :: ZeroBitType Source #
data ThreadId# :: UnliftedType Source #
(In a non-concurrent implementation, this can be a singleton
type, whose (unique) value is returned by myThreadId#
. The
other operations can be omitted.)
data StackSnapshot# :: UnliftedType Source #
Haskell representation of a StgStack*
that was created (cloned)
with a function in GHC.Stack.CloneStack. Please check the
documentation in that module for more detailed explanations.
data PromptTag# a :: UnliftedType Source #
See GHC.Prim.
The builtin function type, written in infix form as a % m -> b
.
Values of this type are functions taking inputs of type a
and
producing outputs of type b
. The multiplicity of the input is
m
.
Note that
permits representation polymorphism in both
FUN
m a ba
and b
, so that types like
can still be
well-kinded.Int#
-> Int#
Instances
Category (->) Source # | Since: base-3.0 |
Monoid b => Monoid (a -> b) Source # | Since: base-2.1 |
Semigroup b => Semigroup (a -> b) Source # | Since: base-4.9.0.0 |
Arrow (->) Source # | Since: base-2.1 |
ArrowApply (->) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Arrow | |
ArrowChoice (->) Source # | Since: base-2.1 |
ArrowLoop (->) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Arrow | |
Applicative ((->) r) Source # | Since: base-2.1 |
Functor ((->) r) Source # | Since: base-2.1 |
Monad ((->) r) Source # | Since: base-2.1 |
MonadFix ((->) r) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Monad.Fix |
data TYPE (a :: RuntimeRep) Source #
Instances
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Identity Source # | |||||
Defined in GHC.Internal.Data.Functor.Identity
| |||||
Generic1 First Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Last Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 ZipList Source # | |||||
Defined in GHC.Internal.Functor.ZipList
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Solo Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source # | Since: base-3.0 | ||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Category (->) Source # | Since: base-3.0 | ||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Control.Arrow
| |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source # to1 :: Rep1 ((,,,,,,,,) a b c d e f g h) a0 -> (a, b, c, d, e, f, g, h, a0) Source # | |||||
Generic1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source # to1 :: Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 -> (a, b, c, d, e, f, g, h, i, a0) Source # | |||||
Generic1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, a0) -> Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 Source # to1 :: Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 -> (a, b, c, d, e, f, g, h, i, j, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, a0) -> Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 -> (a, b, c, d, e, f, g, h, i, j, k, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, a0) -> Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) Source # | |||||
Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Alternative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Applicative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Foldable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Proxy m -> m Source # foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source # foldr :: (a -> b -> b) -> b -> Proxy a -> b Source # foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source # foldl :: (b -> a -> b) -> b -> Proxy a -> b Source # foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source # foldr1 :: (a -> a -> a) -> Proxy a -> a Source # foldl1 :: (a -> a -> a) -> Proxy a -> a Source # toList :: Proxy a -> [a] Source # null :: Proxy a -> Bool Source # length :: Proxy a -> Int Source # elem :: Eq a => a -> Proxy a -> Bool Source # maximum :: Ord a => Proxy a -> a Source # minimum :: Ord a => Proxy a -> a Source # | |||||
Foldable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => U1 m -> m Source # foldMap :: Monoid m => (a -> m) -> U1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> U1 a -> m Source # foldr :: (a -> b -> b) -> b -> U1 a -> b Source # foldr' :: (a -> b -> b) -> b -> U1 a -> b Source # foldl :: (b -> a -> b) -> b -> U1 a -> b Source # foldl' :: (b -> a -> b) -> b -> U1 a -> b Source # foldr1 :: (a -> a -> a) -> U1 a -> a Source # foldl1 :: (a -> a -> a) -> U1 a -> a Source # toList :: U1 a -> [a] Source # length :: U1 a -> Int Source # elem :: Eq a => a -> U1 a -> Bool Source # maximum :: Ord a => U1 a -> a Source # minimum :: Ord a => U1 a -> a Source # | |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |||||
Foldable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => V1 m -> m Source # foldMap :: Monoid m => (a -> m) -> V1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> V1 a -> m Source # foldr :: (a -> b -> b) -> b -> V1 a -> b Source # foldr' :: (a -> b -> b) -> b -> V1 a -> b Source # foldl :: (b -> a -> b) -> b -> V1 a -> b Source # foldl' :: (b -> a -> b) -> b -> V1 a -> b Source # foldr1 :: (a -> a -> a) -> V1 a -> a Source # foldl1 :: (a -> a -> a) -> V1 a -> a Source # toList :: V1 a -> [a] Source # length :: V1 a -> Int Source # elem :: Eq a => a -> V1 a -> Bool Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # | |||||
Traversable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Alternative f => Alternative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Alternative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics empty :: Generically1 f a Source # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # some :: Generically1 f a -> Generically1 f [a] Source # many :: Generically1 f a -> Generically1 f [a] Source # | |||||
Alternative f => Alternative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Monoid m => Applicative (Const m :: Type -> Type) Source # | Since: base-2.0.1 | ||||
Defined in GHC.Internal.Data.Functor.Const | |||||
Applicative f => Applicative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Applicative f => Applicative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics pure :: a -> Generically1 f a Source # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source # | |||||
Applicative f => Applicative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (Const m :: Type -> Type) Source # | Since: base-2.1 | ||||
Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 | ||||
Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |||||
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 | ||||
Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 | ||||
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadFail f => MonadFail (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadFix f => MonadFix (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Data t => Data (Proxy t) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) Source # toConstr :: Proxy t -> Constr Source # dataTypeOf :: Proxy t -> DataType Source # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) Source # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # | |||||
Data p => Data (U1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) Source # toConstr :: U1 p -> Constr Source # dataTypeOf :: U1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # | |||||
Data p => Data (V1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) Source # toConstr :: V1 p -> Constr Source # dataTypeOf :: V1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # | |||||
Foldable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 Source # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldr :: (a -> b -> b) -> b -> Const m a -> b Source # foldr' :: (a -> b -> b) -> b -> Const m a -> b Source # foldl :: (b -> a -> b) -> b -> Const m a -> b Source # foldl' :: (b -> a -> b) -> b -> Const m a -> b Source # foldr1 :: (a -> a -> a) -> Const m a -> a Source # foldl1 :: (a -> a -> a) -> Const m a -> a Source # toList :: Const m a -> [a] Source # null :: Const m a -> Bool Source # length :: Const m a -> Int Source # elem :: Eq a => a -> Const m a -> Bool Source # maximum :: Ord a => Const m a -> a Source # minimum :: Ord a => Const m a -> a Source # | |||||
Foldable f => Foldable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Ap f m -> m Source # foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m Source # foldr :: (a -> b -> b) -> b -> Ap f a -> b Source # foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source # foldl :: (b -> a -> b) -> b -> Ap f a -> b Source # foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source # foldr1 :: (a -> a -> a) -> Ap f a -> a Source # foldl1 :: (a -> a -> a) -> Ap f a -> a Source # toList :: Ap f a -> [a] Source # null :: Ap f a -> Bool Source # length :: Ap f a -> Int Source # elem :: Eq a => a -> Ap f a -> Bool Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # | |||||
Foldable f => Foldable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |||||
Foldable f => Foldable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Rec1 f m -> m Source # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source # foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source # toList :: Rec1 f a -> [a] Source # null :: Rec1 f a -> Bool Source # length :: Rec1 f a -> Int Source # elem :: Eq a => a -> Rec1 f a -> Bool Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # | |||||
Traversable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Monoid c => Applicative (K1 i c :: Type -> Type) Source # | Since: base-4.12.0.0 | ||||
(Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Monoid a) => Monoid (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Monoid (Alt f a) Source # | Since: base-4.8.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Semigroup (Alt f a) Source # | Since: base-4.9.0.0 | ||||
(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) Source # toConstr :: Ap f a -> Constr Source # dataTypeOf :: Ap f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # | |||||
(Data (f a), Data a, Typeable f) => Data (Alt f a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |||||
(Coercible a b, Data a, Data b) => Data (Coercion a b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Coercion a b -> c (Coercion a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion a b) Source # toConstr :: Coercion a b -> Constr Source # dataTypeOf :: Coercion a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Coercion a b -> Coercion a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Coercion a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # | |||||
(a ~ b, Data a) => Data (a :~: b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) Source # toConstr :: (a :~: b) -> Constr Source # dataTypeOf :: (a :~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # | |||||
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) Source # toConstr :: Rec1 f p -> Constr Source # dataTypeOf :: Rec1 f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) Source # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # | |||||
(Foldable f, Foldable g) => Foldable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :*: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source # toList :: (f :*: g) a -> [a] Source # null :: (f :*: g) a -> Bool Source # length :: (f :*: g) a -> Int Source # elem :: Eq a => a -> (f :*: g) a -> Bool Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # | |||||
(Foldable f, Foldable g) => Foldable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :+: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source # toList :: (f :+: g) a -> [a] Source # null :: (f :+: g) a -> Bool Source # length :: (f :+: g) a -> Int Source # elem :: Eq a => a -> (f :+: g) a -> Bool Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # | |||||
Foldable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => K1 i c m -> m Source # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldr1 :: (a -> a -> a) -> K1 i c a -> a Source # foldl1 :: (a -> a -> a) -> K1 i c a -> a Source # toList :: K1 i c a -> [a] Source # null :: K1 i c a -> Bool Source # length :: K1 i c a -> Int Source # elem :: Eq a => a -> K1 i c a -> Bool Source # maximum :: Ord a => K1 i c a -> a Source # minimum :: Ord a => K1 i c a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Applicative f, Bounded a) => Bounded (Ap f a) Source # | Since: base-4.12.0.0 | ||||
(Applicative f, Num a) => Num (Ap f a) Source # | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
(Alternative f, Applicative g) => Alternative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Alternative f => Alternative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Applicative f => Applicative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
(Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadFix f => MonadFix (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) Source # toConstr :: (f :*: g) p -> Constr Source # dataTypeOf :: (f :*: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # | |||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) Source # toConstr :: (f :+: g) p -> Constr Source # dataTypeOf :: (f :+: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # | |||||
(Typeable i, Data p, Data c) => Data (K1 i c p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) Source # toConstr :: K1 i c p -> Constr Source # dataTypeOf :: K1 i c p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) Source # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # | |||||
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :.: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source # toList :: (f :.: g) a -> [a] Source # null :: (f :.: g) a -> Bool Source # length :: (f :.: g) a -> Int Source # elem :: Eq a => a -> (f :.: g) a -> Bool Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # | |||||
Foldable f => Foldable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => M1 i c f m -> m Source # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source # foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source # toList :: M1 i c f a -> [a] Source # null :: M1 i c f a -> Bool Source # length :: M1 i c f a -> Int Source # elem :: Eq a => a -> M1 i c f a -> Bool Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) Source # toConstr :: (f :.: g) p -> Constr Source # dataTypeOf :: (f :.: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # | |||||
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) Source # toConstr :: M1 i c f p -> Constr Source # dataTypeOf :: M1 i c f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) Source # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # | |||||
type Rep1 NonEmpty Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 Identity Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
type Rep1 First Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Last Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Down Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Dual Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Sum Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 ZipList Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Functor.ZipList | |||||
type Rep1 Par1 Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Maybe Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Solo Source # | Since: base-4.15 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 (Either a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 ((,) a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,) a :: Type -> Type) = D1 ('MetaData "Tuple2" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 (Kleisli m a :: Type -> Type) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Control.Arrow | |||||
type Rep1 ((,,) a b :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,) a b :: Type -> Type) = D1 ('MetaData "Tuple3" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,) a b c :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,) a b c :: Type -> Type) = D1 ('MetaData "Tuple4" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,,) a b c d :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,) a b c d :: Type -> Type) = D1 ('MetaData "Tuple5" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 (f :.: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 ((,,,,,) a b c d e :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,) a b c d e :: Type -> Type) = D1 ('MetaData "Tuple6" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) = D1 ('MetaData "Tuple7" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) = D1 ('MetaData "Tuple8" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) = D1 ('MetaData "Tuple9" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) = D1 ('MetaData "Tuple10" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) = D1 ('MetaData "Tuple11" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) = D1 ('MetaData "Tuple12" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "Tuple13" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "Tuple14" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "Tuple15" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) |
data CONSTRAINT (a :: RuntimeRep) Source #
data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
prefetchValue0# :: a -> State# d -> State# d Source #
prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue1# :: a -> State# d -> State# d Source #
prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue2# :: a -> State# d -> State# d Source #
prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue3# :: a -> State# d -> State# d Source #
prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d Source #
writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
negateDoubleX8# :: DoubleX8# -> DoubleX8# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateFloatX16# :: FloatX16# -> FloatX16# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateDoubleX4# :: DoubleX4# -> DoubleX4# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateFloatX8# :: FloatX8# -> FloatX8# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateDoubleX2# :: DoubleX2# -> DoubleX2# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateFloatX4# :: FloatX4# -> FloatX4# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt64X8# :: Int64X8# -> Int64X8# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt32X16# :: Int32X16# -> Int32X16# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt16X32# :: Int16X32# -> Int16X32# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt8X64# :: Int8X64# -> Int8X64# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt64X4# :: Int64X4# -> Int64X4# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt32X8# :: Int32X8# -> Int32X8# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt16X16# :: Int16X16# -> Int16X16# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt8X32# :: Int8X32# -> Int8X32# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt64X2# :: Int64X2# -> Int64X2# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt32X4# :: Int32X4# -> Int32X4# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt16X8# :: Int16X8# -> Int16X8# Source #
Negate element-wise.
Warning: this is only available on LLVM.
negateInt8X16# :: Int8X16# -> Int8X16# Source #
Negate element-wise.
Warning: this is only available on LLVM.
remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
Warning: this is only available on LLVM.
quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Rounds towards zero element-wise.
Warning: this is only available on LLVM.
divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #
Divide two vectors element-wise.
Warning: this is only available on LLVM.
timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Multiply two vectors element-wise.
Warning: this is only available on LLVM.
minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Subtract two vectors element-wise.
Warning: this is only available on LLVM.
plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Add two vectors element-wise.
Warning: this is only available on LLVM.
insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# Source #
Insert a scalar at the given position in a vector.
Warning: this is only available on LLVM.
unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
Warning: this is only available on LLVM.
packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord64X2# :: (# Word64#, Word64# #) -> Word64X2# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt64X2# :: (# Int64#, Int64# #) -> Int64X2# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16# Source #
Pack the elements of an unboxed tuple into a vector.
Warning: this is only available on LLVM.
broadcastDoubleX8# :: Double# -> DoubleX8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastFloatX16# :: Float# -> FloatX16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastDoubleX4# :: Double# -> DoubleX4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastFloatX8# :: Float# -> FloatX8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastDoubleX2# :: Double# -> DoubleX2# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastFloatX4# :: Float# -> FloatX4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord64X8# :: Word64# -> Word64X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord32X16# :: Word32# -> Word32X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord16X32# :: Word16# -> Word16X32# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord8X64# :: Word8# -> Word8X64# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord64X4# :: Word64# -> Word64X4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord32X8# :: Word32# -> Word32X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord16X16# :: Word16# -> Word16X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord8X32# :: Word8# -> Word8X32# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord64X2# :: Word64# -> Word64X2# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord32X4# :: Word32# -> Word32X4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord16X8# :: Word16# -> Word16X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastWord8X16# :: Word8# -> Word8X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt64X8# :: Int64# -> Int64X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt32X16# :: Int32# -> Int32X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt16X32# :: Int16# -> Int16X32# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt8X64# :: Int8# -> Int8X64# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt64X4# :: Int64# -> Int64X4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt32X8# :: Int32# -> Int32X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt16X16# :: Int16# -> Int16X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt8X32# :: Int8# -> Int8X32# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt64X2# :: Int64# -> Int64X2# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt32X4# :: Int32# -> Int32X4# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt16X8# :: Int16# -> Int16X8# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
broadcastInt8X16# :: Int8# -> Int8X16# Source #
Broadcast a scalar to all elements of a vector.
Warning: this is only available on LLVM.
setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld Source #
Sets the allocation counter for the current thread to the given value.
traceMarker# :: Addr# -> State# d -> State# d Source #
Emits a marker event via the RTS tracing framework. The contents
of the event is the zero-terminated byte string passed as the first
argument. The event will be emitted either to the .eventlog
file,
or to stderr, depending on the runtime RTS flags.
traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d Source #
Emits an event via the RTS tracing framework. The contents
of the event is the binary object passed as the first argument with
the given length passed as the second argument. The event will be
emitted to the .eventlog
file.
traceEvent# :: Addr# -> State# d -> State# d Source #
Emits an event via the RTS tracing framework. The contents
of the event is the zero-terminated byte string passed as the first
argument. The event will be emitted either to the .eventlog
file,
or to stderr, depending on the runtime RTS flags.
clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #) Source #
Run the supplied IO action with an empty CCS. For example, this is used by the interpreter to run an interpreted computation without the call stack showing that it was invoked from GHC.
getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #) Source #
Returns the current CostCentreStack
(value is NULL
if
not profiling). Takes a dummy argument which can be used to
avoid the call to getCurrentCCS#
being floated out by the
simplifier, which would result in an uninformative stack
(CAF).
getApStackVal# :: a -> Int# -> (# Int#, b #) Source #
closureSize# :: a -> Int# Source #
returns the size of the given closure in
machine words. closureSize#
closure
unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #) Source #
copies the closure and pointers in the
payload of the given closure into two new arrays, and returns a pointer to
the first word of the closure's info table, a non-pointer array for the raw
bytes of the closure, and a pointer array for the pointers in the payload. unpackClosure#
closure
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) Source #
creates a new bytecode object. The
resulting object encodes a function of the given arity with the instructions
encoded in newBCO#
instrs lits ptrs arity bitmapinstrs
, and a static reference table usage bitmap given by
bitmap
.
mkApUpd0# :: BCO -> (# a #) Source #
Wrap a BCO in a AP_UPD
thunk which will be updated with the value of
the BCO when evaluated.
anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #
Retrieve the address of any Haskell value. This is
essentially an unsafeCoerce#
, but if implemented as such
the core lint pass complains and fails to compile.
As a primop, it is opaque to core/stg, and only appears
in cmm (where the copy propagation pass will get rid of it).
Note that "a" must be a value, not a thunk! It's too late
for strictness analysis to enforce this, so you're on your
own to guarantee this. Also note that Addr#
is not a GC
pointer - up to you to guarantee that it does not become
a dangling pointer immediately after you get it.
addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #) Source #
Convert an Addr#
to a followable Any type.
tagToEnum# :: Int# -> a Source #
keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) d (b :: TYPE r). a -> State# d -> (State# d -> b) -> b Source #
keeps the value keepAlive#
x s kx
alive during the execution
of the computation k
.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
numSparks# :: State# d -> (# State# d, Int# #) Source #
Returns the number of sparks in the local spark pool.
reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int# Source #
Returns 1#
if the given pointers are equal and 0#
otherwise.
compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) Source #
Return the total capacity (in bytes) of all the compact blocks in the CNF.
compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #
Like compactAdd#
, but retains sharing and cycles
during compaction.
compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #
Recursively add a closure and its transitive closure to a
Compact#
(a CNF), evaluating any unevaluated components
at the same time. Note: compactAdd#
is not thread-safe, so
only one thread may call compactAdd#
with a particular
Compact#
at any given time. The primop does not
enforce any mutual exclusion; the caller is expected to
arrange this.
compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) Source #
Given the pointer to the first block of a CNF and the address of the root object in the old address space, fix up the internal pointers inside the CNF to account for a different position in memory than when it was serialized. This method must be called exactly once after importing a serialized CNF. It returns the new CNF and the new adjusted root address.
compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #
Attempt to allocate a compact block with the capacity (in
bytes) given by the first argument. The Addr#
is a pointer
to previous compact block of the CNF or nullAddr#
to create a
new CNF with a single compact block.
The resulting block is not known to the GC until
compactFixupPointers#
is called on it, and care must be taken
so that the address does not escape or memory will be leaked.
compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
Given a CNF and the address of one its compact blocks, returns the
next compact block and its utilized size, or nullAddr#
if the
argument was the last compact block in the CNF.
compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
Returns the address and the utilized size (in bytes) of the first compact block of a CNF.
compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
Returns 1# if the object is in any CNF at all, 0# otherwise.
compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
Returns 1# if the object is contained in the CNF, 0# otherwise.
compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld Source #
Set the new allocation size of the CNF. This value (in bytes) determines the capacity of each compact block in the CNF. It does not retroactively affect existing compact blocks in the CNF.
compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #) Source #
Create a new CNF with a single compact block. The argument is the capacity of the compact block (in bytes, not words). The capacity is rounded up to a multiple of the allocator block size and is capped to one mega block.
stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int# Source #
makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #) Source #
eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int# Source #
deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) Source #
makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) Source #
finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) Source #
Finalize a weak pointer. The return value is an unboxed tuple
containing the new state of the world and an "unboxed Maybe",
represented by an Int#
and a (possibly invalid) finalization
action. An Int#
of 1
indicates that the finalizer is valid. The
return value b
from the finalizer should be ignored.
deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) Source #
addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
attaches a C
function pointer addCFinalizerToWeak#
fptr ptr flag eptr wfptr
to a weak pointer w
as a finalizer. If
flag
is zero, fptr
will be called with one argument,
ptr
. Otherwise, it will be called with two arguments,
eptr
and ptr
. addCFinalizerToWeak#
returns
1 on success, or 0 if w
is already dead.
mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #
mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #
creates a weak reference to value mkWeak#
k v finalizer sk
,
with an associated reference to some value v
. If k
is still
alive then v
can be retrieved using deRefWeak#
. Note that
the type of k
must be represented by a pointer (i.e. of kind
TYPE
'LiftedRep
or TYPE
'UnliftedRep
@).
listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #) Source #
Returns an array of the threads started by the program. Note that this threads which have finished execution may or may not be present in this list, depending upon whether they have been collected by the garbage collector.
Since: ghc-prim-0.10
threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) Source #
Get the status of the given thread. Result is
(ThreadStatus, Capability, Locked)
where
ThreadStatus
is one of the status constants defined in
rts/Constants.h
, Capability
is the number of
the capability which currently owns the thread, and
Locked
is a boolean indicating whether the
thread is bound to that capability.
Since: ghc-prim-0.9
threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #) Source #
Get the label of the given thread.
Morally of type ThreadId# -> IO (Maybe ByteArray#)
, with a 1#
tag
denoting Just
.
Since: ghc-prim-0.10
noDuplicate# :: State# d -> State# d Source #
labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld Source #
Set the label of the given thread. The ByteArray#
should contain
a UTF-8-encoded string.
forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #
fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #
waitWrite# :: Int# -> State# d -> State# d Source #
Block until output is possible on specified file descriptor.
waitRead# :: Int# -> State# d -> State# d Source #
Block until input is available on specified file descriptor.
writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #) Source #
If IOPort#
is full, immediately return with integer 0,
throwing an IOPortException
.
Otherwise, store value arg as 'IOPort#''s new contents,
and return with integer 1.
readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #) Source #
newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #) Source #
Create new IOPort#
; initially empty.
isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #) Source #
Return 1 if MVar#
is empty; 0 otherwise.
tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) Source #
readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #
If MVar#
is empty, block until it becomes full.
Then read its contents without modifying the MVar, without possibility
of intervention from other threads.
tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #) Source #
If MVar#
is full, immediately return with integer 0.
Otherwise, store value arg as 'MVar#''s new contents, and return with integer 1.
putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d Source #
If MVar#
is full, block until it becomes empty.
Then store value arg as its new contents.
tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) Source #
takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #
If MVar#
is empty, block until it becomes full.
Then remove and return its contents, and set it empty.
newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #) Source #
Create new MVar#
; initially empty.
writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d Source #
Write contents of TVar#
.
readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of TVar#
outside an STM transaction.
Does not force evaluation of the result.
readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of TVar#
inside an STM transaction,
i.e. within a call to atomically#
.
Does not force evaluation of the result.
newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #) Source #
Create a new TVar#
holding a specified initial value.
catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #) Source #
atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
control0# :: forall {r :: RuntimeRep} a (b :: TYPE r). PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #) Source #
See GHC.Prim.
Warning: this can fail with an unchecked exception.
prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
See GHC.Prim.
newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #) Source #
See GHC.Prim.
unmaskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates unmaskAsyncUninterruptible#
k sk s
such that asynchronous
exceptions are unmasked.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates maskUninterruptible#
k sk s
such that asynchronous
exceptions are deferred until after evaluation has finished.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates maskAsyncExceptions#
k sk s
such that asynchronous
exceptions are deferred until after evaluation has finished.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #) Source #
raiseDivZero# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b Source #
raiseOverflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b Source #
raiseUnderflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b Source #
raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> b Source #
catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates catch#
k handler sk s
, invoking handler
on any exceptions
thrown.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Compare-and-swap: perform a pointer equality test between
the first value passed to this function and the value
stored inside the MutVar#
. If the pointers are equal,
replace the stored value with the second value passed to this
function, otherwise do nothing.
Returns the final value stored inside the MutVar#
.
The Int#
indicates whether a swap took place,
with 1#
meaning that we didn't swap, and 0#
that we did.
Implies a full memory barrier.
Because the comparison is done on the level of pointers,
all of the difficulties of using
reallyUnsafePtrEquality#
correctly apply to
casMutVar#
as well.
atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) Source #
Modify the contents of a MutVar#
, returning the previous
contents and the result of applying the given function to the
previous contents.
atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) Source #
Modify the contents of a MutVar#
, returning the previous
contents x :: a
and the result of applying the given function to the
previous contents f x :: c
.
The data
type c
(not a newtype
!) must be a record whose first field
is of lifted type a :: Type
and is not unpacked. For example, product
types c ~ Solo a
or c ~ (a, b)
work well. If the record type is both
monomorphic and strict in its first field, it's recommended to mark the
latter {-# NOUNPACK #-}
explicitly.
Under the hood atomicModifyMutVar2#
atomically replaces a pointer to an
old x :: a
with a pointer to a selector thunk fst r
, where
fst
is a selector for the first field of the record and r
is a
function application thunk r = f x
.
atomicModifyIORef2Native
from atomic-modify-general
package makes an
effort to reflect restrictions on c
faithfully, providing a
well-typed high-level wrapper.
atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) Source #
Atomically exchange the value of a MutVar#
.
writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d Source #
Write contents of MutVar#
.
readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of MutVar#
. Result is not yet evaluated.
newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) Source #
Create MutVar#
with specified initial value in specified state thread.
atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d Source #
Given an address, write a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #) Source #
Given an address, read a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) Source #
Compare and swap on a 64 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr64# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) Source #
Compare and swap on a 32 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr32# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) Source #
Compare and swap on a 16 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr16# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) Source #
Compare and swap on a 8 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr8# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) Source #
Compare and swap on a word-sized and aligned memory location.
Use as: s -> atomicCasWordAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
Compare and swap on a word-sized memory location.
Use as: s -> atomicCasAddrAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.
Warning: this can fail with an unchecked exception.
atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer; offset in bytes.
indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer; offset in bytes.
indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer; offset in bytes.
indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer; offset in bytes.
indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer; offset in bytes.
indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer; offset in bytes.
indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value; offset in bytes.
indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value; offset in bytes.
indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value; offset in bytes.
indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer; offset in bytes.
indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer; offset in bytes.
indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character; offset in bytes.
indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char# Source #
Read an 8-bit character; offset in bytes.
indexWord64OffAddr# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt64OffAddr# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord32OffAddr# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt32OffAddr# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord16OffAddr# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt16OffAddr# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord8OffAddr# :: Addr# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer; offset in bytes.
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexFloatOffAddr# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source #
Read a machine address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWordOffAddr# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexIntOffAddr# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) Source #
Given an array, an offset in 64 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) Source #
Given an array, an offset in 32 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) Source #
Given an array, an offset in 16 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) Source #
Given an array, an offset in bytes, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, an offset in machine words, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Given an array and an offset in machine words, write an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array and an offset in machine words, read an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld Source #
sets all of the bytes in
setAddrRange#
dest len c[dest, dest+len)
to the value c
.
Analogous to the standard C function memset
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d Source #
sets the byte range setByteArray#
ba off len c[off, off+len)
of
the MutableByteArray#
to the byte c
.
Warning: this can fail with an unchecked exception.
copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddrNonOverlapping#
src dest lenlen
bytes
from src
to dest
. As the name suggests, these two memory ranges
must not overlap, although this pre-condition is not checked.
Analogous to the standard C function memcpy
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddr#
src dest lenlen
bytes
from src
to dest
. These two memory ranges are allowed to overlap.
Analogous to the standard C function memmove
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Copy a memory range starting at the Addr# to the specified range in the MutableByteArray#. The memory region at Addr# and the ByteArray# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the MutableByteArray# to the memory range starting at the Addr#. The MutableByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the ByteArray# to the memory range starting at the Addr#. The ByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the ByteArray# (e.g. if the ByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range starting at offset copyMutableByteArrayNonOverlapping#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from
the MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are not
allowed to overlap, but this is also not checked.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the
range starting at offset copyMutableByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are
allowed to overlap, although this is only possible when the same
array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range
starting at offset copyByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
ByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain
the specified ranges, but this is not checked. The two arrays must
not be the same array in different states, but this is not checked
either.
Warning: this can fail with an unchecked exception.
compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #
compares
compareByteArrays#
src1 src1_ofs src2 src2_ofs nn
bytes starting at offset src1_ofs
in the first
ByteArray#
src1
to the range of n
bytes
(i.e. same length) starting at offset src2_ofs
of the second
ByteArray#
src2
. Both arrays must fully contain the
specified ranges, but this is not checked. Returns an Int#
less than, equal to, or greater than zero if the range is found,
respectively, to be byte-wise lexicographically less than, to
match, or be greater than the second range.
Since: ghc-prim-0.5.2.0
writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value; offset in machine words.
Warning: this can fail with an unchecked exception.
writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address; offset in machine words.
Warning: this can fail with an unchecked exception.
writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer; offset in machine words.
Warning: this can fail with an unchecked exception.
writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer; offset in machine words.
Warning: this can fail with an unchecked exception.
writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer; offset in bytes.
Warning: this can fail with an unchecked exception.
readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value; offset in machine words.
Warning: this can fail with an unchecked exception.
readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address; offset in machine words.
Warning: this can fail with an unchecked exception.
readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer; offset in machine words.
Warning: this can fail with an unchecked exception.
readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer; offset in machine words.
Warning: this can fail with an unchecked exception.
readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character; offset in bytes.
Warning: this can fail with an unchecked exception.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer; offset in bytes.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer; offset in bytes.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer; offset in bytes.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer; offset in bytes.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer; offset in bytes.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer; offset in bytes.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value; offset in bytes.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value; offset in bytes.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value; offset in bytes.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address; offset in bytes.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer; offset in bytes.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer; offset in bytes.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character; offset in bytes.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character; offset in bytes.
indexWord64Array# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer; offset in 8-byte words.
indexInt64Array# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer; offset in 8-byte words.
indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer; offset in 4-byte words.
indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer; offset in 4-byte words.
indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer; offset in 2-byte words.
indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer; offset in 2-byte words.
indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer; offset in bytes.
indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #
Read an 8-bit signed integer; offset in bytes.
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value; offset in machine words.
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value; offset in 8-byte words.
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value; offset in 4-byte words.
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address; offset in machine words.
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer; offset in machine words.
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer; offset in machine words.
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character; offset in 4-byte words.
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character; offset in bytes.
getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkMutableByteArray#
and resizeMutableByteArray#
.
Since: ghc-prim-0.5.0.0
sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #
Return the size of the array in bytes. Deprecated, it is
unsafe in the presence of shrinkMutableByteArray#
and resizeMutableByteArray#
operations on the same mutable byte
array.
sizeofByteArray# :: ByteArray# -> Int# Source #
Return the size of the array in bytes.
unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Make an immutable byte array mutable, without copying.
Since: ghc-prim-0.12.0.0
unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Source #
Make a mutable byte array immutable, without copying.
resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Resize mutable byte array to new specified size (in bytes), shrinking or growing it.
The returned MutableByteArray#
is either the original
MutableByteArray#
resized in-place or, if not possible, a newly
allocated (unpinned) MutableByteArray#
(with the original content
copied over).
To avoid undefined behaviour, the original MutableByteArray#
shall
not be accessed anymore after a resizeMutableByteArray#
has been
performed. Moreover, no reference to the old one should be kept in order
to allow garbage collection of the original MutableByteArray#
in
case a new MutableByteArray#
had to be allocated.
Since: ghc-prim-0.4.0.0
shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
Shrink mutable byte array to new specified size (in bytes), in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofMutableByteArray#
.
Assuming the non-profiling RTS, this primitive compiles to an O(1) operation in C--, modifying the array in-place. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.4.0.0
mutableByteArrayContents# :: MutableByteArray# d -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
byteArrayContents# :: ByteArray# -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
isByteArrayPinned# :: ByteArray# -> Int# Source #
Determine whether a ByteArray#
is guaranteed not to move during GC.
isMutableByteArrayPinned# :: MutableByteArray# d -> Int# Source #
Determine whether a MutableByteArray#
is guaranteed not to move
during GC.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newPinnedByteArray#
but allow specifying an arbitrary
alignment, which must be a power of two.
Warning: this can fail with an unchecked exception.
newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newByteArray#
but GC guarantees not to move it.
newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Create a new mutable byte array of specified size (in bytes), in the specified state thread. The size of the memory underlying the array will be rounded up to the platform's word size.
casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Unsafe, machine-level atomic compare and swap on an element within an array.
See the documentation of casArray#
.
Warning: this can fail with an unchecked exception.
thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Make an immutable array mutable, without copying.
unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) Source #
Make a mutable array immutable, without copying.
indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkSmallMutableArray#
and resizeSmallMutableArray#
.
Since: ghc-prim-0.6.1
sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# Source #
Return the number of elements in the array. Deprecated, it is
unsafe in the presence of shrinkSmallMutableArray#
and resizeSmallMutableArray#
operations on the same small mutable array.
sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# Source #
Return the number of elements in the array.
writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d Source #
Shrink mutable array to new specified size, in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofSmallMutableArray#
.
Assuming the non-profiling RTS, for the copying garbage collector (default) this primitive compiles to an O(1) operation in C--, modifying the array in-place. For the non-moving garbage collector, however, the time is proportional to the number of elements shrinked out. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.6.1
newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Given an array, an offset, the expected old value, and
the new value, perform an atomic compare and swap (i.e. write the new
value if the current value and the old value are the same pointer).
Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns
the element at the offset after the operation completes. This means that
on a success the new value is returned, and on a failure the actual old
value (not the expected one) is returned. Implies a full memory barrier.
The use of a pointer equality on a boxed value makes this function harder
to use correctly than casIntArray#
. All of the difficulties
of using reallyUnsafePtrEquality#
correctly apply to
casArray#
as well.
Warning: this can fail with an unchecked exception.
thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. In the case where the source and destination are the same array the source and destination regions may overlap.
Warning: this can fail with an unchecked exception.
copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) Source #
Make an immutable array mutable, without copying.
unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) Source #
Make a mutable array immutable, without copying.
indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #) Source #
Read from the specified index of an immutable array. The result is packaged into an unboxed unary tuple; the result itself is not yet evaluated. Pattern matching on the tuple forces the indexing of the array to happen but does not evaluate the element itself. Evaluating the thunk prevents additional thunks from building up on the heap. Avoiding these thunks, in turn, reduces references to the argument array, allowing it to be garbage collected more promptly.
sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# Source #
Return the number of elements in the array.
sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# Source #
Return the number of elements in the array.
writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
fnmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
fnmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
fnmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
fnmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
decodeFloat_Int# :: Float# -> (# Int#, Int# #) Source #
Convert to integers.
First Int#
in result is the mantissa; second is the exponent.
float2Double# :: Float# -> Double# Source #
atanhFloat# :: Float# -> Float# Source #
acoshFloat# :: Float# -> Float# Source #
asinhFloat# :: Float# -> Float# Source #
tanhFloat# :: Float# -> Float# Source #
coshFloat# :: Float# -> Float# Source #
sinhFloat# :: Float# -> Float# Source #
atanFloat# :: Float# -> Float# Source #
acosFloat# :: Float# -> Float# Source #
asinFloat# :: Float# -> Float# Source #
sqrtFloat# :: Float# -> Float# Source #
log1pFloat# :: Float# -> Float# Source #
expm1Float# :: Float# -> Float# Source #
float2Int# :: Float# -> Int# Source #
fabsFloat# :: Float# -> Float# Source #
negateFloat# :: Float# -> Float# Source #
decodeDouble_Int64# :: Double# -> (# Int64#, Int# #) Source #
Decode Double#
into mantissa and base-2 exponent.
decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) Source #
Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.
atanhDouble# :: Double# -> Double# Source #
acoshDouble# :: Double# -> Double# Source #
asinhDouble# :: Double# -> Double# Source #
tanhDouble# :: Double# -> Double# Source #
coshDouble# :: Double# -> Double# Source #
sinhDouble# :: Double# -> Double# Source #
atanDouble# :: Double# -> Double# Source #
acosDouble# :: Double# -> Double# Source #
asinDouble# :: Double# -> Double# Source #
tanDouble# :: Double# -> Double# Source #
cosDouble# :: Double# -> Double# Source #
sinDouble# :: Double# -> Double# Source #
sqrtDouble# :: Double# -> Double# Source #
log1pDouble# :: Double# -> Double# Source #
logDouble# :: Double# -> Double# Source #
expm1Double# :: Double# -> Double# Source #
expDouble# :: Double# -> Double# Source #
double2Float# :: Double# -> Float# Source #
double2Int# :: Double# -> Int# Source #
fabsDouble# :: Double# -> Double# Source #
negateDouble# :: Double# -> Double# Source #
narrow32Word# :: Word# -> Word# Source #
narrow16Word# :: Word# -> Word# Source #
narrow8Word# :: Word# -> Word# Source #
narrow32Int# :: Int# -> Int# Source #
narrow16Int# :: Int# -> Int# Source #
narrow8Int# :: Int# -> Int# Source #
bitReverse# :: Word# -> Word# Source #
Reverse the order of the bits in a word.
bitReverse64# :: Word64# -> Word64# Source #
Reverse the order of the bits in a 64-bit word.
bitReverse32# :: Word# -> Word# Source #
Reverse the order of the bits in a 32-bit word.
bitReverse16# :: Word# -> Word# Source #
Reverse the order of the bits in a 16-bit word.
bitReverse8# :: Word# -> Word# Source #
Reverse the order of the bits in a 8-bit word.
byteSwap64# :: Word64# -> Word64# Source #
Swap bytes in a 64 bits of a word.
byteSwap32# :: Word# -> Word# Source #
Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.
byteSwap16# :: Word# -> Word# Source #
Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.
pext# :: Word# -> Word# -> Word# Source #
Extract bits from a word at locations specified by a mask, aka parallel bit extract.
Software emulation:
pext :: Word -> Word -> Word pext src mask = loop 0 0 0 where loop i count result | i >= finiteBitSize (0 :: Word) = result | testBit mask i = loop (i + 1) (count + 1) (if testBit src i then setBit result count else result) | otherwise = loop (i + 1) count result
Since: ghc-prim-0.5.2.0
pext64# :: Word64# -> Word64# -> Word64# Source #
Extract bits from a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext32# :: Word# -> Word# -> Word# Source #
Extract bits from lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext16# :: Word# -> Word# -> Word# Source #
Extract bits from lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext8# :: Word# -> Word# -> Word# Source #
Extract bits from lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep# :: Word# -> Word# -> Word# Source #
Deposit bits to a word at locations specified by a mask, aka parallel bit deposit.
Software emulation:
pdep :: Word -> Word -> Word pdep src mask = go 0 src mask where go :: Word -> Word -> Word -> Word go result _ 0 = result go result src mask = go newResult newSrc newMask where maskCtz = countTrailingZeros mask newResult = if testBit src 0 then setBit result maskCtz else result newSrc = src `shiftR` 1 newMask = clearBit mask maskCtz
Since: ghc-prim-0.5.2.0
pdep64# :: Word64# -> Word64# -> Word64# Source #
Deposit bits to a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep32# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep16# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep8# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
uncheckedShiftRL# :: Word# -> Int# -> Word# Source #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedShiftL# :: Word# -> Int# -> Word# Source #
Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) Source #
Takes high word of dividend, then low word of dividend, then divisor. Requires that high word < divisor.
plusWord2# :: Word# -> Word# -> (# Word#, Word# #) Source #
Add unsigned integers, with the high part (carry) in the first
component of the returned pair and the low part in the second
component of the pair. See also addWordC#
.
subWordC# :: Word# -> Word# -> (# Word#, Int# #) Source #
Subtract unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow.
addWordC# :: Word# -> Word# -> (# Word#, Int# #) Source #
Add unsigned integers reporting overflow.
The first element of the pair is the result. The second element is
the carry flag, which is nonzero on overflow. See also plusWord2#
.
uncheckedIShiftRL# :: Int# -> Int# -> Int# Source #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRA# :: Int# -> Int# -> Int# Source #
Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftL# :: Int# -> Int# -> Int# Source #
Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
word2Double# :: Word# -> Double# Source #
Convert an Word#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Double#
1## == 1.0##
word2Float# :: Word# -> Float# Source #
Convert an Word#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Float#
1## == 1.0#
int2Double# :: Int# -> Double# Source #
Convert an Int#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Double#
1# == 1.0##
int2Float# :: Int# -> Float# Source #
Convert an Int#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Float#
1# == 1.0#
negateInt# :: Int# -> Int# Source #
Unary negation.
Since the negative Int#
range extends one further than the
positive range, negateInt#
of the most negative number is an
identity operation. This way, negateInt#
is always its own inverse.
quotInt# :: Int# -> Int# -> Int# Source #
Rounds towards zero. The behavior is undefined if the second argument is zero.
mulIntMayOflo# :: Int# -> Int# -> Int# Source #
Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommended implementation is to do a 32 x 32 -> 64 signed multiply, and subtract result[63:32] from (result[31] >>signed 31). If this is zero, meaning that the upper word is merely a sign extension of the lower one, no overflow can occur.
On a 64-bit platform it is not always possible to acquire the top 64 bits of the result. Therefore, a recommended implementation is to take the absolute value of both operands, and return 0 iff bits[63:31] of them are zero, since that means that their magnitudes fit within 31 bits, so the magnitude of the product must fit into 62 bits.
If in doubt, return non-zero, but do make an effort to create the
correct answer for small args, since otherwise the performance of
(*) :: Integer -> Integer -> Integer
will be poor.
timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) Source #
Return a triple (isHighNeeded,high,low) where high and low are respectively the high and low bits of the double-word result. isHighNeeded is a cheap way to test if the high word is a sign-extension of the low word (isHighNeeded = 0#) or not (isHighNeeded = 1#).
word64ToInt64# :: Word64# -> Int64# Source #
wordToWord64# :: Word# -> Word64# Source #
word64ToWord# :: Word64# -> Word# Source #
int64ToWord64# :: Int64# -> Word64# Source #
negateInt64# :: Int64# -> Int64# Source #
intToInt64# :: Int# -> Int64# Source #
int64ToInt# :: Int64# -> Int# Source #
word32ToInt32# :: Word32# -> Int32# Source #
notWord32# :: Word32# -> Word32# Source #
wordToWord32# :: Word# -> Word32# Source #
word32ToWord# :: Word32# -> Word# Source #
int32ToWord32# :: Int32# -> Word32# Source #
negateInt32# :: Int32# -> Int32# Source #
intToInt32# :: Int# -> Int32# Source #
int32ToInt# :: Int32# -> Int# Source #
word16ToInt16# :: Word16# -> Int16# Source #
notWord16# :: Word16# -> Word16# Source #
wordToWord16# :: Word# -> Word16# Source #
word16ToWord# :: Word16# -> Word# Source #
int16ToWord16# :: Int16# -> Word16# Source #
negateInt16# :: Int16# -> Int16# Source #
intToInt16# :: Int# -> Int16# Source #
int16ToInt# :: Int16# -> Int# Source #
word8ToInt8# :: Word8# -> Int8# Source #
wordToWord8# :: Word# -> Word8# Source #
word8ToWord# :: Word8# -> Word# Source #
int8ToWord8# :: Int8# -> Word8# Source #
negateInt8# :: Int8# -> Int8# Source #
intToInt8# :: Int# -> Int8# Source #
int8ToInt# :: Int8# -> Int# Source #
rightSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {s :: RuntimeRep} {n :: Multiplicity} {o :: Multiplicity} (a :: TYPE q) (b :: TYPE r) (c :: TYPE s). (a %n -> b %o -> c) -> b %o -> a %n -> c Source #
leftSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {n :: Multiplicity} (a :: TYPE q) (b :: TYPE r). (a %n -> b) -> a %n -> b Source #
proxy# :: forall {k} (a :: k). Proxy# a Source #
Witness for an unboxed Proxy#
value, which has no runtime
representation.
seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b infixr 0 Source #
The value of
is bottom if seq
a ba
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression
does
not guarantee that seq
a ba
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
This is an alias for the unboxed unit tuple constructor.
In earlier versions of GHC, void#
was a value
of the primitive type Void#
, which is now defined to be (# #)
.
realWorld# :: State# RealWorld Source #
The token used in the implementation of the IO monad as a state monad.
It does not pass any information at runtime.
See also runRW#
.
module GHC.Prim.Ext
Running RealWorld
state thread
runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o Source #
Apply a function to a
token. When manually applying
a function to State#
RealWorld
realWorld#
, it is necessary to use NOINLINE
to prevent
semantically undesirable floating. runRW#
is inlined, but only very late
in compilation after all floating is complete.
Bit shift operations
shiftL# :: Word# -> Int# -> Word# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word# Source #
Shift the argument right by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic) (although an arithmetic right shift wouldn't make sense for Word#)
iShiftL# :: Int# -> Int# -> Int# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int# Source #
Shift the argument right (signed) by the specified number of bits (which must be non-negative). The RA means "right, arithmetic" (as opposed to RL for logical)
iShiftRL# :: Int# -> Int# -> Int# Source #
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic)
Pointer comparison operations
reallyUnsafePtrEquality :: a -> a -> Int# Source #
Compare the underlying pointers of two values for equality.
Returns 1
if the pointers are equal and 0
otherwise.
The two values must be of the same type, of kind Type
.
See also reallyUnsafePtrEquality#
, which doesn't have
such restrictions.
unsafePtrEquality# :: forall (a :: UnliftedType) (b :: UnliftedType). a -> b -> Int# Source #
Compare the underlying pointers of two unlifted values for equality.
This is less dangerous than reallyUnsafePtrEquality
,
since the arguments are guaranteed to be evaluated.
This means there is no risk of accidentally comparing
a thunk.
It's however still more dangerous than e.g. sameArray#
.
eqStableName# :: forall {k :: Levity} {l :: Levity} (a :: TYPE ('BoxedRep k)) (b :: TYPE ('BoxedRep l)). StableName# a -> StableName# b -> Int# Source #
Compare two stable names for equality.
sameArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Array# a -> Int# Source #
Compare the underlying pointers of two arrays.
sameMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutableArray# s a -> MutableArray# s a -> Int# Source #
Compare the underlying pointers of two mutable arrays.
sameSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> SmallArray# a -> Int# Source #
Compare the underlying pointers of two small arrays.
sameSmallMutableArray# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). SmallMutableArray# s a -> SmallMutableArray# s a -> Int# Source #
Compare the underlying pointers of two small mutable arrays.
sameByteArray# :: ByteArray# -> ByteArray# -> Int# Source #
Compare the pointers of two byte arrays.
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# Source #
Compare the underlying pointers of two mutable byte arrays.
sameMVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MVar# s a -> MVar# s a -> Int# Source #
Compare the underlying pointers of two MVar#
s.
sameMutVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). MutVar# s a -> MutVar# s a -> Int# Source #
Compare the underlying pointers of two MutVar#
s.
sameTVar# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). TVar# s a -> TVar# s a -> Int# Source #
Compare the underlying pointers of two TVar#
s.
sameIOPort# :: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)). IOPort# s a -> IOPort# s a -> Int# Source #
Compare the underlying pointers of two IOPort#
s.
samePromptTag# :: PromptTag# a -> PromptTag# a -> Int# Source #
Compare the underlying pointers of two PromptTag#
s.
Compat wrapper
atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #) Source #
An implementation of the old atomicModifyMutVar#
primop in
terms of the new atomicModifyMutVar2#
primop, for backwards
compatibility. The type of this function is a bit bogus. It's
best to think of it as having type
atomicModifyMutVar# :: MutVar# s a -> (a -> (a, b)) -> State# s -> (# State# s, b #)
but there may be code that uses this with other two-field record types.
Resize functions
Resizing arrays of boxed elements is currently handled in library space (rather than being a primop) since there is not an efficient way to grow arrays. However, resize operations may become primops in a future release of GHC.
resizeSmallMutableArray# Source #
:: SmallMutableArray# s a | Array to resize |
-> Int# | New size of array |
-> a | Newly created slots initialized to this element. Only used when array is grown. |
-> State# s | |
-> (# State# s, SmallMutableArray# s a #) |
Resize a mutable array to new specified size. The returned
SmallMutableArray#
is either the original SmallMutableArray#
resized in-place or, if not possible, a newly allocated
SmallMutableArray#
with the original content copied over.
To avoid undefined behaviour, the original SmallMutableArray#
shall
not be accessed anymore after a resizeSmallMutableArray#
has been
performed. Moreover, no reference to the old one should be kept in order
to allow garbage collection of the original SmallMutableArray#
in
case a new SmallMutableArray#
had to be allocated.
Since: base-4.14.0.0
Fusion
Overloaded lists
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
fromList :: [Item l] -> l Source #
The fromList
function constructs the structure l
from the given
list of Item l
fromListN :: Int -> [Item l] -> l Source #
The fromListN
function takes the input list's length and potentially
uses it to construct the structure l
more efficiently compared to
fromList
. If the given number does not equal to the input list's length
the behaviour of fromListN
is not specified.
fromListN (length xs) xs == fromList xs
toList :: l -> [Item l] Source #
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.
Instances
IsList Version Source # | Since: base-4.8.0.0 |
IsList CallStack Source # | Be aware that 'fromList . toList = id' only for unfrozen Since: base-4.9.0.0 |
IsList (NonEmpty a) Source # | Since: base-4.9.0.0 |
IsList (ZipList a) Source # | Since: base-4.15.0.0 |
IsList [a] Source # | Since: base-4.7.0.0 |
Transform comprehensions
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).Down
a
If a
has an
instance associated with it then comparing two
values thus wrapped will give you the opposite of their normal sort order.
This is particularly useful when sorting in generalised list comprehensions,
as in: Ord
then sortWith by
.Down
x
>>>
compare True False
GT
>>>
compare (Down True) (Down False)
LT
If a
has a
instance then the wrapped instance also respects
the reversed ordering by exchanging the values of Bounded
and
minBound
.maxBound
>>>
minBound :: Int
-9223372036854775808
>>>
minBound :: Down Int
Down 9223372036854775807
All other instances of
behave as they do for Down
aa
.
Since: base-4.6.0.0
Instances
Applicative Down Source # | Since: base-4.11.0.0 | ||||
Functor Down Source # | Since: base-4.11.0.0 | ||||
Monad Down Source # | Since: base-4.11.0.0 | ||||
MonadFix Down Source # | Since: base-4.12.0.0 | ||||
Foldable Down Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Down m -> m Source # foldMap :: Monoid m => (a -> m) -> Down a -> m Source # foldMap' :: Monoid m => (a -> m) -> Down a -> m Source # foldr :: (a -> b -> b) -> b -> Down a -> b Source # foldr' :: (a -> b -> b) -> b -> Down a -> b Source # foldl :: (b -> a -> b) -> b -> Down a -> b Source # foldl' :: (b -> a -> b) -> b -> Down a -> b Source # foldr1 :: (a -> a -> a) -> Down a -> a Source # foldl1 :: (a -> a -> a) -> Down a -> a Source # toList :: Down a -> [a] Source # null :: Down a -> Bool Source # length :: Down a -> Int Source # elem :: Eq a => a -> Down a -> Bool Source # maximum :: Ord a => Down a -> a Source # minimum :: Ord a => Down a -> a Source # | |||||
Traversable Down Source # | Since: base-4.12.0.0 | ||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monoid a => Monoid (Down a) Source # | Since: base-4.11.0.0 | ||||
Semigroup a => Semigroup (Down a) Source # | Since: base-4.11.0.0 | ||||
Bits a => Bits (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord (.&.) :: Down a -> Down a -> Down a Source # (.|.) :: Down a -> Down a -> Down a Source # xor :: Down a -> Down a -> Down a Source # complement :: Down a -> Down a Source # shift :: Down a -> Int -> Down a Source # rotate :: Down a -> Int -> Down a Source # setBit :: Down a -> Int -> Down a Source # clearBit :: Down a -> Int -> Down a Source # complementBit :: Down a -> Int -> Down a Source # testBit :: Down a -> Int -> Bool Source # bitSizeMaybe :: Down a -> Maybe Int Source # bitSize :: Down a -> Int Source # isSigned :: Down a -> Bool Source # shiftL :: Down a -> Int -> Down a Source # unsafeShiftL :: Down a -> Int -> Down a Source # shiftR :: Down a -> Int -> Down a Source # unsafeShiftR :: Down a -> Int -> Down a Source # rotateL :: Down a -> Int -> Down a Source # | |||||
FiniteBits a => FiniteBits (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord finiteBitSize :: Down a -> Int Source # countLeadingZeros :: Down a -> Int Source # countTrailingZeros :: Down a -> Int Source # | |||||
Data a => Data (Down a) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Down a -> c (Down a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Down a) Source # toConstr :: Down a -> Constr Source # dataTypeOf :: Down a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Down a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Down a)) Source # gmapT :: (forall b. Data b => b -> b) -> Down a -> Down a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Down a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Down a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # | |||||
Bounded a => Bounded (Down a) Source # | Swaps Since: base-4.14.0.0 | ||||
(Enum a, Bounded a, Eq a) => Enum (Down a) Source # | Swaps Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.Data.Ord succ :: Down a -> Down a Source # pred :: Down a -> Down a Source # toEnum :: Int -> Down a Source # fromEnum :: Down a -> Int Source # enumFrom :: Down a -> [Down a] Source # enumFromThen :: Down a -> Down a -> [Down a] Source # enumFromTo :: Down a -> Down a -> [Down a] Source # enumFromThenTo :: Down a -> Down a -> Down a -> [Down a] Source # | |||||
Floating a => Floating (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord exp :: Down a -> Down a Source # log :: Down a -> Down a Source # sqrt :: Down a -> Down a Source # (**) :: Down a -> Down a -> Down a Source # logBase :: Down a -> Down a -> Down a Source # sin :: Down a -> Down a Source # cos :: Down a -> Down a Source # tan :: Down a -> Down a Source # asin :: Down a -> Down a Source # acos :: Down a -> Down a Source # atan :: Down a -> Down a Source # sinh :: Down a -> Down a Source # cosh :: Down a -> Down a Source # tanh :: Down a -> Down a Source # asinh :: Down a -> Down a Source # acosh :: Down a -> Down a Source # atanh :: Down a -> Down a Source # log1p :: Down a -> Down a Source # expm1 :: Down a -> Down a Source # | |||||
RealFloat a => RealFloat (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord floatRadix :: Down a -> Integer Source # floatDigits :: Down a -> Int Source # floatRange :: Down a -> (Int, Int) Source # decodeFloat :: Down a -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Down a Source # exponent :: Down a -> Int Source # significand :: Down a -> Down a Source # scaleFloat :: Int -> Down a -> Down a Source # isNaN :: Down a -> Bool Source # isInfinite :: Down a -> Bool Source # isDenormalized :: Down a -> Bool Source # isNegativeZero :: Down a -> Bool Source # | |||||
Storable a => Storable (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord sizeOf :: Down a -> Int Source # alignment :: Down a -> Int Source # peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) Source # pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (Down a) Source # pokeByteOff :: Ptr b -> Int -> Down a -> IO () Source # | |||||
Generic (Down a) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Ix a => Ix (Down a) Source # | Since: base-4.14.0.0 | ||||
Num a => Num (Down a) Source # | Since: base-4.11.0.0 | ||||
Defined in GHC.Internal.Data.Ord | |||||
Read a => Read (Down a) Source # | This instance would be equivalent to the derived instances of the
Since: base-4.7.0.0 | ||||
Fractional a => Fractional (Down a) Source # | Since: base-4.14.0.0 | ||||
Real a => Real (Down a) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Data.Ord toRational :: Down a -> Rational Source # | |||||
RealFrac a => RealFrac (Down a) Source # | Since: base-4.14.0.0 | ||||
Show a => Show (Down a) Source # | This instance would be equivalent to the derived instances of the
Since: base-4.7.0.0 | ||||
Eq a => Eq (Down a) Source # | Since: base-4.6.0.0 | ||||
Ord a => Ord (Down a) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Data.Ord | |||||
type Rep1 Down Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (Down a) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics |
groupWith :: Ord b => (a -> b) -> [a] -> [[a]] Source #
The groupWith
function uses the user supplied function which
projects an element out of every list element in order to first sort the
input list and then to form groups by equality on these projected elements
sortWith :: Ord b => (a -> b) -> [a] -> [a] Source #
The sortWith
function sorts a list of elements using the
user supplied function to project something out of each element
In general if the user supplied function is expensive to compute then
you should probably be using sortOn
, as it only needs
to compute it once for each element. sortWith
, on the other hand
must compute the mapping function for every comparison that it performs.
the :: Eq a => [a] -> a Source #
the
ensures that all the elements of the list are identical
and then returns that unique element
Strings
Overloaded string literals
class IsString a where Source #
IsString
is used in combination with the -XOverloadedStrings
language extension to convert the literals to different string types.
For example, if you use the text package, you can say
{-# LANGUAGE OverloadedStrings #-} myText = "hello world" :: Text
Internally, the extension will convert this to the equivalent of
myText = fromString @Text ("hello world" :: String)
Note: You can use fromString
in normal code as well,
but the usual performance/memory efficiency problems with String
apply.
fromString :: String -> a Source #
Instances
IsString a => IsString (Identity a) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.String fromString :: String -> Identity a Source # | |
a ~ Char => IsString [a] Source # |
Since: base-2.1 |
Defined in GHC.Internal.Data.String fromString :: String -> [a] Source # | |
IsString a => IsString (Const a b) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.String fromString :: String -> Const a b Source # |
CString
unpackCString# :: Addr# -> [Char] Source #
unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a Source #
unpackCStringUtf8# :: Addr# -> [Char] Source #
cstringLength# :: Addr# -> Int# Source #
Compute the length of a NUL-terminated string. This address
must refer to immutable memory. GHC includes a built-in rule for
constant folding when the argument is a statically-known literal.
That is, a core-to-core pass reduces the expression
cstringLength# "hello"#
to the constant 5#
.
Debugging
Breakpoints
breakpoint :: a -> a Source #
breakpointCond :: Bool -> a -> a Source #
Event logging
traceEvent :: String -> IO () Source #
Deprecated: Use traceEvent
or traceEventIO
The call stack
currentCallStack :: IO [String] Source #
Returns a [String]
representing the current call stack. This
can be useful for debugging.
The implementation uses the call-stack simulation maintained by the
profiler, so it only works if the program was compiled with -prof
and contains suitable SCC annotations (e.g. by using -fprof-auto
).
Otherwise, the list returned is likely to be empty or
uninformative.
Since: base-4.5.0.0
Ids with special behaviour
The call inline f
arranges that f
is inlined, regardless of
its size. More precisely, the call inline f
rewrites to the
right-hand side of f
's definition. This allows the programmer to
control inlining from a particular call site rather than the
definition site of the function (c.f. INLINE
pragmas).
This inlining occurs regardless of the argument to the call or the
size of f
's definition; it is unconditional. The main caveat is
that f
's definition must be visible to the compiler; it is
therefore recommended to mark the function with an INLINABLE
pragma at its definition so that GHC guarantees to record its
unfolding regardless of size.
If no inlining takes place, the inline
function expands to the
identity function in Phase zero, so its use imposes no overhead.
The call noinline f
arranges that f
will not be inlined.
It is removed during CorePrep so that its use imposes no overhead
(besides the fact that it blocks inlining.)
The lazy
function restrains strictness analysis a little. The
call lazy e
means the same as e
, but lazy
has a magical
property so far as strictness analysis is concerned: it is lazy in
its first argument, even though its semantics is strict. After
strictness analysis has run, calls to lazy
are inlined to be the
identity function.
This behaviour is occasionally useful when controlling evaluation
order. Notably, lazy
is used in the library definition of
par
:
par :: a -> b -> b par x y = case (par# x) of _ -> lazy y
If lazy
were not lazy, par
would look strict in
y
which would defeat the whole purpose of par
.
oneShot :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b Source #
The oneShot
function can be used to give a hint to the compiler that its
argument will be called at most once, which may (or may not) enable certain
optimizations. It can be useful to improve the performance of code in continuation
passing style.
If oneShot
is used wrongly, then it may be that computations whose result
that would otherwise be shared are re-evaluated every time they are used. Otherwise,
the use of oneShot
is safe.
oneShot
is representation-polymorphic: the type variables may refer to lifted
or unlifted types.
considerAccessible :: Bool Source #
Semantically, considerAccessible = True
. But it has special meaning
to the pattern-match checker, which will never flag the clause in which
considerAccessible
occurs as a guard as redundant or inaccessible.
Example:
case (x, x) of (True, True) -> 1 (False, False) -> 2 (True, False) -> 3 -- Warning: redundant
The pattern-match checker will warn here that the third clause is redundant.
It will stop doing so if the clause is adorned with considerAccessible
:
case (x, x) of (True, True) -> 1 (False, False) -> 2 (True, False) | considerAccessible -> 3 -- No warning
Put considerAccessible
as the last statement of the guard to avoid get
confusing results from the pattern-match checker, which takes "consider
accessible" by word.
SpecConstr annotations
data SpecConstrAnnotation Source #
Deprecated, use SPEC
directly instead.
Annotating a type with NoSpecConstr
will make SpecConstr
not specialise for arguments of that type,
e. g., {-# ANN type SPEC ForceSpecConstr #-}
.
Instances
Data SpecConstrAnnotation Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Exts gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpecConstrAnnotation -> c SpecConstrAnnotation Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpecConstrAnnotation Source # toConstr :: SpecConstrAnnotation -> Constr Source # dataTypeOf :: SpecConstrAnnotation -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpecConstrAnnotation) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpecConstrAnnotation) Source # gmapT :: (forall b. Data b => b -> b) -> SpecConstrAnnotation -> SpecConstrAnnotation Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpecConstrAnnotation -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpecConstrAnnotation -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpecConstrAnnotation -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecConstrAnnotation -> m SpecConstrAnnotation Source # | |
Eq SpecConstrAnnotation Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Exts (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # |
SPEC
is used by GHC in the SpecConstr
pass in order to inform
the compiler when to be particularly aggressive. In particular, it
tells GHC to specialize regardless of size or the number of
specializations. However, not all loops fall into this category.
Libraries can specify this by using SPEC
data type to inform which
loops should be aggressively specialized. For example,
instead of
loop x where loop arg = ...
write
loop SPEC x where loop !_ arg = ...
There is no semantic difference between SPEC
and SPEC2
,
we just need a type with two constructors lest it is optimised away
before SpecConstr
.
This type is reexported from GHC.Exts since GHC 9.0 and base-4.15
.
For compatibility with earlier releases import it from GHC.Types
in ghc-prim
package.
Since: ghc-prim-0.3.1.0
Coercions
Safe coercions
These are available from the Trustworthy module Data.Coerce as well.
Since: base-4.7.0.0
coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b Source #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
When used in conversions involving a newtype wrapper, make sure the newtype constructor is in scope.
This function is representation-polymorphic, but the
RuntimeRep
type argument is marked as Inferred
, meaning
that it is not available for visible type application. This means
the typechecker will accept
.coerce
@Int
@Age 42
Examples
>>>
newtype TTL = TTL Int deriving (Eq, Ord, Show)
>>>
newtype Age = Age Int deriving (Eq, Ord, Show)
>>>
coerce (Age 42) :: TTL
TTL 42>>>
coerce (+ (1 :: Int)) (Age 42) :: TTL
TTL 43>>>
coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
[TTL 43,TTL 25]
Very unsafe coercion
unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b Source #
Highly, terribly dangerous coercion from one representation type to another. Misuse of this function can invite the garbage collector to trounce upon your data and then laugh in your face. You don't want this function. Really.
Casting class dictionaries with single methods
class WithDict cls meth where Source #
The constraint
can be solved when evidence for
the constraint WithDict
cls methcls
can be provided in the form of a dictionary of
type meth
. This requires cls
to be a class constraint whose single
method has type meth
.
For more (important) details on how this works, see
Note [withDict]
in GHC.Tc.Instance.Class in GHC.
Since: ghc-prim-0.9.0
withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r Source #
Converting ADTs to constructor tags
class DataToTag (a :: TYPE ('BoxedRep lev)) where Source #
evaluates its argument and returns the index
(starting at zero) of the constructor used to produce that
argument. Any algebraic data type with all of its constructors
in scope may be used with dataToTag#
dataToTag#
.
>>>
dataToTag# (Left ())
0#>>>
dataToTag# (Right undefined)
1#
dataToTag# :: a -> Int# Source #
The maximum tuple size
maxTupleSize :: Int Source #