Copyright | (c) The University of Glasgow 2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
- Representations of some basic types
- The maximum tuple size
- Primitive operations
- Fusion
- Overloaded string literals
- Debugging
- Ids with special behaviour
- Running
RealWorld
state transformers - Safe coercions
- Equality
- Representation polymorphism
- Transform comprehensions
- Event logging
- SpecConstr annotations
- The call stack
- The Constraint kind
- The Any type
- Overloaded lists
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Note: no other base module should import this module.
Synopsis
- data Int = I# Int#
- data Word = W# Word#
- data Float = F# Float#
- data Double = D# Double#
- data Char = C# Char#
- data Ptr a = Ptr Addr#
- data FunPtr a = FunPtr Addr#
- maxTupleSize :: Int
- seq :: a -> b -> b
- realWorld# :: State# RealWorld
- void# :: Void#
- unsafeCoerce# :: a -> b
- nullAddr# :: Addr#
- magicDict :: a
- proxy# :: Proxy# a
- data Addr# :: TYPE AddrRep
- data Array# (a :: Type) :: Type -> TYPE UnliftedRep
- data ByteArray# :: TYPE UnliftedRep
- data Char# :: TYPE WordRep
- data Double# :: TYPE DoubleRep
- data Float# :: TYPE FloatRep
- data Int# :: TYPE IntRep
- data Int32# :: TYPE IntRep
- data Int64# :: TYPE Int64Rep
- data Weak# (a :: Type) :: Type -> TYPE UnliftedRep
- data MutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data MutableByteArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data MVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data RealWorld :: Type
- data StablePtr# (a :: Type) :: Type -> TYPE AddrRep
- data ArrayArray# :: TYPE UnliftedRep
- data MutableArrayArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data State# (a :: Type) :: Type -> TYPE (TupleRep ([] :: [RuntimeRep]))
- data StableName# (a :: Type) :: Type -> TYPE UnliftedRep
- data MutVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data Void# :: TYPE (TupleRep ([] :: [RuntimeRep]))
- data Word# :: TYPE WordRep
- data Word32# :: TYPE WordRep
- data Word64# :: TYPE Word64Rep
- data ThreadId# :: TYPE UnliftedRep
- data BCO# :: TYPE UnliftedRep
- data TVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data Compact# :: TYPE UnliftedRep
- data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] :: [RuntimeRep]))
- data SmallArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data SmallMutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- 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)
- gtChar# :: Char# -> Char# -> Int#
- geChar# :: Char# -> Char# -> Int#
- eqChar# :: Char# -> Char# -> Int#
- neChar# :: Char# -> Char# -> Int#
- ltChar# :: Char# -> Char# -> Int#
- leChar# :: Char# -> Char# -> Int#
- ord# :: Char# -> Int#
- (+#) :: Int# -> Int# -> Int#
- (-#) :: Int# -> Int# -> Int#
- (*#) :: Int# -> Int# -> Int#
- mulIntMayOflo# :: Int# -> Int# -> Int#
- quotInt# :: Int# -> Int# -> Int#
- remInt# :: Int# -> Int# -> Int#
- quotRemInt# :: Int# -> Int# -> (#Int#, Int##)
- andI# :: Int# -> Int# -> Int#
- orI# :: Int# -> Int# -> Int#
- xorI# :: Int# -> Int# -> Int#
- notI# :: Int# -> Int#
- negateInt# :: Int# -> Int#
- addIntC# :: Int# -> Int# -> (#Int#, Int##)
- subIntC# :: Int# -> Int# -> (#Int#, Int##)
- (>#) :: Int# -> Int# -> Int#
- (>=#) :: Int# -> Int# -> Int#
- (==#) :: Int# -> Int# -> Int#
- (/=#) :: Int# -> Int# -> Int#
- (<#) :: Int# -> Int# -> Int#
- (<=#) :: Int# -> Int# -> Int#
- chr# :: Int# -> Char#
- int2Word# :: Int# -> Word#
- int2Float# :: Int# -> Float#
- int2Double# :: Int# -> Double#
- word2Float# :: Word# -> Float#
- word2Double# :: Word# -> Double#
- uncheckedIShiftL# :: Int# -> Int# -> Int#
- uncheckedIShiftRA# :: Int# -> Int# -> Int#
- uncheckedIShiftRL# :: Int# -> Int# -> Int#
- plusWord# :: Word# -> Word# -> Word#
- addWordC# :: Word# -> Word# -> (#Word#, Int##)
- subWordC# :: Word# -> Word# -> (#Word#, Int##)
- plusWord2# :: Word# -> Word# -> (#Word#, Word##)
- minusWord# :: Word# -> Word# -> Word#
- timesWord# :: Word# -> Word# -> Word#
- timesWord2# :: Word# -> Word# -> (#Word#, Word##)
- quotWord# :: Word# -> Word# -> Word#
- remWord# :: Word# -> Word# -> Word#
- quotRemWord# :: Word# -> Word# -> (#Word#, Word##)
- quotRemWord2# :: Word# -> Word# -> Word# -> (#Word#, Word##)
- and# :: Word# -> Word# -> Word#
- or# :: Word# -> Word# -> Word#
- xor# :: Word# -> Word# -> Word#
- not# :: Word# -> Word#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- word2Int# :: Word# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- geWord# :: Word# -> Word# -> Int#
- eqWord# :: Word# -> Word# -> Int#
- neWord# :: Word# -> Word# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- leWord# :: Word# -> Word# -> Int#
- popCnt8# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt64# :: Word# -> Word#
- popCnt# :: Word# -> Word#
- pdep8# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep32# :: Word# -> Word# -> Word#
- pdep64# :: Word# -> Word# -> Word#
- pdep# :: Word# -> Word# -> Word#
- pext8# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext32# :: Word# -> Word# -> Word#
- pext64# :: Word# -> Word# -> Word#
- pext# :: Word# -> Word# -> Word#
- clz8# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz32# :: Word# -> Word#
- clz64# :: Word# -> Word#
- clz# :: Word# -> Word#
- ctz8# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz32# :: Word# -> Word#
- ctz64# :: Word# -> Word#
- ctz# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- byteSwap32# :: Word# -> Word#
- byteSwap64# :: Word# -> Word#
- byteSwap# :: Word# -> Word#
- narrow8Int# :: Int# -> Int#
- narrow16Int# :: Int# -> Int#
- narrow32Int# :: Int# -> Int#
- narrow8Word# :: Word# -> Word#
- narrow16Word# :: Word# -> Word#
- narrow32Word# :: Word# -> Word#
- (>##) :: Double# -> Double# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (<=##) :: Double# -> Double# -> Int#
- (+##) :: Double# -> Double# -> Double#
- (-##) :: Double# -> Double# -> Double#
- (*##) :: Double# -> Double# -> Double#
- (/##) :: Double# -> Double# -> Double#
- negateDouble# :: Double# -> Double#
- fabsDouble# :: Double# -> Double#
- double2Int# :: Double# -> Int#
- double2Float# :: Double# -> Float#
- expDouble# :: Double# -> Double#
- logDouble# :: Double# -> Double#
- sqrtDouble# :: Double# -> Double#
- sinDouble# :: Double# -> Double#
- cosDouble# :: Double# -> Double#
- tanDouble# :: Double# -> Double#
- asinDouble# :: Double# -> Double#
- acosDouble# :: Double# -> Double#
- atanDouble# :: Double# -> Double#
- sinhDouble# :: Double# -> Double#
- coshDouble# :: Double# -> Double#
- tanhDouble# :: Double# -> Double#
- (**##) :: Double# -> Double# -> Double#
- decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)
- decodeDouble_Int64# :: Double# -> (#Int#, Int##)
- gtFloat# :: Float# -> Float# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- leFloat# :: Float# -> Float# -> Int#
- plusFloat# :: Float# -> Float# -> Float#
- minusFloat# :: Float# -> Float# -> Float#
- timesFloat# :: Float# -> Float# -> Float#
- divideFloat# :: Float# -> Float# -> Float#
- negateFloat# :: Float# -> Float#
- fabsFloat# :: Float# -> Float#
- float2Int# :: Float# -> Int#
- expFloat# :: Float# -> Float#
- logFloat# :: Float# -> Float#
- sqrtFloat# :: Float# -> Float#
- sinFloat# :: Float# -> Float#
- cosFloat# :: Float# -> Float#
- tanFloat# :: Float# -> Float#
- asinFloat# :: Float# -> Float#
- acosFloat# :: Float# -> Float#
- atanFloat# :: Float# -> Float#
- sinhFloat# :: Float# -> Float#
- coshFloat# :: Float# -> Float#
- tanhFloat# :: Float# -> Float#
- powerFloat# :: Float# -> Float# -> Float#
- float2Double# :: Float# -> Double#
- decodeFloat_Int# :: Float# -> (#Int#, Int##)
- newArray# :: Int# -> a -> State# d -> (#State# d, MutableArray# d a#)
- sameMutableArray# :: MutableArray# d a -> MutableArray# d a -> Int#
- readArray# :: MutableArray# d a -> Int# -> State# d -> (#State# d, a#)
- writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofArray# :: Array# a -> Int#
- sizeofMutableArray# :: MutableArray# d a -> Int#
- indexArray# :: Array# a -> Int# -> (#a#)
- unsafeFreezeArray# :: MutableArray# d a -> State# d -> (#State# d, Array# a#)
- unsafeThawArray# :: Array# a -> State# d -> (#State# d, MutableArray# d a#)
- copyArray# :: Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyMutableArray# :: MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneArray# :: Array# a -> Int# -> Int# -> Array# a
- cloneMutableArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#)
- freezeArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, Array# a#)
- thawArray# :: Array# a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#)
- casArray# :: MutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#)
- newSmallArray# :: Int# -> a -> State# d -> (#State# d, SmallMutableArray# d a#)
- sameSmallMutableArray# :: SmallMutableArray# d a -> SmallMutableArray# d a -> Int#
- readSmallArray# :: SmallMutableArray# d a -> Int# -> State# d -> (#State# d, a#)
- writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofSmallArray# :: SmallArray# a -> Int#
- sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int#
- indexSmallArray# :: SmallArray# a -> Int# -> (#a#)
- unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (#State# d, SmallArray# a#)
- unsafeThawSmallArray# :: SmallArray# a -> State# d -> (#State# d, SmallMutableArray# d a#)
- copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copySmallMutableArray# :: SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a
- cloneSmallMutableArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#)
- freezeSmallArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallArray# a#)
- thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#)
- casSmallArray# :: SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#)
- newByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#)
- newPinnedByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#)
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- isByteArrayPinned# :: ByteArray# -> Int#
- byteArrayContents# :: ByteArray# -> Addr#
- sameMutableByteArray# :: MutableByteArray# d -> MutableByteArray# d -> Int#
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (#State# d, ByteArray##)
- sizeofByteArray# :: ByteArray# -> Int#
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (#State# d, Int##)
- indexCharArray# :: ByteArray# -> Int# -> Char#
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexInt8Array# :: ByteArray# -> Int# -> Int#
- indexInt16Array# :: ByteArray# -> Int# -> Int#
- indexInt32Array# :: ByteArray# -> Int# -> Int#
- indexInt64Array# :: ByteArray# -> Int# -> Int#
- indexWord8Array# :: ByteArray# -> Int# -> Word#
- indexWord16Array# :: ByteArray# -> Int# -> Word#
- indexWord32Array# :: ByteArray# -> Int# -> Word#
- indexWord64Array# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- newArrayArray# :: Int# -> State# d -> (#State# d, MutableArrayArray# d#)
- sameMutableArrayArray# :: MutableArrayArray# d -> MutableArrayArray# d -> Int#
- unsafeFreezeArrayArray# :: MutableArrayArray# d -> State# d -> (#State# d, ArrayArray##)
- sizeofArrayArray# :: ArrayArray# -> Int#
- sizeofMutableArrayArray# :: MutableArrayArray# d -> Int#
- indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray#
- indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray#
- readByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ByteArray##)
- readMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- readArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ArrayArray##)
- readMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableArrayArray# d#)
- writeByteArrayArray# :: MutableArrayArray# d -> Int# -> ByteArray# -> State# d -> State# d
- writeMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> MutableByteArray# d -> State# d -> State# d
- writeArrayArrayArray# :: MutableArrayArray# d -> Int# -> ArrayArray# -> State# d -> State# d
- writeMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> State# d -> State# d
- copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d
- plusAddr# :: Addr# -> Int# -> Addr#
- minusAddr# :: Addr# -> Addr# -> Int#
- remAddr# :: Addr# -> Int# -> Int#
- addr2Int# :: Addr# -> Int#
- int2Addr# :: Int# -> Addr#
- gtAddr# :: Addr# -> Addr# -> Int#
- geAddr# :: Addr# -> Addr# -> Int#
- eqAddr# :: Addr# -> Addr# -> Int#
- neAddr# :: Addr# -> Addr# -> Int#
- ltAddr# :: Addr# -> Addr# -> Int#
- leAddr# :: Addr# -> Addr# -> Int#
- indexCharOffAddr# :: Addr# -> Int# -> Char#
- indexWideCharOffAddr# :: Addr# -> Int# -> Char#
- indexIntOffAddr# :: Addr# -> Int# -> Int#
- indexWordOffAddr# :: Addr# -> Int# -> Word#
- indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- indexFloatOffAddr# :: Addr# -> Int# -> Float#
- indexDoubleOffAddr# :: Addr# -> Int# -> Double#
- indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
- indexInt8OffAddr# :: Addr# -> Int# -> Int#
- indexInt16OffAddr# :: Addr# -> Int# -> Int#
- indexInt32OffAddr# :: Addr# -> Int# -> Int#
- indexInt64OffAddr# :: Addr# -> Int# -> Int#
- indexWord8OffAddr# :: Addr# -> Int# -> Word#
- indexWord16OffAddr# :: Addr# -> Int# -> Word#
- indexWord32OffAddr# :: Addr# -> Int# -> Word#
- indexWord64OffAddr# :: Addr# -> Int# -> Word#
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Addr##)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Float##)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Double##)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- newMutVar# :: a -> State# d -> (#State# d, MutVar# d a#)
- readMutVar# :: MutVar# d a -> State# d -> (#State# d, a#)
- writeMutVar# :: MutVar# d a -> a -> State# d -> State# d
- sameMutVar# :: MutVar# d a -> MutVar# d a -> Int#
- atomicModifyMutVar# :: MutVar# d a -> (a -> b) -> State# d -> (#State# d, c#)
- casMutVar# :: MutVar# d a -> a -> a -> State# d -> (#State# d, Int#, a#)
- catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- raise# :: b -> a
- raiseIO# :: a -> State# RealWorld -> (#State# RealWorld, b#)
- maskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- maskUninterruptible# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- unmaskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- getMaskingState# :: State# RealWorld -> (#State# RealWorld, Int##)
- atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- retry# :: State# RealWorld -> (#State# RealWorld, a#)
- catchRetry# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- catchSTM# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- newTVar# :: a -> State# d -> (#State# d, TVar# d a#)
- readTVar# :: TVar# d a -> State# d -> (#State# d, a#)
- readTVarIO# :: TVar# d a -> State# d -> (#State# d, a#)
- writeTVar# :: TVar# d a -> a -> State# d -> State# d
- sameTVar# :: TVar# d a -> TVar# d a -> Int#
- newMVar# :: State# d -> (#State# d, MVar# d a#)
- takeMVar# :: MVar# d a -> State# d -> (#State# d, a#)
- tryTakeMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#)
- putMVar# :: MVar# d a -> a -> State# d -> State# d
- tryPutMVar# :: MVar# d a -> a -> State# d -> (#State# d, Int##)
- readMVar# :: MVar# d a -> State# d -> (#State# d, a#)
- tryReadMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#)
- sameMVar# :: MVar# d a -> MVar# d a -> Int#
- isEmptyMVar# :: MVar# d a -> State# d -> (#State# d, Int##)
- delay# :: Int# -> State# d -> State# d
- waitRead# :: Int# -> State# d -> State# d
- waitWrite# :: Int# -> State# d -> State# d
- fork# :: a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
- forkOn# :: Int# -> a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
- killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
- yield# :: State# RealWorld -> State# RealWorld
- myThreadId# :: State# RealWorld -> (#State# RealWorld, ThreadId##)
- labelThread# :: ThreadId# -> Addr# -> State# RealWorld -> State# RealWorld
- isCurrentThreadBound# :: State# RealWorld -> (#State# RealWorld, Int##)
- noDuplicate# :: State# d -> State# d
- threadStatus# :: ThreadId# -> State# RealWorld -> (#State# RealWorld, Int#, Int#, Int##)
- mkWeak# :: a -> b -> (State# RealWorld -> (#State# RealWorld, c#)) -> State# RealWorld -> (#State# RealWorld, Weak# b#)
- mkWeakNoFinalizer# :: a -> b -> State# RealWorld -> (#State# RealWorld, Weak# b#)
- addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (#State# RealWorld, Int##)
- deRefWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, a#)
- finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, b#)#)
- touch# :: a -> State# RealWorld -> State# RealWorld
- makeStablePtr# :: a -> State# RealWorld -> (#State# RealWorld, StablePtr# a#)
- deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (#State# RealWorld, a#)
- eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int#
- makeStableName# :: a -> State# RealWorld -> (#State# RealWorld, StableName# a#)
- eqStableName# :: StableName# a -> StableName# b -> Int#
- stableNameToInt# :: StableName# a -> Int#
- compactNew# :: Word# -> State# RealWorld -> (#State# RealWorld, Compact##)
- compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld
- compactContains# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, Int##)
- compactContainsAny# :: a -> State# RealWorld -> (#State# RealWorld, Int##)
- compactGetFirstBlock# :: Compact# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##)
- compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##)
- compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr##)
- compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (#State# RealWorld, Compact#, Addr##)
- compactAdd# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#)
- compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#)
- compactSize# :: Compact# -> State# RealWorld -> (#State# RealWorld, Word##)
- reallyUnsafePtrEquality# :: a -> a -> Int#
- par# :: a -> Int#
- spark# :: a -> State# d -> (#State# d, a#)
- seq# :: a -> State# d -> (#State# d, a#)
- getSpark# :: State# d -> (#State# d, Int#, a#)
- numSparks# :: State# d -> (#State# d, Int##)
- dataToTag# :: a -> Int#
- tagToEnum# :: Int# -> a
- addrToAny# :: Addr# -> (#a#)
- anyToAddr# :: a -> State# RealWorld -> (#State# RealWorld, Addr##)
- mkApUpd0# :: BCO# -> (#a#)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (#State# d, BCO##)
- unpackClosure# :: a -> (#Addr#, ByteArray#, Array# b#)
- getApStackVal# :: a -> Int# -> (#Int#, b#)
- getCCSOf# :: a -> State# d -> (#State# d, Addr##)
- getCurrentCCS# :: a -> State# d -> (#State# d, Addr##)
- clearCCS# :: (State# d -> (#State# d, a#)) -> State# d -> (#State# d, a#)
- traceEvent# :: Addr# -> State# d -> State# d
- traceMarker# :: Addr# -> State# d -> State# d
- getThreadAllocationCounter# :: State# RealWorld -> (#State# RealWorld, Int##)
- setThreadAllocationCounter# :: Int# -> State# RealWorld -> State# RealWorld
- broadcastInt8X16# :: Int# -> Int8X16#
- broadcastInt16X8# :: Int# -> Int16X8#
- broadcastInt32X4# :: Int# -> Int32X4#
- broadcastInt64X2# :: Int# -> Int64X2#
- broadcastInt8X32# :: Int# -> Int8X32#
- broadcastInt16X16# :: Int# -> Int16X16#
- broadcastInt32X8# :: Int# -> Int32X8#
- broadcastInt64X4# :: Int# -> Int64X4#
- broadcastInt8X64# :: Int# -> Int8X64#
- broadcastInt16X32# :: Int# -> Int16X32#
- broadcastInt32X16# :: Int# -> Int32X16#
- broadcastInt64X8# :: Int# -> Int64X8#
- broadcastWord8X16# :: Word# -> Word8X16#
- broadcastWord16X8# :: Word# -> Word16X8#
- broadcastWord32X4# :: Word# -> Word32X4#
- broadcastWord64X2# :: Word# -> Word64X2#
- broadcastWord8X32# :: Word# -> Word8X32#
- broadcastWord16X16# :: Word# -> Word16X16#
- broadcastWord32X8# :: Word# -> Word32X8#
- broadcastWord64X4# :: Word# -> Word64X4#
- broadcastWord8X64# :: Word# -> Word8X64#
- broadcastWord16X32# :: Word# -> Word16X32#
- broadcastWord32X16# :: Word# -> Word32X16#
- broadcastWord64X8# :: Word# -> Word64X8#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- packInt8X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X16#
- packInt16X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X8#
- packInt32X4# :: (#Int#, Int#, Int#, Int##) -> Int32X4#
- packInt64X2# :: (#Int#, Int##) -> Int64X2#
- packInt8X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X32#
- packInt16X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X16#
- packInt32X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X8#
- packInt64X4# :: (#Int#, Int#, Int#, Int##) -> Int64X4#
- packInt8X64# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X64#
- packInt16X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X32#
- packInt32X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X16#
- packInt64X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int64X8#
- packWord8X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X16#
- packWord16X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X8#
- packWord32X4# :: (#Word#, Word#, Word#, Word##) -> Word32X4#
- packWord64X2# :: (#Word#, Word##) -> Word64X2#
- packWord8X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X32#
- packWord16X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X16#
- packWord32X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X8#
- packWord64X4# :: (#Word#, Word#, Word#, Word##) -> Word64X4#
- packWord8X64# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X64#
- packWord16X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X32#
- packWord32X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X16#
- packWord64X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word64X8#
- packFloatX4# :: (#Float#, Float#, Float#, Float##) -> FloatX4#
- packDoubleX2# :: (#Double#, Double##) -> DoubleX2#
- packFloatX8# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX8#
- packDoubleX4# :: (#Double#, Double#, Double#, Double##) -> DoubleX4#
- packFloatX16# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX16#
- packDoubleX8# :: (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) -> DoubleX8#
- unpackInt8X16# :: Int8X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X8# :: Int16X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X4# :: Int32X4# -> (#Int#, Int#, Int#, Int##)
- unpackInt64X2# :: Int64X2# -> (#Int#, Int##)
- unpackInt8X32# :: Int8X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X16# :: Int16X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X8# :: Int32X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt64X4# :: Int64X4# -> (#Int#, Int#, Int#, Int##)
- unpackInt8X64# :: Int8X64# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X32# :: Int16X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X16# :: Int32X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt64X8# :: Int64X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackWord8X16# :: Word8X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X8# :: Word16X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X4# :: Word32X4# -> (#Word#, Word#, Word#, Word##)
- unpackWord64X2# :: Word64X2# -> (#Word#, Word##)
- unpackWord8X32# :: Word8X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X16# :: Word16X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X8# :: Word32X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord64X4# :: Word64X4# -> (#Word#, Word#, Word#, Word##)
- unpackWord8X64# :: Word8X64# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X32# :: Word16X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X16# :: Word32X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord64X8# :: Word64X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackFloatX4# :: FloatX4# -> (#Float#, Float#, Float#, Float##)
- unpackDoubleX2# :: DoubleX2# -> (#Double#, Double##)
- unpackFloatX8# :: FloatX8# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##)
- unpackDoubleX4# :: DoubleX4# -> (#Double#, Double#, Double#, Double##)
- unpackFloatX16# :: FloatX16# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##)
- unpackDoubleX8# :: DoubleX8# -> (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##)
- insertInt8X16# :: Int8X16# -> Int# -> Int# -> Int8X16#
- insertInt16X8# :: Int16X8# -> Int# -> Int# -> Int16X8#
- insertInt32X4# :: Int32X4# -> Int# -> Int# -> Int32X4#
- insertInt64X2# :: Int64X2# -> Int# -> Int# -> Int64X2#
- insertInt8X32# :: Int8X32# -> Int# -> Int# -> Int8X32#
- insertInt16X16# :: Int16X16# -> Int# -> Int# -> Int16X16#
- insertInt32X8# :: Int32X8# -> Int# -> Int# -> Int32X8#
- insertInt64X4# :: Int64X4# -> Int# -> Int# -> Int64X4#
- insertInt8X64# :: Int8X64# -> Int# -> Int# -> Int8X64#
- insertInt16X32# :: Int16X32# -> Int# -> Int# -> Int16X32#
- insertInt32X16# :: Int32X16# -> Int# -> Int# -> Int32X16#
- insertInt64X8# :: Int64X8# -> Int# -> Int# -> Int64X8#
- insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16#
- insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8#
- insertWord32X4# :: Word32X4# -> Word# -> Int# -> Word32X4#
- insertWord64X2# :: Word64X2# -> Word# -> Int# -> Word64X2#
- insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32#
- insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16#
- insertWord32X8# :: Word32X8# -> Word# -> Int# -> Word32X8#
- insertWord64X4# :: Word64X4# -> Word# -> Int# -> Word64X4#
- insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64#
- insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32#
- insertWord32X16# :: Word32X16# -> Word# -> Int# -> Word32X16#
- insertWord64X8# :: Word64X8# -> Word# -> Int# -> Word64X8#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt8X64# :: Int8X64# -> Int8X64#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue0# :: a -> State# d -> State# d
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- uncheckedShiftL64# :: Word# -> Int# -> Word#
- uncheckedShiftRL64# :: Word# -> Int# -> Word#
- uncheckedIShiftL64# :: Int# -> Int# -> Int#
- uncheckedIShiftRA64# :: Int# -> Int# -> Int#
- isTrue# :: Int# -> Bool
- build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- class IsString a where
- fromString :: String -> a
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- lazy :: a -> a
- inline :: a -> a
- oneShot :: (a -> b) -> a -> b
- runRW# :: (State# RealWorld -> o) -> o
- coerce :: Coercible a b => a -> b
- class a ~R# b => Coercible (a :: k0) (b :: k0)
- class a ~# b => (a :: k0) ~~ (b :: k1)
- data TYPE (a :: RuntimeRep) :: RuntimeRep -> Type
- data RuntimeRep
- data VecCount
- data VecElem
- newtype Down a = Down a
- groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
- the :: Eq a => [a] -> a
- traceEvent :: String -> IO ()
- data SpecConstrAnnotation
- currentCallStack :: IO [String]
- data Constraint
- type family Any :: k0 where ...
- class IsList l where
Representations of some basic types
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
Bounded Int Source # | Since: 2.1 |
Enum Int Source # | Since: 2.1 |
Defined in GHC.Enum | |
Eq Int | |
Integral Int Source # | Since: 2.0.1 |
Data Int Source # | Since: 4.0.0.0 |
Defined in 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 :: (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 # | |
Num Int Source # | Since: 2.1 |
Ord Int | |
Read Int Source # | Since: 2.1 |
Real Int Source # | Since: 2.0.1 |
Show Int Source # | Since: 2.1 |
Ix Int Source # | Since: 2.1 |
FiniteBits Int Source # | Since: 4.6.0.0 |
Bits Int Source # | Since: 2.1 |
Defined in Data.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 # | |
Storable Int Source # | Since: 2.1 |
PrintfArg Int Source # | Since: 2.1 |
Defined in Text.Printf formatArg :: Int -> FieldFormatter Source # parseFormat :: Int -> ModifierParser Source # | |
Generic1 (URec Int :: k -> Type) Source # | |
Functor (URec Int :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec Int :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Int m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Int a -> m Source # foldr :: (a -> b -> b) -> b -> URec Int a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Int a -> b Source # foldl :: (b -> a -> b) -> b -> URec Int a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Int a -> b Source # foldr1 :: (a -> a -> a) -> URec Int a -> a Source # foldl1 :: (a -> a -> a) -> URec Int a -> a Source # toList :: URec Int a -> [a] Source # null :: URec Int a -> Bool Source # length :: URec Int a -> Int Source # elem :: Eq a => a -> URec Int a -> Bool Source # maximum :: Ord a => URec Int a -> a Source # minimum :: Ord a => URec Int a -> a Source # | |
Traversable (URec Int :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Int p) Source # | Since: 4.9.0.0 |
Ord (URec Int p) Source # | Since: 4.9.0.0 |
Show (URec Int p) Source # | Since: 4.9.0.0 |
Generic (URec Int p) Source # | |
data URec Int (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec Int :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Int p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics |
Instances
Bounded Word Source # | Since: 2.1 |
Enum Word Source # | Since: 2.1 |
Eq Word | |
Integral Word Source # | Since: 2.1 |
Data Word Source # | Since: 4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source # toConstr :: Word -> Constr Source # dataTypeOf :: Word -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) Source # gmapT :: (forall b. Data b => b -> b) -> Word -> Word Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # | |
Num Word Source # | Since: 2.1 |
Ord Word | |
Read Word Source # | Since: 4.5.0.0 |
Real Word Source # | Since: 2.1 |
Show Word Source # | Since: 2.1 |
Ix Word Source # | Since: 4.6.0.0 |
FiniteBits Word Source # | Since: 4.6.0.0 |
Bits Word Source # | Since: 2.1 |
Defined in Data.Bits (.&.) :: Word -> Word -> Word Source # (.|.) :: Word -> Word -> Word Source # xor :: Word -> Word -> Word Source # complement :: Word -> Word Source # shift :: Word -> Int -> Word Source # rotate :: Word -> Int -> Word Source # setBit :: Word -> Int -> Word Source # clearBit :: Word -> Int -> Word Source # complementBit :: Word -> Int -> Word Source # testBit :: Word -> Int -> Bool Source # bitSizeMaybe :: Word -> Maybe Int Source # bitSize :: Word -> Int Source # isSigned :: Word -> Bool Source # shiftL :: Word -> Int -> Word Source # unsafeShiftL :: Word -> Int -> Word Source # shiftR :: Word -> Int -> Word Source # unsafeShiftR :: Word -> Int -> Word Source # rotateL :: Word -> Int -> Word Source # | |
Storable Word Source # | Since: 2.1 |
Defined in Foreign.Storable sizeOf :: Word -> Int Source # alignment :: Word -> Int Source # peekElemOff :: Ptr Word -> Int -> IO Word Source # pokeElemOff :: Ptr Word -> Int -> Word -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word Source # pokeByteOff :: Ptr b -> Int -> Word -> IO () Source # | |
PrintfArg Word Source # | Since: 2.1 |
Defined in Text.Printf formatArg :: Word -> FieldFormatter Source # parseFormat :: Word -> ModifierParser Source # | |
Generic1 (URec Word :: k -> Type) Source # | |
Functor (URec Word :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec Word :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Word m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Word a -> m Source # foldr :: (a -> b -> b) -> b -> URec Word a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Word a -> b Source # foldl :: (b -> a -> b) -> b -> URec Word a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Word a -> b Source # foldr1 :: (a -> a -> a) -> URec Word a -> a Source # foldl1 :: (a -> a -> a) -> URec Word a -> a Source # toList :: URec Word a -> [a] Source # null :: URec Word a -> Bool Source # length :: URec Word a -> Int Source # elem :: Eq a => a -> URec Word a -> Bool Source # maximum :: Ord a => URec Word a -> a Source # minimum :: Ord a => URec Word a -> a Source # | |
Traversable (URec Word :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Word p) Source # | Since: 4.9.0.0 |
Ord (URec Word p) Source # | Since: 4.9.0.0 |
Show (URec Word p) Source # | Since: 4.9.0.0 |
Generic (URec Word p) Source # | |
data URec Word (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec Word :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Word p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics |
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
Enum Float Source # | Since: 2.1 |
Defined in GHC.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 # | |
Eq Float | Note that due to the presence of
Also note that
|
Floating Float Source # | Since: 2.1 |
Defined in GHC.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 # | |
Fractional Float Source # | Note that due to the presence of
Since: 2.1 |
Data Float Source # | Since: 4.0.0.0 |
Defined in 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 :: (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 # | |
Num Float Source # | Note that due to the presence of
Also note that due to the presence of -0,
Since: 2.1 |
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Read Float Source # | Since: 2.1 |
Real Float Source # | Since: 2.1 |
RealFloat Float Source # | Since: 2.1 |
Defined in GHC.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 # | |
RealFrac Float Source # | Since: 2.1 |
Show Float Source # | Since: 2.1 |
Storable Float Source # | Since: 2.1 |
Defined in 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 # | |
PrintfArg Float Source # | Since: 2.1 |
Defined in Text.Printf formatArg :: Float -> FieldFormatter Source # parseFormat :: Float -> ModifierParser Source # | |
Generic1 (URec Float :: k -> Type) Source # | |
Functor (URec Float :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec Float :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Float m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Float a -> m Source # foldr :: (a -> b -> b) -> b -> URec Float a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Float a -> b Source # foldl :: (b -> a -> b) -> b -> URec Float a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Float a -> b Source # foldr1 :: (a -> a -> a) -> URec Float a -> a Source # foldl1 :: (a -> a -> a) -> URec Float a -> a Source # toList :: URec Float a -> [a] Source # null :: URec Float a -> Bool Source # length :: URec Float a -> Int Source # elem :: Eq a => a -> URec Float a -> Bool Source # maximum :: Ord a => URec Float a -> a Source # minimum :: Ord a => URec Float a -> a Source # | |
Traversable (URec Float :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) Source # sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) Source # mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) Source # sequence :: Monad m => URec Float (m a) -> m (URec Float a) Source # | |
Eq (URec Float p) Source # | |
Ord (URec Float p) Source # | |
Defined in GHC.Generics | |
Show (URec Float p) Source # | |
Generic (URec Float p) Source # | |
data URec Float (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec Float :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Float p) Source # | |
Defined in GHC.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
Enum Double Source # | Since: 2.1 |
Defined in GHC.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 # | |
Eq Double | Note that due to the presence of
Also note that
|
Floating Double Source # | Since: 2.1 |
Defined in GHC.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 # | |
Fractional Double Source # | Note that due to the presence of
Since: 2.1 |
Data Double Source # | Since: 4.0.0.0 |
Defined in 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 :: (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 # | |
Num Double Source # | Note that due to the presence of
Also note that due to the presence of -0,
Since: 2.1 |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Read Double Source # | Since: 2.1 |
Real Double Source # | Since: 2.1 |
RealFloat Double Source # | Since: 2.1 |
Defined in GHC.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 # | |
RealFrac Double Source # | Since: 2.1 |
Show Double Source # | Since: 2.1 |
Storable Double Source # | Since: 2.1 |
Defined in 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 # | |
PrintfArg Double Source # | Since: 2.1 |
Defined in Text.Printf formatArg :: Double -> FieldFormatter Source # parseFormat :: Double -> ModifierParser Source # | |
Generic1 (URec Double :: k -> Type) Source # | |
Functor (URec Double :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec Double :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Double m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Double a -> m Source # foldr :: (a -> b -> b) -> b -> URec Double a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Double a -> b Source # foldl :: (b -> a -> b) -> b -> URec Double a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Double a -> b Source # foldr1 :: (a -> a -> a) -> URec Double a -> a Source # foldl1 :: (a -> a -> a) -> URec Double a -> a Source # toList :: URec Double a -> [a] Source # null :: URec Double a -> Bool Source # length :: URec Double a -> Int Source # elem :: Eq a => a -> URec Double a -> Bool Source # maximum :: Ord a => URec Double a -> a Source # minimum :: Ord a => URec Double a -> a Source # | |
Traversable (URec Double :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) Source # sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) Source # mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) Source # sequence :: Monad m => URec Double (m a) -> m (URec Double a) Source # | |
Eq (URec Double p) Source # | Since: 4.9.0.0 |
Ord (URec Double p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Show (URec Double p) Source # | Since: 4.9.0.0 |
Generic (URec Double p) Source # | |
data URec Double (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec Double :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Double p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and chr
).
Instances
Bounded Char Source # | Since: 2.1 |
Enum Char Source # | Since: 2.1 |
Eq Char | |
Data Char Source # | Since: 4.0.0.0 |
Defined in 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 :: (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 # | |
Ord Char | |
Read Char Source # | Since: 2.1 |
Show Char Source # | Since: 2.1 |
Ix Char Source # | Since: 2.1 |
Storable Char Source # | Since: 2.1 |
Defined in 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 # | |
IsChar Char Source # | Since: 2.1 |
PrintfArg Char Source # | Since: 2.1 |
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |
Generic1 (URec Char :: k -> Type) Source # | |
Functor (URec Char :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec Char :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Char m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Char a -> m Source # foldr :: (a -> b -> b) -> b -> URec Char a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Char a -> b Source # foldl :: (b -> a -> b) -> b -> URec Char a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Char a -> b Source # foldr1 :: (a -> a -> a) -> URec Char a -> a Source # foldl1 :: (a -> a -> a) -> URec Char a -> a Source # toList :: URec Char a -> [a] Source # null :: URec Char a -> Bool Source # length :: URec Char a -> Int Source # elem :: Eq a => a -> URec Char a -> Bool Source # maximum :: Ord a => URec Char a -> a Source # minimum :: Ord a => URec Char a -> a Source # | |
Traversable (URec Char :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Char p) Source # | Since: 4.9.0.0 |
Ord (URec Char p) Source # | Since: 4.9.0.0 |
Show (URec Char p) Source # | Since: 4.9.0.0 |
Generic (URec Char p) Source # | |
data URec Char (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec Char :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Char p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics |
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 # | |
Eq (Ptr a) Source # | Since: 2.1 |
Data a => Data (Ptr a) Source # | Since: 4.8.0.0 |
Defined in 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 :: (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 # | |
Ord (Ptr a) Source # | Since: 2.1 |
Show (Ptr a) Source # | Since: 2.1 |
Storable (Ptr a) Source # | Since: 2.1 |
Defined in 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 # | |
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: 4.9.0.0 |
Foldable (URec (Ptr ()) :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec (Ptr ()) m -> m Source # foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m Source # foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # toList :: URec (Ptr ()) a -> [a] Source # null :: URec (Ptr ()) a -> Bool Source # length :: URec (Ptr ()) a -> Int Source # elem :: Eq a => a -> URec (Ptr ()) a -> Bool Source # maximum :: Ord a => URec (Ptr ()) a -> a Source # minimum :: Ord a => URec (Ptr ()) a -> a Source # | |
Traversable (URec (Ptr ()) :: Type -> Type) Source # | Since: 4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) Source # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) Source # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) Source # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) Source # | |
Eq (URec (Ptr ()) p) Source # | Since: 4.9.0.0 |
Ord (URec (Ptr ()) p) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
Generic (URec (Ptr ()) p) Source # | |
data URec (Ptr ()) (p :: k) Source # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) Source # | Since: 4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) Source # | Since: 4.9.0.0 |
Defined in GHC.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
Eq (FunPtr a) Source # | |
Ord (FunPtr a) Source # | |
Show (FunPtr a) Source # | Since: 2.1 |
Storable (FunPtr a) Source # | Since: 2.1 |
Defined in 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 # |
The maximum tuple size
maxTupleSize :: Int Source #
Primitive operations
The value of seq a b
is bottom if a
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 seq a b
does
not guarantee that a
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.
unsafeCoerce# :: a -> b #
The function unsafeCoerce#
allows you to side-step the typechecker entirely. That
is, it allows you to coerce any type into any other type. If you use this function,
you had better get it right, otherwise segmentation faults await. It is generally
used when you want to write a program that you know is well-typed, but where Haskell's
type system is not expressive enough to prove that it is well typed.
The following uses of unsafeCoerce#
are supposed to work (i.e. not lead to
spurious compile-time or run-time crashes):
- Casting any lifted type to
Any
- Casting
Any
back to the real type - Casting an unboxed type to another unboxed type of the same size.
(Casting between floating-point and integral types does not work.
See the
GHC.Float
module for functions to do work.) - Casting between two types that have the same runtime representation. One case is when
the two types differ only in "phantom" type parameters, for example
Ptr Int
toPtr Float
, or[Int]
to[Float]
when the list is known to be empty. Also, anewtype
of a typeT
has the same representation at runtime asT
.
Other uses of unsafeCoerce#
are undefined. In particular, you should not use
unsafeCoerce#
to cast a T to an algebraic data type D, unless T is also
an algebraic data type. For example, do not cast Int->Int
to Bool
, even if
you later cast that Bool
back to Int->Int
before applying it. The reasons
have to do with GHC's internal representation details (for the cognoscenti, data values
can be entered but function closures cannot). If you want a safe type to cast things
to, use Any
, which is not an algebraic data type.
An arbitrary machine address assumed to point outside the garbage-collected heap.
data ByteArray# :: TYPE UnliftedRep #
data MutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep #
data MutableByteArray# (a :: Type) :: Type -> TYPE UnliftedRep #
data MVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep #
A shared mutable variable (not the same as a MutVar#
!).
(Note: in a non-concurrent implementation, (MVar# a)
can be
represented by (MutVar# (Maybe a))
.)
RealWorld
is deeply magical. It is primitive, but it is not
unlifted (hence ptrArg
). We never manipulate values of type
RealWorld
; it's only used in the type system, to parameterise State#
.
data ArrayArray# :: TYPE UnliftedRep #
data MutableArrayArray# (a :: Type) :: Type -> TYPE UnliftedRep #
data State# (a :: Type) :: Type -> TYPE (TupleRep ([] :: [RuntimeRep])) #
State#
is the primitive, unlifted type of states. It has
one type parameter, thus State# RealWorld
, or State# s
,
where s is a type variable. The only purpose of the type parameter
is to keep different state threads separate. It is represented by
nothing at all.
data StableName# (a :: Type) :: Type -> TYPE UnliftedRep #
data MutVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep #
A MutVar#
behaves like a single-element mutable array.
data Void# :: TYPE (TupleRep ([] :: [RuntimeRep])) #
data ThreadId# :: TYPE UnliftedRep #
(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 BCO# :: TYPE UnliftedRep #
Primitive bytecode type.
data Compact# :: TYPE UnliftedRep #
data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] :: [RuntimeRep])) #
The type constructor Proxy#
is used to bear witness to some
type variable. It's used when you want to pass around proxy values
for doing things like modelling type applications. A Proxy#
is not only unboxed, it also has a polymorphic kind, and has no
runtime representation, being totally free.
data SmallArray# (a :: Type) :: Type -> TYPE UnliftedRep #
data SmallMutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep #
data Word16X16# :: TYPE (VecRep Vec16 Word16ElemRep) #
data Word16X32# :: TYPE (VecRep Vec32 Word16ElemRep) #
data Word32X16# :: TYPE (VecRep Vec16 Word32ElemRep) #
mulIntMayOflo# :: Int# -> Int# -> Int# #
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.
quotInt# :: Int# -> Int# -> Int# #
Rounds towards zero. The behavior is undefined if the second argument is zero.
remInt# :: Int# -> Int# -> Int# #
Satisfies (quotInt# x y) *# y +# (remInt# x y) == x
. The
behavior is undefined if the second argument is zero.
negateInt# :: Int# -> Int# #
addIntC# :: Int# -> Int# -> (#Int#, Int##) #
Add signed integers reporting overflow.
First member of result is the sum truncated to an Int#
;
second member is zero if the true sum fits in an Int#
,
nonzero if overflow occurred (the sum is either too large
or too small to fit in an Int#
).
subIntC# :: Int# -> Int# -> (#Int#, Int##) #
Subtract signed integers reporting overflow.
First member of result is the difference truncated to an Int#
;
second member is zero if the true difference fits in an Int#
,
nonzero if overflow occurred (the difference is either too large
or too small to fit in an Int#
).
int2Float# :: Int# -> Float# #
int2Double# :: Int# -> Double# #
word2Float# :: Word# -> Float# #
word2Double# :: Word# -> Double# #
uncheckedIShiftL# :: Int# -> Int# -> Int# #
Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRA# :: Int# -> Int# -> Int# #
Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRL# :: Int# -> Int# -> Int# #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
addWordC# :: Word# -> Word# -> (#Word#, Int##) #
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#
.
subWordC# :: Word# -> Word# -> (#Word#, Int##) #
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.
plusWord2# :: Word# -> Word# -> (#Word#, Word##) #
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#
.
minusWord# :: Word# -> Word# -> Word# #
timesWord# :: Word# -> Word# -> Word# #
uncheckedShiftL# :: Word# -> Int# -> Word# #
Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedShiftRL# :: Word# -> Int# -> Word# #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
pdep8# :: Word# -> Word# -> Word# #
Deposit bits to lower 8 bits of a word at locations specified by a mask.
pdep16# :: Word# -> Word# -> Word# #
Deposit bits to lower 16 bits of a word at locations specified by a mask.
pdep32# :: Word# -> Word# -> Word# #
Deposit bits to lower 32 bits of a word at locations specified by a mask.
pext8# :: Word# -> Word# -> Word# #
Extract bits from lower 8 bits of a word at locations specified by a mask.
pext16# :: Word# -> Word# -> Word# #
Extract bits from lower 16 bits of a word at locations specified by a mask.
pext32# :: Word# -> Word# -> Word# #
Extract bits from lower 32 bits of a word at locations specified by a mask.
byteSwap16# :: Word# -> Word# #
Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.
byteSwap32# :: Word# -> Word# #
Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.
byteSwap64# :: Word# -> Word# #
Swap bytes in a 64 bits of a word.
narrow8Int# :: Int# -> Int# #
narrow16Int# :: Int# -> Int# #
narrow32Int# :: Int# -> Int# #
narrow8Word# :: Word# -> Word# #
narrow16Word# :: Word# -> Word# #
narrow32Word# :: Word# -> Word# #
negateDouble# :: Double# -> Double# #
fabsDouble# :: Double# -> Double# #
double2Int# :: Double# -> Int# #
Truncates a Double#
value to the nearest Int#
.
Results are undefined if the truncation if truncation yields
a value outside the range of Int#
.
double2Float# :: Double# -> Float# #
expDouble# :: Double# -> Double# #
logDouble# :: Double# -> Double# #
sqrtDouble# :: Double# -> Double# #
sinDouble# :: Double# -> Double# #
cosDouble# :: Double# -> Double# #
tanDouble# :: Double# -> Double# #
asinDouble# :: Double# -> Double# #
acosDouble# :: Double# -> Double# #
atanDouble# :: Double# -> Double# #
sinhDouble# :: Double# -> Double# #
coshDouble# :: Double# -> Double# #
tanhDouble# :: Double# -> Double# #
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##) #
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.
decodeDouble_Int64# :: Double# -> (#Int#, Int##) #
Decode Double#
into mantissa and base-2 exponent.
plusFloat# :: Float# -> Float# -> Float# #
minusFloat# :: Float# -> Float# -> Float# #
timesFloat# :: Float# -> Float# -> Float# #
divideFloat# :: Float# -> Float# -> Float# #
negateFloat# :: Float# -> Float# #
fabsFloat# :: Float# -> Float# #
float2Int# :: Float# -> Int# #
Truncates a Float#
value to the nearest Int#
.
Results are undefined if the truncation if truncation yields
a value outside the range of Int#
.
sqrtFloat# :: Float# -> Float# #
asinFloat# :: Float# -> Float# #
acosFloat# :: Float# -> Float# #
atanFloat# :: Float# -> Float# #
sinhFloat# :: Float# -> Float# #
coshFloat# :: Float# -> Float# #
tanhFloat# :: Float# -> Float# #
powerFloat# :: Float# -> Float# -> Float# #
float2Double# :: Float# -> Double# #
decodeFloat_Int# :: Float# -> (#Int#, Int##) #
Convert to integers.
First Int#
in result is the mantissa; second is the exponent.
newArray# :: Int# -> a -> State# d -> (#State# d, MutableArray# d a#) #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
sameMutableArray# :: MutableArray# d a -> MutableArray# d a -> Int# #
readArray# :: MutableArray# d a -> Int# -> State# d -> (#State# d, a#) #
Read from specified index of mutable array. Result is not yet evaluated.
writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d #
Write to specified index of mutable array.
sizeofArray# :: Array# a -> Int# #
Return the number of elements in the array.
sizeofMutableArray# :: MutableArray# d a -> Int# #
Return the number of elements in the array.
indexArray# :: Array# a -> Int# -> (#a#) #
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.
unsafeFreezeArray# :: MutableArray# d a -> State# d -> (#State# d, Array# a#) #
Make a mutable array immutable, without copying.
unsafeThawArray# :: Array# a -> State# d -> (#State# d, MutableArray# d a#) #
Make an immutable array mutable, without copying.
copyArray# :: Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d #
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.
copyMutableArray# :: MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d #
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.
cloneArray# :: Array# a -> Int# -> Int# -> Array# a #
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.
cloneMutableArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#) #
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.
freezeArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, Array# a#) #
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.
thawArray# :: Array# a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#) #
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.
casArray# :: MutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#) #
Unsafe, machine-level atomic compare and swap on an element within an Array.
newSmallArray# :: Int# -> a -> State# d -> (#State# d, SmallMutableArray# d a#) #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
sameSmallMutableArray# :: SmallMutableArray# d a -> SmallMutableArray# d a -> Int# #
readSmallArray# :: SmallMutableArray# d a -> Int# -> State# d -> (#State# d, a#) #
Read from specified index of mutable array. Result is not yet evaluated.
writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d #
Write to specified index of mutable array.
sizeofSmallArray# :: SmallArray# a -> Int# #
Return the number of elements in the array.
sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int# #
Return the number of elements in the array.
indexSmallArray# :: SmallArray# a -> Int# -> (#a#) #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (#State# d, SmallArray# a#) #
Make a mutable array immutable, without copying.
unsafeThawSmallArray# :: SmallArray# a -> State# d -> (#State# d, SmallMutableArray# d a#) #
Make an immutable array mutable, without copying.
copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d #
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.
copySmallMutableArray# :: SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d #
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.
cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a #
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.
cloneSmallMutableArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#) #
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.
freezeSmallArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallArray# a#) #
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.
thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#) #
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.
casSmallArray# :: SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#) #
Unsafe, machine-level atomic compare and swap on an element within an array.
newByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#) #
Create a new mutable byte array of specified size (in bytes), in the specified state thread.
newPinnedByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#) #
Create a mutable byte array that the GC guarantees not to move.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (#State# d, MutableByteArray# d#) #
Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move.
isMutableByteArrayPinned# :: MutableByteArray# d -> Int# #
Determine whether a MutableByteArray#
is guaranteed not to move
during GC.
isByteArrayPinned# :: ByteArray# -> Int# #
Determine whether a ByteArray#
is guaranteed not to move during GC.
byteArrayContents# :: ByteArray# -> Addr# #
Intended for use with pinned arrays; otherwise very unsafe!
sameMutableByteArray# :: MutableByteArray# d -> MutableByteArray# d -> Int# #
shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d #
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 sizeofMutableArray#
.
resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#) #
Resize (unpinned) mutable byte array to new specified size (in bytes).
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.
unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (#State# d, ByteArray##) #
Make a mutable byte array immutable, without copying.
sizeofByteArray# :: ByteArray# -> Int# #
Return the size of the array in bytes.
sizeofMutableByteArray# :: MutableByteArray# d -> Int# #
Return the size of the array in bytes. Note that this is deprecated as it is
unsafe in the presence of concurrent resize operations on the same byte
array. See getSizeofMutableByteArray
.
getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (#State# d, Int##) #
Return the number of elements in the array.
indexCharArray# :: ByteArray# -> Int# -> Char# #
Read 8-bit character; offset in bytes.
indexWideCharArray# :: ByteArray# -> Int# -> Char# #
Read 31-bit character; offset in 4-byte words.
indexIntArray# :: ByteArray# -> Int# -> Int# #
indexWordArray# :: ByteArray# -> Int# -> Word# #
indexAddrArray# :: ByteArray# -> Int# -> Addr# #
indexFloatArray# :: ByteArray# -> Int# -> Float# #
indexDoubleArray# :: ByteArray# -> Int# -> Double# #
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a #
indexInt8Array# :: ByteArray# -> Int# -> Int# #
Read 8-bit integer; offset in bytes.
indexInt16Array# :: ByteArray# -> Int# -> Int# #
Read 16-bit integer; offset in 16-bit words.
indexInt32Array# :: ByteArray# -> Int# -> Int# #
Read 32-bit integer; offset in 32-bit words.
indexInt64Array# :: ByteArray# -> Int# -> Int# #
Read 64-bit integer; offset in 64-bit words.
indexWord8Array# :: ByteArray# -> Int# -> Word# #
Read 8-bit word; offset in bytes.
indexWord16Array# :: ByteArray# -> Int# -> Word# #
Read 16-bit word; offset in 16-bit words.
indexWord32Array# :: ByteArray# -> Int# -> Word# #
Read 32-bit word; offset in 32-bit words.
indexWord64Array# :: ByteArray# -> Int# -> Word# #
Read 64-bit word; offset in 64-bit words.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# #
Read 8-bit character; offset in bytes.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# #
Read 31-bit character; offset in bytes.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# #
Read address; offset in bytes.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# #
Read float; offset in bytes.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# #
Read double; offset in bytes.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a #
Read stable pointer; offset in bytes.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int# #
Read 16-bit int; offset in bytes.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int# #
Read 32-bit int; offset in bytes.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# #
Read 64-bit int; offset in bytes.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# #
Read int; offset in bytes.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word# #
Read 16-bit word; offset in bytes.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word# #
Read 32-bit word; offset in bytes.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# #
Read 64-bit word; offset in bytes.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# #
Read word; offset in bytes.
readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) #
Read 8-bit character; offset in bytes.
readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) #
Read 31-bit character; offset in 4-byte words.
readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
Read integer; offset in words.
readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
Read word; offset in words.
readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##) #
readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##) #
readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##) #
readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#) #
readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) #
readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) #
readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##) #
readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##) #
readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##) #
readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#) #
readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) #
readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) #
writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #
Write 8-bit character; offset in bytes.
writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #
Write 31-bit character; offset in 4-byte words.
writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #
writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d #
writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d #
writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d #
writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d #
writeInt8Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeInt16Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeInt32Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeInt64Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeWord8Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #
writeWord16Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #
writeWord32Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #
writeWord64Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #
writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #
writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #
writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d #
writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d #
writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d #
writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d #
writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #
writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #