Maintainer | ghc-devs@haskell.org |
---|---|
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
- The word size story.
- Char#
- Int#
- Word#
- Narrowings
- Double#
- Float#
- Arrays
- Small Arrays
- Byte Arrays
- Arrays of arrays
- Addr#
- Mutable variables
- Exceptions
- STM-accessible Mutable Variables
- Synchronized Mutable Variables
- Delay/wait operations
- Concurrency primitives
- Weak pointers
- Stable pointers and names
- Compact normal form
- Unsafe pointer equality
- Parallelism
- Tag to enum stuff
- Bytecode operations
- Misc
- Etc
- Safe coercions
- SIMD Vectors
- Prefetch
GHC's primitive types and operations. Use GHC.Exts from the base package instead of importing this module directly.
- data Char#
- 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#
- data 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#
- data Word#
- plusWord# :: Word# -> Word# -> Word#
- 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#
- 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#
- data Double#
- (>##) :: 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##)
- data Float#
- 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##)
- data Array# a
- data MutableArray# s a
- newArray# :: Int# -> a -> State# s -> (#State# s, MutableArray# s a#)
- sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int#
- readArray# :: MutableArray# s a -> Int# -> State# s -> (#State# s, a#)
- writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s
- sizeofArray# :: Array# a -> Int#
- sizeofMutableArray# :: MutableArray# s a -> Int#
- indexArray# :: Array# a -> Int# -> (#a#)
- unsafeFreezeArray# :: MutableArray# s a -> State# s -> (#State# s, Array# a#)
- unsafeThawArray# :: Array# a -> State# s -> (#State# s, MutableArray# s a#)
- copyArray# :: Array# a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s
- copyMutableArray# :: MutableArray# s a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s
- cloneArray# :: Array# a -> Int# -> Int# -> Array# a
- cloneMutableArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, MutableArray# s a#)
- freezeArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, Array# a#)
- thawArray# :: Array# a -> Int# -> Int# -> State# s -> (#State# s, MutableArray# s a#)
- casArray# :: MutableArray# s a -> Int# -> a -> a -> State# s -> (#State# s, Int#, a#)
- data SmallArray# a
- data SmallMutableArray# s a
- newSmallArray# :: Int# -> a -> State# s -> (#State# s, SmallMutableArray# s a#)
- sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int#
- readSmallArray# :: SmallMutableArray# s a -> Int# -> State# s -> (#State# s, a#)
- writeSmallArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> State# s
- sizeofSmallArray# :: SmallArray# a -> Int#
- sizeofSmallMutableArray# :: SmallMutableArray# s a -> Int#
- indexSmallArray# :: SmallArray# a -> Int# -> (#a#)
- unsafeFreezeSmallArray# :: SmallMutableArray# s a -> State# s -> (#State# s, SmallArray# a#)
- unsafeThawSmallArray# :: SmallArray# a -> State# s -> (#State# s, SmallMutableArray# s a#)
- copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s
- copySmallMutableArray# :: SmallMutableArray# s a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s
- cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a
- cloneSmallMutableArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, SmallMutableArray# s a#)
- freezeSmallArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, SmallArray# a#)
- thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# s -> (#State# s, SmallMutableArray# s a#)
- casSmallArray# :: SmallMutableArray# s a -> Int# -> a -> a -> State# s -> (#State# s, Int#, a#)
- data ByteArray#
- data MutableByteArray# s
- newByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
- newPinnedByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (#State# s, MutableByteArray# s#)
- isMutableByteArrayPinned# :: MutableByteArray# s -> Int#
- isByteArrayPinned# :: ByteArray# -> Int#
- byteArrayContents# :: ByteArray# -> Addr#
- sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int#
- shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s
- resizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, MutableByteArray# s#)
- unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (#State# s, ByteArray##)
- sizeofByteArray# :: ByteArray# -> Int#
- sizeofMutableByteArray# :: MutableByteArray# s -> Int#
- getSizeofMutableByteArray# :: MutableByteArray# s -> State# s -> (#State# s, 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#
- readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)
- readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)
- readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
- readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Addr##)
- readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Float##)
- readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Double##)
- readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, StablePtr# a#)
- readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
- readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
- readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
- readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
- writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
- writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
- writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
- writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
- writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
- writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
- writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
- writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
- writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
- writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
- writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- copyMutableByteArray# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# s -> State# s
- copyMutableByteArrayToAddr# :: MutableByteArray# s -> Int# -> Addr# -> Int# -> State# s -> State# s
- copyAddrToByteArray# :: Addr# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s
- atomicReadIntArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
- atomicWriteIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- casIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchAddIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchSubIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchAndIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchNandIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchOrIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- fetchXorIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)
- data ArrayArray#
- data MutableArrayArray# s
- newArrayArray# :: Int# -> State# s -> (#State# s, MutableArrayArray# s#)
- sameMutableArrayArray# :: MutableArrayArray# s -> MutableArrayArray# s -> Int#
- unsafeFreezeArrayArray# :: MutableArrayArray# s -> State# s -> (#State# s, ArrayArray##)
- sizeofArrayArray# :: ArrayArray# -> Int#
- sizeofMutableArrayArray# :: MutableArrayArray# s -> Int#
- indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray#
- indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray#
- readByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, ByteArray##)
- readMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, MutableByteArray# s#)
- readArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, ArrayArray##)
- readMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, MutableArrayArray# s#)
- writeByteArrayArray# :: MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s
- writeMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s
- writeArrayArrayArray# :: MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s
- writeMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s
- copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s
- copyMutableArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s
- data Addr#
- nullAddr# :: Addr#
- 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# s -> (#State# s, Char##)
- readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)
- readIntOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
- readWordOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
- readAddrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Addr##)
- readFloatOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Float##)
- readDoubleOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Double##)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, StablePtr# a#)
- readInt8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
- readInt16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
- readInt32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
- readInt64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
- readWord8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
- readWord16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
- readWord32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
- readWord64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# s -> State# s
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# s -> State# s
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# s -> State# s
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s
- writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
- writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
- writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
- writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
- writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
- writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
- writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
- writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
- data MutVar# s a
- newMutVar# :: a -> State# s -> (#State# s, MutVar# s a#)
- readMutVar# :: MutVar# s a -> State# s -> (#State# s, a#)
- writeMutVar# :: MutVar# s a -> a -> State# s -> State# s
- sameMutVar# :: MutVar# s a -> MutVar# s a -> Int#
- atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (#State# s, c#)
- casMutVar# :: MutVar# s a -> a -> a -> State# s -> (#State# s, Int#, a#)
- catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- raise# :: b -> o
- 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##)
- data TVar# s a
- 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#)
- check# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> State# RealWorld
- newTVar# :: a -> State# s -> (#State# s, TVar# s a#)
- readTVar# :: TVar# s a -> State# s -> (#State# s, a#)
- readTVarIO# :: TVar# s a -> State# s -> (#State# s, a#)
- writeTVar# :: TVar# s a -> a -> State# s -> State# s
- sameTVar# :: TVar# s a -> TVar# s a -> Int#
- data MVar# s a
- newMVar# :: State# s -> (#State# s, MVar# s a#)
- takeMVar# :: MVar# s a -> State# s -> (#State# s, a#)
- tryTakeMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#)
- putMVar# :: MVar# s a -> a -> State# s -> State# s
- tryPutMVar# :: MVar# s a -> a -> State# s -> (#State# s, Int##)
- readMVar# :: MVar# s a -> State# s -> (#State# s, a#)
- tryReadMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#)
- sameMVar# :: MVar# s a -> MVar# s a -> Int#
- isEmptyMVar# :: MVar# s a -> State# s -> (#State# s, Int##)
- delay# :: Int# -> State# s -> State# s
- waitRead# :: Int# -> State# s -> State# s
- waitWrite# :: Int# -> State# s -> State# s
- data State# s
- data RealWorld
- data ThreadId#
- 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# s -> State# s
- threadStatus# :: ThreadId# -> State# RealWorld -> (#State# RealWorld, Int#, Int#, Int##)
- data Weak# b
- mkWeak# :: o -> b -> (State# RealWorld -> (#State# RealWorld, c#)) -> State# RealWorld -> (#State# RealWorld, Weak# b#)
- mkWeakNoFinalizer# :: o -> 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# :: o -> State# RealWorld -> State# RealWorld
- data StablePtr# a
- data StableName# a
- 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#
- data Compact#
- 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# s -> (#State# s, a#)
- seq# :: a -> State# s -> (#State# s, a#)
- getSpark# :: State# s -> (#State# s, Int#, a#)
- numSparks# :: State# s -> (#State# s, Int##)
- dataToTag# :: a -> Int#
- tagToEnum# :: Int# -> a
- data BCO#
- addrToAny# :: Addr# -> (#a#)
- anyToAddr# :: a -> State# RealWorld -> (#State# RealWorld, Addr##)
- mkApUpd0# :: BCO# -> (#a#)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (#State# s, BCO##)
- unpackClosure# :: a -> (#Addr#, Array# b, ByteArray##)
- getApStackVal# :: a -> Int# -> (#Int#, b#)
- getCCSOf# :: a -> State# s -> (#State# s, Addr##)
- getCurrentCCS# :: a -> State# s -> (#State# s, Addr##)
- clearCCS# :: (State# s -> (#State# s, a#)) -> State# s -> (#State# s, a#)
- data Proxy# a
- proxy# :: Proxy# a
- seq :: a -> b -> b
- unsafeCoerce# :: a -> b
- traceEvent# :: Addr# -> State# s -> State# s
- traceMarker# :: Addr# -> State# s -> State# s
- coerce :: Coercible a b => a -> b
- data Int8X16#
- data Int16X8#
- data Int32X4#
- data Int64X2#
- data Int8X32#
- data Int16X16#
- data Int32X8#
- data Int64X4#
- data Int8X64#
- data Int16X32#
- data Int32X16#
- data Int64X8#
- data Word8X16#
- data Word16X8#
- data Word32X4#
- data Word64X2#
- data Word8X32#
- data Word16X16#
- data Word32X8#
- data Word64X4#
- data Word8X64#
- data Word16X32#
- data Word32X16#
- data Word64X8#
- data FloatX4#
- data DoubleX2#
- data FloatX8#
- data DoubleX4#
- data FloatX16#
- data DoubleX8#
- 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# s -> Int# -> State# s -> (#State# s, Int8X16##)
- readInt16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X8##)
- readInt32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X4##)
- readInt64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X2##)
- readInt8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X32##)
- readInt16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X16##)
- readInt32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X8##)
- readInt64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X4##)
- readInt8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X64##)
- readInt16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X32##)
- readInt32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X16##)
- readInt64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X8##)
- readWord8X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X16##)
- readWord16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X8##)
- readWord32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X4##)
- readWord64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X2##)
- readWord8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X32##)
- readWord16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X16##)
- readWord32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X8##)
- readWord64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X4##)
- readWord8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X64##)
- readWord16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X32##)
- readWord32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X16##)
- readWord64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X8##)
- readFloatX4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX4##)
- readDoubleX2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX2##)
- readFloatX8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX8##)
- readDoubleX4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX4##)
- readFloatX16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX16##)
- readDoubleX8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX8##)
- writeInt8X16Array# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s
- writeInt16X8Array# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s
- writeInt32X4Array# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s
- writeInt64X2Array# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s
- writeInt8X32Array# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s
- writeInt16X16Array# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s
- writeInt32X8Array# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s
- writeInt64X4Array# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s
- writeInt8X64Array# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s
- writeInt16X32Array# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s
- writeInt32X16Array# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s
- writeInt64X8Array# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s
- writeWord8X16Array# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s
- writeWord16X8Array# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s
- writeWord32X4Array# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s
- writeWord64X2Array# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s
- writeWord8X32Array# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s
- writeWord16X16Array# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s
- writeWord32X8Array# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s
- writeWord64X4Array# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s
- writeWord8X64Array# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s
- writeWord16X32Array# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s
- writeWord32X16Array# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s
- writeWord64X8Array# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s
- writeFloatX4Array# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s
- writeDoubleX2Array# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s
- writeFloatX8Array# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s
- writeDoubleX4Array# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s
- writeFloatX16Array# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s
- writeDoubleX8Array# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s
- 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# s -> (#State# s, Int8X16##)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X8##)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X4##)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X2##)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int8X32##)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X16##)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X8##)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X4##)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int8X64##)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X32##)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X16##)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X8##)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X16##)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X8##)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X4##)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X2##)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X32##)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X16##)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X8##)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X4##)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X64##)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X32##)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X16##)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X8##)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX4##)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX2##)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX8##)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX4##)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX16##)
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX8##)
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s
- 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# s -> Int# -> State# s -> (#State# s, Int8X16##)
- readInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X8##)
- readInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X4##)
- readInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X2##)
- readInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X32##)
- readInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X16##)
- readInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X8##)
- readInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X4##)
- readInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X64##)
- readInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X32##)
- readInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X16##)
- readInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X8##)
- readWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X16##)
- readWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X8##)
- readWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X4##)
- readWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X2##)
- readWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X32##)
- readWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X16##)
- readWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X8##)
- readWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X4##)
- readWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X64##)
- readWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X32##)
- readWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X16##)
- readWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X8##)
- readFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX4##)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX2##)
- readFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX8##)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX4##)
- readFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX16##)
- readDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX8##)
- writeInt8ArrayAsInt8X16# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s
- writeInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s
- writeInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s
- writeInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s
- writeInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s
- writeInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s
- writeInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s
- writeInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s
- writeInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s
- writeInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s
- writeInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s
- writeInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s
- writeWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s
- writeWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s
- writeWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s
- writeWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s
- writeWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s
- writeWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s
- writeWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s
- writeWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s
- writeWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s
- writeWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s
- writeWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s
- writeWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s
- writeFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s
- writeFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s
- writeFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s
- 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# s -> (#State# s, Int8X16##)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# s -> (#State# s, Int16X8##)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# s -> (#State# s, Int32X4##)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# s -> (#State# s, Int64X2##)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# s -> (#State# s, Int8X32##)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# s -> (#State# s, Int16X16##)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# s -> (#State# s, Int32X8##)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# s -> (#State# s, Int64X4##)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# s -> (#State# s, Int8X64##)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# s -> (#State# s, Int16X32##)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# s -> (#State# s, Int32X16##)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# s -> (#State# s, Int64X8##)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# s -> (#State# s, Word8X16##)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# s -> (#State# s, Word16X8##)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# s -> (#State# s, Word32X4##)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# s -> (#State# s, Word64X2##)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# s -> (#State# s, Word8X32##)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# s -> (#State# s, Word16X16##)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# s -> (#State# s, Word32X8##)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# s -> (#State# s, Word64X4##)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# s -> (#State# s, Word8X64##)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# s -> (#State# s, Word16X32##)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# s -> (#State# s, Word32X16##)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# s -> (#State# s, Word64X8##)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# s -> (#State# s, FloatX4##)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX2##)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# s -> (#State# s, FloatX8##)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX4##)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# s -> (#State# s, FloatX16##)
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX8##)
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s
- prefetchByteArray3# :: ByteArray# -> Int# -> State# s -> State# s
- prefetchMutableByteArray3# :: MutableByteArray# s -> Int# -> State# s -> State# s
- prefetchAddr3# :: Addr# -> Int# -> State# s -> State# s
- prefetchValue3# :: a -> State# s -> State# s
- prefetchByteArray2# :: ByteArray# -> Int# -> State# s -> State# s
- prefetchMutableByteArray2# :: MutableByteArray# s -> Int# -> State# s -> State# s
- prefetchAddr2# :: Addr# -> Int# -> State# s -> State# s
- prefetchValue2# :: a -> State# s -> State# s
- prefetchByteArray1# :: ByteArray# -> Int# -> State# s -> State# s
- prefetchMutableByteArray1# :: MutableByteArray# s -> Int# -> State# s -> State# s
- prefetchAddr1# :: Addr# -> Int# -> State# s -> State# s
- prefetchValue1# :: a -> State# s -> State# s
- prefetchByteArray0# :: ByteArray# -> Int# -> State# s -> State# s
- prefetchMutableByteArray0# :: MutableByteArray# s -> Int# -> State# s -> State# s
- prefetchAddr0# :: Addr# -> Int# -> State# s -> State# s
- prefetchValue0# :: a -> State# s -> State# s
The word size story.
Haskell98 specifies that signed integers (type Int
)
must contain at least 30 bits. GHC always implements Int
using the primitive type Int#
, whose size equals
the MachDeps.h
constant WORD_SIZE_IN_BITS
.
This is normally set based on the config.h
parameter
SIZEOF_HSWORD
, i.e., 32 bits on 32-bit machines, 64
bits on 64-bit machines. However, it can also be explicitly
set to a smaller number, e.g., 31 bits, to allow the
possibility of using tag bits. Currently GHC itself has only
32-bit and 64-bit variants, but 30 or 31-bit code can be
exported as an external core file for use in other back ends.
GHC also implements a primitive unsigned integer type Word#
which always has the same number of bits as Int#
.
In addition, GHC supports families of explicit-sized integers
and words at 8, 16, 32, and 64 bits, with the usual
arithmetic operations, comparisons, and a range of
conversions. The 8-bit and 16-bit sizes are always
represented as Int#
and Word#
, and the
operations implemented in terms of the the primops on these
types, with suitable range restrictions on the results (using
the narrow$n$Int#
and narrow$n$Word#
families
of primops. The 32-bit sizes are represented using Int#
and Word#
when WORD_SIZE_IN_BITS
$geq$ 32; otherwise, these are represented using distinct
primitive types Int32#
and Word32#
. These (when
needed) have a complete set of corresponding operations;
however, nearly all of these are implemented as external C
functions rather than as primops. Exactly the same story
applies to the 64-bit sizes. All of these details are hidden
under the PrelInt
and PrelWord
modules, which use
#if
-defs to invoke the appropriate types and
operators.
Word size also matters for the families of primops for
indexing/reading/writing fixed-size quantities at offsets
from an array base, address, or foreign pointer. Here, a
slightly different approach is taken. The names of these
primops are fixed, but their types vary according to
the value of WORD_SIZE_IN_BITS
. For example, if word
size is at least 32 bits then an operator like
indexInt32Array#
has type ByteArray# -> Int# -> Int#
; otherwise it has type ByteArray# -> Int# -> Int32#
. This approach confines the necessary #if
-defs to this file; no conditional compilation is needed
in the files that expose these primops.
Finally, there are strongly deprecated primops for coercing
between Addr#
, the primitive type of machine
addresses, and Int#
. These are pretty bogus anyway,
but will work on existing 32-bit and 64-bit GHC targets; they
are completely bogus when tag bits are used in Int#
,
so are not available in this case.
Char#
Operations on 31-bit characters.
Int#
Operations on native-size integers (30+ bits).
mulIntMayOflo# :: Int# -> Int# -> Int# Source #
Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommmended 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# Source #
Rounds towards zero. The behavior is undefined if the second argument is zero.
remInt# :: Int# -> Int# -> Int# Source #
Satisfies (quotInt# x y) *# y +# (remInt# x y) == x
. The
behavior is undefined if the second argument is zero.
negateInt# :: Int# -> Int# Source #
addIntC# :: Int# -> Int# -> (#Int#, Int##) Source #
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##) Source #
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# Source #
int2Double# :: Int# -> Double# Source #
word2Float# :: Word# -> Float# Source #
word2Double# :: Word# -> Double# Source #
uncheckedIShiftL# :: Int# -> Int# -> Int# Source #
Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRA# :: Int# -> Int# -> Int# Source #
Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRL# :: Int# -> Int# -> Int# Source #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
Word#
Operations on native-sized unsigned words (30+ bits).
subWordC# :: Word# -> Word# -> (#Word#, Int##) Source #
Subtract unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow.
uncheckedShiftL# :: Word# -> Int# -> Word# Source #
Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedShiftRL# :: Word# -> Int# -> Word# Source #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
byteSwap16# :: Word# -> Word# Source #
Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.
byteSwap32# :: Word# -> Word# Source #
Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.
byteSwap64# :: Word# -> Word# Source #
Swap bytes in a 64 bits of a word.
Narrowings
Explicit narrowing of native-sized ints or words.
narrow8Int# :: Int# -> Int# Source #
narrow16Int# :: Int# -> Int# Source #
narrow32Int# :: Int# -> Int# Source #
narrow8Word# :: Word# -> Word# Source #
narrow16Word# :: Word# -> Word# Source #
narrow32Word# :: Word# -> Word# Source #
Double#
Operations on double-precision (64 bit) floating-point numbers.
negateDouble# :: Double# -> Double# Source #
fabsDouble# :: Double# -> Double# Source #
double2Int# :: Double# -> Int# Source #
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# Source #
expDouble# :: Double# -> Double# Source #
logDouble# :: Double# -> Double# Source #
sqrtDouble# :: Double# -> Double# Source #
sinDouble# :: Double# -> Double# Source #
cosDouble# :: Double# -> Double# Source #
tanDouble# :: Double# -> Double# Source #
asinDouble# :: Double# -> Double# Source #
acosDouble# :: Double# -> Double# Source #
atanDouble# :: Double# -> Double# Source #
sinhDouble# :: Double# -> Double# Source #
coshDouble# :: Double# -> Double# Source #
tanhDouble# :: Double# -> Double# Source #
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##) Source #
Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.
decodeDouble_Int64# :: Double# -> (#Int#, Int##) Source #
Decode Double#
into mantissa and base-2 exponent.
Float#
Operations on single-precision (32-bit) floating-point numbers.
negateFloat# :: Float# -> Float# Source #
fabsFloat# :: Float# -> Float# Source #
float2Int# :: Float# -> Int# Source #
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# Source #
asinFloat# :: Float# -> Float# Source #
acosFloat# :: Float# -> Float# Source #
atanFloat# :: Float# -> Float# Source #
sinhFloat# :: Float# -> Float# Source #
coshFloat# :: Float# -> Float# Source #
tanhFloat# :: Float# -> Float# Source #
float2Double# :: Float# -> Double# Source #
decodeFloat_Int# :: Float# -> (#Int#, Int##) Source #
Convert to integers.
First Int#
in result is the mantissa; second is the exponent.
Arrays
Operations on Array#
.
data MutableArray# s a Source #
newArray# :: Int# -> a -> State# s -> (#State# s, MutableArray# s a#) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int# Source #
readArray# :: MutableArray# s a -> Int# -> State# s -> (#State# s, a#) Source #
Read from specified index of mutable array. Result is not yet evaluated.
writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s Source #
Write to specified index of mutable array.
sizeofArray# :: Array# a -> Int# Source #
Return the number of elements in the array.
sizeofMutableArray# :: MutableArray# s a -> Int# Source #
Return the number of elements in the array.
indexArray# :: Array# a -> Int# -> (#a#) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeArray# :: MutableArray# s a -> State# s -> (#State# s, Array# a#) Source #
Make a mutable array immutable, without copying.
unsafeThawArray# :: Array# a -> State# s -> (#State# s, MutableArray# s a#) Source #
Make an immutable array mutable, without copying.
copyArray# :: Array# a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
copyMutableArray# :: MutableArray# s a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked.
cloneArray# :: Array# a -> Int# -> Int# -> Array# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
cloneMutableArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, MutableArray# s a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
freezeArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, Array# a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
thawArray# :: Array# a -> Int# -> Int# -> State# s -> (#State# s, MutableArray# s a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
casArray# :: MutableArray# s a -> Int# -> a -> a -> State# s -> (#State# s, Int#, a#) Source #
Unsafe, machine-level atomic compare and swap on an element within an Array.
Small Arrays
Operations on SmallArray#
. A SmallArray#
works
just like an Array#
, but with different space use and
performance characteristics (that are often useful with small
arrays). The SmallArray#
and SmallMutableArray#
lack a `card table'. The purpose of a card table is to avoid
having to scan every element of the array on each GC by
keeping track of which elements have changed since the last GC
and only scanning those that have changed. So the consequence
of there being no card table is that the representation is
somewhat smaller and the writes are somewhat faster (because
the card table does not need to be updated). The disadvantage
of course is that for a SmallMutableArray#
the whole
array has to be scanned on each GC. Thus it is best suited for
use cases where the mutable array is not long lived, e.g.
where a mutable array is initialised quickly and then frozen
to become an immutable SmallArray#
.
data SmallArray# a Source #
data SmallMutableArray# s a Source #
newSmallArray# :: Int# -> a -> State# s -> (#State# s, SmallMutableArray# s a#) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int# Source #
readSmallArray# :: SmallMutableArray# s a -> Int# -> State# s -> (#State# s, a#) Source #
Read from specified index of mutable array. Result is not yet evaluated.
writeSmallArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> State# s Source #
Write to specified index of mutable array.
sizeofSmallArray# :: SmallArray# a -> Int# Source #
Return the number of elements in the array.
sizeofSmallMutableArray# :: SmallMutableArray# s a -> Int# Source #
Return the number of elements in the array.
indexSmallArray# :: SmallArray# a -> Int# -> (#a#) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeSmallArray# :: SmallMutableArray# s a -> State# s -> (#State# s, SmallArray# a#) Source #
Make a mutable array immutable, without copying.
unsafeThawSmallArray# :: SmallArray# a -> State# s -> (#State# s, SmallMutableArray# s a#) Source #
Make an immutable array mutable, without copying.
copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
copySmallMutableArray# :: SmallMutableArray# s a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked.
cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
cloneSmallMutableArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, SmallMutableArray# s a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
freezeSmallArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (#State# s, SmallArray# a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# s -> (#State# s, SmallMutableArray# s a#) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
casSmallArray# :: SmallMutableArray# s a -> Int# -> a -> a -> State# s -> (#State# s, Int#, a#) Source #
Unsafe, machine-level atomic compare and swap on an element within an array.
Byte Arrays
Operations on ByteArray#
. A ByteArray#
is a just a region of
raw memory in the garbage-collected heap, which is not
scanned for pointers. It carries its own size (in bytes).
There are
three sets of operations for accessing byte array contents:
index for reading from immutable byte arrays, and read/write
for mutable byte arrays. Each set contains operations for a
range of useful primitive data types. Each operation takes
an offset measured in terms of the size of the primitive type
being read or written.
data ByteArray# Source #
data MutableByteArray# s Source #
newByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#) Source #
Create a new mutable byte array of specified size (in bytes), in the specified state thread.
newPinnedByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#) Source #
Create a mutable byte array that the GC guarantees not to move.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (#State# s, MutableByteArray# s#) Source #
Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move.
isMutableByteArrayPinned# :: MutableByteArray# s -> Int# Source #
Determine whether a MutableByteArray#
is guaranteed not to move
during GC.
isByteArrayPinned# :: ByteArray# -> Int# Source #
Determine whether a ByteArray#
is guaranteed not to move during GC.
byteArrayContents# :: ByteArray# -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# Source #
shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
Shrink mutable byte array to new specified size (in bytes), in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by sizeofMutableArray#
.
resizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, MutableByteArray# s#) Source #
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# s -> State# s -> (#State# s, ByteArray##) Source #
Make a mutable byte array immutable, without copying.
sizeofByteArray# :: ByteArray# -> Int# Source #
Return the size of the array in bytes.
sizeofMutableByteArray# :: MutableByteArray# s -> Int# Source #
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# s -> State# s -> (#State# s, Int##) Source #
Return the number of elements in the array.
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
Read 8-bit character; offset in bytes.
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
Read 31-bit character; offset in 4-byte words.
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
indexInt8Array# :: ByteArray# -> Int# -> Int# Source #
Read 8-bit integer; offset in bytes.
indexInt16Array# :: ByteArray# -> Int# -> Int# Source #
Read 16-bit integer; offset in 16-bit words.
indexInt32Array# :: ByteArray# -> Int# -> Int# Source #
Read 32-bit integer; offset in 32-bit words.
indexInt64Array# :: ByteArray# -> Int# -> Int# Source #
Read 64-bit integer; offset in 64-bit words.
indexWord8Array# :: ByteArray# -> Int# -> Word# Source #
Read 8-bit word; offset in bytes.
indexWord16Array# :: ByteArray# -> Int# -> Word# Source #
Read 16-bit word; offset in 16-bit words.
indexWord32Array# :: ByteArray# -> Int# -> Word# Source #
Read 32-bit word; offset in 32-bit words.
indexWord64Array# :: ByteArray# -> Int# -> Word# Source #
Read 64-bit word; offset in 64-bit words.
readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##) Source #
Read 8-bit character; offset in bytes.
readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##) Source #
Read 31-bit character; offset in 4-byte words.
readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
Read intger; offset in words.
readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
Read word; offset in words.
readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Addr##) Source #
readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Float##) Source #
readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Double##) Source #
readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, StablePtr# a#) Source #
readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
Write 8-bit character; offset in bytes.
writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
Write 31-bit character; offset in 4-byte words.
writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s Source #
writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s Source #
writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s Source #
writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s Source #
writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyMutableByteArray# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# s -> State# s Source #
copyMutableByteArrayToAddr# :: MutableByteArray# s -> Int# -> Addr# -> Int# -> State# s -> State# s Source #
copyAddrToByteArray# :: Addr# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s Source #
setByteArray# ba off len c
sets the byte range [off, off+len]
of
the MutableByteArray#
to the byte c
.
atomicReadIntArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array and an offset in Int units, read an element. The index is assumed to be in bounds. Implies a full memory barrier.
atomicWriteIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
Given an array and an offset in Int units, write an element. The index is assumed to be in bounds. Implies a full memory barrier.
casIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, an offset in Int units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
fetchAddIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchSubIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to subtract, atomically substract the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchAndIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to AND, atomically AND the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchNandIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to NAND, atomically NAND the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchOrIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to OR, atomically OR the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchXorIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##) Source #
Given an array, and offset in Int units, and a value to XOR, atomically XOR the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Arrays of arrays
Operations on ArrayArray#
. An ArrayArray#
contains references to {em unpointed}
arrays, such as ByteArray#s
. Hence, it is not parameterised by the element types,
just like a ByteArray#
, but it needs to be scanned during GC, just like an Array#
.
We represent an ArrayArray#
exactly as a Array#
, but provide element-type-specific
indexing, reading, and writing.
data ArrayArray# Source #
data MutableArrayArray# s Source #
newArrayArray# :: Int# -> State# s -> (#State# s, MutableArrayArray# s#) Source #
Create a new mutable array of arrays with the specified number of elements, in the specified state thread, with each element recursively referring to the newly created array.
sameMutableArrayArray# :: MutableArrayArray# s -> MutableArrayArray# s -> Int# Source #
unsafeFreezeArrayArray# :: MutableArrayArray# s -> State# s -> (#State# s, ArrayArray##) Source #
Make a mutable array of arrays immutable, without copying.
sizeofArrayArray# :: ArrayArray# -> Int# Source #
Return the number of elements in the array.
sizeofMutableArrayArray# :: MutableArrayArray# s -> Int# Source #
Return the number of elements in the array.
indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# Source #
indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# Source #
readByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, ByteArray##) Source #
readMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, MutableByteArray# s#) Source #
readArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, ArrayArray##) Source #
readMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (#State# s, MutableArrayArray# s#) Source #
writeByteArrayArray# :: MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s Source #
writeMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s Source #
writeArrayArrayArray# :: MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s Source #
writeMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s Source #
copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyMutableArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s Source #
Copy a range of the first MutableArrayArray# to the specified region in the second MutableArrayArray#. Both arrays must fully contain the specified ranges, but this is not checked.
Addr#
An arbitrary machine address assumed to point outside the garbage-collected heap.
minusAddr# :: Addr# -> Addr# -> Int# Source #
Result is meaningless if two Addr#
s are so far apart that their
difference doesn't fit in an Int#
.
remAddr# :: Addr# -> Int# -> Int# Source #
Return the remainder when the Addr#
arg, treated like an Int#
,
is divided by the Int#
arg.
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #
Reads 31-bit character; offset in 4-byte words.
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
readCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##) Source #
Reads 8-bit character; offset in bytes.
readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##) Source #
Reads 31-bit character; offset in 4-byte words.
readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, StablePtr# a#) Source #
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s Source #
Mutable variables
Operations on MutVar#s.
newMutVar# :: a -> State# s -> (#State# s, MutVar# s a#) Source #
Create MutVar#
with specified initial value in specified state thread.
readMutVar# :: MutVar# s a -> State# s -> (#State# s, a#) Source #
Read contents of MutVar#
. Result is not yet evaluated.
Exceptions
catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
maskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
maskUninterruptible# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
unmaskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
STM-accessible Mutable Variables
atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
catchRetry# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
catchSTM# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
check# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> State# RealWorld Source #
newTVar# :: a -> State# s -> (#State# s, TVar# s a#) Source #
Create a new TVar#
holding a specified initial value.
readTVar# :: TVar# s a -> State# s -> (#State# s, a#) Source #
Read contents of TVar#
. Result is not yet evaluated.
readTVarIO# :: TVar# s a -> State# s -> (#State# s, a#) Source #
Read contents of TVar#
outside an STM transaction
Synchronized Mutable Variables
Operations on MVar#
s.
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))
.)
takeMVar# :: MVar# s a -> State# s -> (#State# s, a#) Source #
If MVar#
is empty, block until it becomes full.
Then remove and return its contents, and set it empty.
tryTakeMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#) Source #
If MVar#
is empty, immediately return with integer 0 and value undefined.
Otherwise, return with integer 1 and contents of MVar#
, and set MVar#
empty.
putMVar# :: MVar# s a -> a -> State# s -> State# s Source #
If MVar#
is full, block until it becomes empty.
Then store value arg as its new contents.
tryPutMVar# :: MVar# s a -> a -> State# s -> (#State# s, Int##) Source #
If MVar#
is full, immediately return with integer 0.
Otherwise, store value arg as MVar#
's new contents, and return with integer 1.
readMVar# :: MVar# s a -> State# s -> (#State# s, a#) Source #
If MVar#
is empty, block until it becomes full.
Then read its contents without modifying the MVar, without possibility
of intervention from other threads.
tryReadMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#) Source #
If MVar#
is empty, immediately return with integer 0 and value undefined.
Otherwise, return with integer 1 and contents of MVar#
.
isEmptyMVar# :: MVar# s a -> State# s -> (#State# s, Int##) Source #
Return 1 if MVar#
is empty; 0 otherwise.
Delay/wait operations
waitRead# :: Int# -> State# s -> State# s Source #
Block until input is available on specified file descriptor.
waitWrite# :: Int# -> State# s -> State# s Source #
Block until output is possible on specified file descriptor.
Concurrency primitives
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.
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#
.
(In a non-concurrent implementation, this can be a singleton
type, whose (unique) value is returned by myThreadId#
. The
other operations can be omitted.)
noDuplicate# :: State# s -> State# s Source #
Weak pointers
mkWeak# :: o -> b -> (State# RealWorld -> (#State# RealWorld, c#)) -> State# RealWorld -> (#State# RealWorld, Weak# b#) Source #
mkWeak# k v finalizer s
creates a weak reference to value k
,
with an associated reference to some value v
. If k
is still
alive then v
can be retrieved using deRefWeak#
. Note that
the type of k
must be represented by a pointer (i.e. of kind TYPE 'LiftedRep
or TYPE 'UnliftedRep
).
addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (#State# RealWorld, Int##) Source #
addCFinalizerToWeak# fptr ptr flag eptr w
attaches a C
function pointer fptr
to a weak pointer w
as a finalizer. If
flag
is zero, fptr
will be called with one argument,
ptr
. Otherwise, it will be called with two arguments,
eptr
and ptr
. addCFinalizerToWeak#
returns
1 on success, or 0 if w
is already dead.
finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, b#)#) Source #
Finalize a weak pointer. The return value is an unboxed tuple
containing the new state of the world and an "unboxed Maybe",
represented by an Int#
and a (possibly invalid) finalization
action. An Int#
of 1
indicates that the finalizer is valid. The
return value b
from the finalizer should be ignored.
Stable pointers and names
data StablePtr# a Source #
data StableName# a Source #
makeStablePtr# :: a -> State# RealWorld -> (#State# RealWorld, StablePtr# a#) Source #
deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (#State# RealWorld, a#) Source #
eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int# Source #
makeStableName# :: a -> State# RealWorld -> (#State# RealWorld, StableName# a#) Source #
eqStableName# :: StableName# a -> StableName# b -> Int# Source #
stableNameToInt# :: StableName# a -> Int# Source #
Compact normal form
compactNew# :: Word# -> State# RealWorld -> (#State# RealWorld, Compact##) Source #
Create a new Compact with the given size (in bytes, not words). The size is rounded up to a multiple of the allocator block size, and capped to one mega block.
compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld Source #
Set the new allocation size of the compact. This value (in bytes) determines the size of each block in the compact chain.
compactGetFirstBlock# :: Compact# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##) Source #
Returns the address and the size (in bytes) of the first block of a compact.
compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##) Source #
Given a compact and the address of one its blocks, returns the next block and its size, or #nullAddr if the argument was the last block in the compact.
compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr##) Source #
Attempt to allocate a compact block with the given size (in bytes) at the given address. The first argument is a hint to the allocator, allocation might be satisfied at a different address (which is returned). The resulting block is not known to the GC until compactFixupPointers# is called on it, and care must be taken so that the address does not escape or memory will be leaked.
compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (#State# RealWorld, Compact#, Addr##) Source #
Given the pointer to the first block of a compact, and the address of the root object in the old address space, fix up the internal pointers inside the compact to account for a different position in memory than when it was serialized. This method must be called exactly once after importing a serialized compact, and returns the new compact and the new adjusted root address.
compactAdd# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#) Source #
Recursively add a closure and its transitive closure to a {texttt Compact#}, evaluating any unevaluated components at the same time. Note: {texttt compactAdd#} is not thread-safe, so only one thread may call {texttt compactAdd#} with a particular {texttt Compact#} at any given time. The primop does not enforce any mutual exclusion; the caller is expected to arrange this.
compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#) Source #
Like {texttt compactAdd#}, but retains sharing and cycles during compaction.
compactSize# :: Compact# -> State# RealWorld -> (#State# RealWorld, Word##) Source #
Return the size (in bytes) of the total amount of data in the Compact#
Unsafe pointer equality
reallyUnsafePtrEquality# :: a -> a -> Int# Source #
Parallelism
numSparks# :: State# s -> (#State# s, Int##) Source #
Returns the number of sparks in the local spark pool.
Tag to enum stuff
Convert back and forth between values of enumerated types and small integers.
dataToTag# :: a -> Int# Source #
tagToEnum# :: Int# -> a Source #
- Note [dataToTag#] ~~~~~~~~~~~~~~~~~~~~ The dataToTag# primop should always be applied to an evaluated argument. The way to ensure this is to invoke it via the 'getTag' wrapper in GHC.Base: getTag :: a -> Int# getTag !x = dataToTag# x
But now consider z. case x of y -> let v = dataToTag# y in ...
To improve floating, the FloatOut pass (deliberately) does a binder-swap on the case, to give z. case x of y -> let v = dataToTag# x in ...
Now FloatOut might float that v-binding outside the z. But that is bad because that might mean x gest evaluated much too early! (CorePrep adds an eval to a dataToTag# call, to ensure that the argument really is evaluated; see CorePrep Note [dataToTag magic].)
Solution: make DataToTag into a can_fail primop. That will stop it floating (see Note [PrimOp can_fail and has_side_effects] in PrimOp). It's a bit of a hack but never mind. -
Bytecode operations
Support for manipulating bytecode objects used by the interpreter and linker.
Bytecode objects are heap objects which represent top-level bindings and contain a list of instructions and data needed by these instructions.
addrToAny# :: Addr# -> (#a#) Source #
Convert an Addr#
to a followable Any type.
anyToAddr# :: a -> State# RealWorld -> (#State# RealWorld, Addr##) Source #
Retrive the address of any Haskell value. This is essentially an {texttt unsafeCoerce#}, but if implemented as such the core lint pass complains and fails to compile. As a primop, it is opaque to core/stg, and only appears in cmm (where the copy propagation pass will get rid of it). Note that "a" must be a value, not a thunk! It's too late for strictness analysis to enforce this, so you're on your own to guarantee this. Also note that {texttt Addr#} is not a GC pointer - up to you to guarantee that it does not become a dangling pointer immediately after you get it.
mkApUpd0# :: BCO# -> (#a#) Source #
Wrap a BCO in a AP_UPD
thunk which will be updated with the value of
the BCO when evaluated.
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (#State# s, BCO##) Source #
newBCO# instrs lits ptrs arity bitmap
creates a new bytecode object. The
resulting object encodes a function of the given arity with the instructions
encoded in instrs
, and a static reference table usage bitmap given by
bitmap
.
unpackClosure# :: a -> (#Addr#, Array# b, ByteArray##) Source #
unpackClosure# closure
copies non-pointers and pointers in the
payload of the given closure into two new arrays, and returns a pointer to
the first word of the closure's info table, a pointer array for the
pointers in the payload, and a non-pointer array for the non-pointers in
the payload.
getApStackVal# :: a -> Int# -> (#Int#, b#) Source #
Misc
These aren't nearly as wired in as Etc...
getCurrentCCS# :: a -> State# s -> (#State# s, Addr##) Source #
Returns the current CostCentreStack
(value is NULL
if
not profiling). Takes a dummy argument which can be used to
avoid the call to getCCCS#
being floated out by the
simplifier, which would result in an uninformative stack
("CAF").
clearCCS# :: (State# s -> (#State# s, a#)) -> State# s -> (#State# s, a#) Source #
Run the supplied IO action with an empty CCS. For example, this is used by the interpreter to run an interpreted computation without the call stack showing that it was invoked from GHC.
Etc
Miscellaneous built-ins
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.
Witness for an unboxed Proxy#
value, which has no runtime
representation.
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. 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 Source #
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 (but not coercions between floating-point and integral types)
- 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 congnoscenti, 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.
traceEvent# :: Addr# -> State# s -> State# s Source #
Emits an event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.
traceMarker# :: Addr# -> State# s -> State# s Source #
Emits a marker event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.
Safe coercions
coerce :: Coercible a b => a -> b Source #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
SIMD Vectors
Operations on SIMD vectors.
data Word16X16# Source #
data Word16X32# Source #
data Word32X16# Source #
broadcastInt8X16# :: Int# -> Int8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X8# :: Int# -> Int16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X4# :: Int# -> Int32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X2# :: Int# -> Int64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X32# :: Int# -> Int8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X16# :: Int# -> Int16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X8# :: Int# -> Int32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X4# :: Int# -> Int64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X64# :: Int# -> Int8X64# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X32# :: Int# -> Int16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X16# :: Int# -> Int32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X8# :: Int# -> Int64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X16# :: Word# -> Word8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X8# :: Word# -> Word16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X4# :: Word# -> Word32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X2# :: Word# -> Word64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X32# :: Word# -> Word8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X16# :: Word# -> Word16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X8# :: Word# -> Word32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X4# :: Word# -> Word64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X64# :: Word# -> Word8X64# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X32# :: Word# -> Word16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X16# :: Word# -> Word32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X8# :: Word# -> Word64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX4# :: Float# -> FloatX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX2# :: Double# -> DoubleX2# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX8# :: Float# -> FloatX8# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX4# :: Double# -> DoubleX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX16# :: Float# -> FloatX16# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX8# :: Double# -> DoubleX8# Source #
Broadcast a scalar to all elements of a vector.
packInt8X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X4# :: (#Int#, Int#, Int#, Int##) -> Int32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X2# :: (#Int#, Int##) -> Int64X2# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X4# :: (#Int#, Int#, Int#, Int##) -> Int64X4# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X4# :: (#Word#, Word#, Word#, Word##) -> Word32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X2# :: (#Word#, Word##) -> Word64X2# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X4# :: (#Word#, Word#, Word#, Word##) -> Word64X4# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
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# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX4# :: (#Float#, Float#, Float#, Float##) -> FloatX4# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX2# :: (#Double#, Double##) -> DoubleX2# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX8# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX8# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX4# :: (#Double#, Double#, Double#, Double##) -> DoubleX4# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX16# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX16# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX8# :: (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) -> DoubleX8# Source #
Pack the elements of an unboxed tuple into a vector.
unpackInt8X16# :: Int8X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X8# :: Int16X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X4# :: Int32X4# -> (#Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X2# :: Int64X2# -> (#Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X16# :: Int16X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X8# :: Int32X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X4# :: Int64X4# -> (#Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X16# :: Int32X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X8# :: Int64X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X16# :: Word8X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X8# :: Word16X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X4# :: Word32X4# -> (#Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X2# :: Word64X2# -> (#Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X16# :: Word16X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X8# :: Word32X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X4# :: Word64X4# -> (#Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
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##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X16# :: Word32X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X8# :: Word64X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX4# :: FloatX4# -> (#Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX2# :: DoubleX2# -> (#Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX8# :: FloatX8# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX4# :: DoubleX4# -> (#Double#, Double#, Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX16# :: FloatX16# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX8# :: DoubleX8# -> (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
insertInt8X16# :: Int8X16# -> Int# -> Int# -> Int8X16# Source #
Insert a scalar at the given position in a vector.
insertInt16X8# :: Int16X8# -> Int# -> Int# -> Int16X8# Source #
Insert a scalar at the given position in a vector.
insertInt32X4# :: Int32X4# -> Int# -> Int# -> Int32X4# Source #
Insert a scalar at the given position in a vector.
insertInt64X2# :: Int64X2# -> Int# -> Int# -> Int64X2# Source #
Insert a scalar at the given position in a vector.
insertInt8X32# :: Int8X32# -> Int# -> Int# -> Int8X32# Source #
Insert a scalar at the given position in a vector.
insertInt16X16# :: Int16X16# -> Int# -> Int# -> Int16X16# Source #
Insert a scalar at the given position in a vector.
insertInt32X8# :: Int32X8# -> Int# -> Int# -> Int32X8# Source #
Insert a scalar at the given position in a vector.
insertInt64X4# :: Int64X4# -> Int# -> Int# -> Int64X4# Source #
Insert a scalar at the given position in a vector.
insertInt8X64# :: Int8X64# -> Int# -> Int# -> Int8X64# Source #
Insert a scalar at the given position in a vector.
insertInt16X32# :: Int16X32# -> Int# -> Int# -> Int16X32# Source #
Insert a scalar at the given position in a vector.
insertInt32X16# :: Int32X16# -> Int# -> Int# -> Int32X16# Source #
Insert a scalar at the given position in a vector.
insertInt64X8# :: Int64X8# -> Int# -> Int# -> Int64X8# Source #
Insert a scalar at the given position in a vector.
insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16# Source #
Insert a scalar at the given position in a vector.
insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8# Source #
Insert a scalar at the given position in a vector.
insertWord32X4# :: Word32X4# -> Word# -> Int# -> Word32X4# Source #
Insert a scalar at the given position in a vector.
insertWord64X2# :: Word64X2# -> Word# -> Int# -> Word64X2# Source #
Insert a scalar at the given position in a vector.
insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32# Source #
Insert a scalar at the given position in a vector.
insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16# Source #
Insert a scalar at the given position in a vector.
insertWord32X8# :: Word32X8# -> Word# -> Int# -> Word32X8# Source #
Insert a scalar at the given position in a vector.
insertWord64X4# :: Word64X4# -> Word# -> Int# -> Word64X4# Source #
Insert a scalar at the given position in a vector.
insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64# Source #
Insert a scalar at the given position in a vector.
insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32# Source #
Insert a scalar at the given position in a vector.
insertWord32X16# :: Word32X16# -> Word# -> Int# -> Word32X16# Source #
Insert a scalar at the given position in a vector.
insertWord64X8# :: Word64X8# -> Word# -> Int# -> Word64X8# Source #
Insert a scalar at the given position in a vector.
insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# Source #
Insert a scalar at the given position in a vector.
insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# Source #
Insert a scalar at the given position in a vector.
insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# Source #
Insert a scalar at the given position in a vector.
insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# Source #
Insert a scalar at the given position in a vector.
insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# Source #
Insert a scalar at the given position in a vector.
insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# Source #
Insert a scalar at the given position in a vector.
plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Add two vectors element-wise.
plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Add two vectors element-wise.
plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Add two vectors element-wise.
minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Subtract two vectors element-wise.
minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Subtract two vectors element-wise.
minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Subtract two vectors element-wise.
timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Multiply two vectors element-wise.
timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Multiply two vectors element-wise.
timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Multiply two vectors element-wise.
quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Rounds towards zero element-wise.
quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Rounds towards zero element-wise.
quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Rounds towards zero element-wise.
remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
negateInt8X16# :: Int8X16# -> Int8X16# Source #
Negate element-wise.
negateInt16X8# :: Int16X8# -> Int16X8# Source #
Negate element-wise.
negateInt32X4# :: Int32X4# -> Int32X4# Source #
Negate element-wise.
negateInt64X2# :: Int64X2# -> Int64X2# Source #
Negate element-wise.
negateInt8X32# :: Int8X32# -> Int8X32# Source #
Negate element-wise.
negateInt16X16# :: Int16X16# -> Int16X16# Source #
Negate element-wise.
negateInt32X8# :: Int32X8# -> Int32X8# Source #
Negate element-wise.
negateInt64X4# :: Int64X4# -> Int64X4# Source #
Negate element-wise.
negateInt8X64# :: Int8X64# -> Int8X64# Source #
Negate element-wise.
negateInt16X32# :: Int16X32# -> Int16X32# Source #
Negate element-wise.
negateInt32X16# :: Int32X16# -> Int32X16# Source #
Negate element-wise.
negateInt64X8# :: Int64X8# -> Int64X8# Source #
Negate element-wise.
negateFloatX4# :: FloatX4# -> FloatX4# Source #
Negate element-wise.
negateDoubleX2# :: DoubleX2# -> DoubleX2# Source #
Negate element-wise.
negateFloatX8# :: FloatX8# -> FloatX8# Source #
Negate element-wise.
negateDoubleX4# :: DoubleX4# -> DoubleX4# Source #
Negate element-wise.
negateFloatX16# :: FloatX16# -> FloatX16# Source #
Negate element-wise.
negateDoubleX8# :: DoubleX8# -> DoubleX8# Source #
Negate element-wise.
indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array.
indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array.
indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array.
indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array.
indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array.
indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array.
indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array.
indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array.
indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array.
indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array.
indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array.
indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array.
indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array.
indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array.
indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array.
indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array.
indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array.
indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array.
indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array.
indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array.
indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array.
indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array.
indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array.
indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array.
indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array.
indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array.
indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array.
indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array.
indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array.
indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array.
readInt8X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X16##) Source #
Read a vector from specified index of mutable array.
readInt16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X8##) Source #
Read a vector from specified index of mutable array.
readInt32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X4##) Source #
Read a vector from specified index of mutable array.
readInt64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X2##) Source #
Read a vector from specified index of mutable array.
readInt8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X32##) Source #
Read a vector from specified index of mutable array.
readInt16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X16##) Source #
Read a vector from specified index of mutable array.
readInt32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X8##) Source #
Read a vector from specified index of mutable array.
readInt64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X4##) Source #
Read a vector from specified index of mutable array.
readInt8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X64##) Source #
Read a vector from specified index of mutable array.
readInt16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X32##) Source #
Read a vector from specified index of mutable array.
readInt32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X16##) Source #
Read a vector from specified index of mutable array.
readInt64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X8##) Source #
Read a vector from specified index of mutable array.
readWord8X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X16##) Source #
Read a vector from specified index of mutable array.
readWord16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X8##) Source #
Read a vector from specified index of mutable array.
readWord32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X4##) Source #
Read a vector from specified index of mutable array.
readWord64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X2##) Source #
Read a vector from specified index of mutable array.
readWord8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X32##) Source #
Read a vector from specified index of mutable array.
readWord16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X16##) Source #
Read a vector from specified index of mutable array.
readWord32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X8##) Source #
Read a vector from specified index of mutable array.
readWord64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X4##) Source #
Read a vector from specified index of mutable array.
readWord8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X64##) Source #
Read a vector from specified index of mutable array.
readWord16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X32##) Source #
Read a vector from specified index of mutable array.
readWord32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X16##) Source #
Read a vector from specified index of mutable array.
readWord64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X8##) Source #
Read a vector from specified index of mutable array.
readFloatX4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX4##) Source #
Read a vector from specified index of mutable array.
readDoubleX2Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX2##) Source #
Read a vector from specified index of mutable array.
readFloatX8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX8##) Source #
Read a vector from specified index of mutable array.
readDoubleX4Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX4##) Source #
Read a vector from specified index of mutable array.
readFloatX16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX16##) Source #
Read a vector from specified index of mutable array.
readDoubleX8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX8##) Source #
Read a vector from specified index of mutable array.
writeInt8X16Array# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt16X8Array# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt32X4Array# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt64X2Array# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt8X32Array# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt16X16Array# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt32X8Array# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt64X4Array# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt8X64Array# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt16X32Array# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt32X16Array# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeInt64X8Array# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord8X16Array# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord16X8Array# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord32X4Array# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord64X2Array# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord8X32Array# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord16X16Array# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord32X8Array# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord64X4Array# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord8X64Array# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord16X32Array# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord32X16Array# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeWord64X8Array# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeFloatX4Array# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeDoubleX2Array# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeFloatX8Array# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeDoubleX4Array# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeFloatX16Array# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
writeDoubleX8Array# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array.
indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in bytes.
indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in bytes.
indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in bytes.
readInt8X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int8X16##) Source #
Reads vector; offset in bytes.
readInt16X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X8##) Source #
Reads vector; offset in bytes.
readInt32X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X4##) Source #
Reads vector; offset in bytes.
readInt64X2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X2##) Source #
Reads vector; offset in bytes.
readInt8X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int8X32##) Source #
Reads vector; offset in bytes.
readInt16X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X16##) Source #
Reads vector; offset in bytes.
readInt32X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X8##) Source #
Reads vector; offset in bytes.
readInt64X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X4##) Source #
Reads vector; offset in bytes.
readInt8X64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int8X64##) Source #
Reads vector; offset in bytes.
readInt16X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int16X32##) Source #
Reads vector; offset in bytes.
readInt32X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int32X16##) Source #
Reads vector; offset in bytes.
readInt64X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64X8##) Source #
Reads vector; offset in bytes.
readWord8X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X16##) Source #
Reads vector; offset in bytes.
readWord16X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X8##) Source #
Reads vector; offset in bytes.
readWord32X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X4##) Source #
Reads vector; offset in bytes.
readWord64X2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X2##) Source #
Reads vector; offset in bytes.
readWord8X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X32##) Source #
Reads vector; offset in bytes.
readWord16X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X16##) Source #
Reads vector; offset in bytes.
readWord32X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X8##) Source #
Reads vector; offset in bytes.
readWord64X4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X4##) Source #
Reads vector; offset in bytes.
readWord8X64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word8X64##) Source #
Reads vector; offset in bytes.
readWord16X32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word16X32##) Source #
Reads vector; offset in bytes.
readWord32X16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word32X16##) Source #
Reads vector; offset in bytes.
readWord64X8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64X8##) Source #
Reads vector; offset in bytes.
readFloatX4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX4##) Source #
Reads vector; offset in bytes.
readDoubleX2OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX2##) Source #
Reads vector; offset in bytes.
readFloatX8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX8##) Source #
Reads vector; offset in bytes.
readDoubleX4OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX4##) Source #
Reads vector; offset in bytes.
readFloatX16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, FloatX16##) Source #
Reads vector; offset in bytes.
readDoubleX8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX8##) Source #
Reads vector; offset in bytes.
writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s Source #
Write vector; offset in bytes.
writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s Source #
Write vector; offset in bytes.
indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int8X64##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int16X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int32X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word8X64##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word16X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word32X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, FloatX16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, DoubleX8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X16# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# s -> (#State# s, Int8X16##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# s -> (#State# s, Int16X8##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# s -> (#State# s, Int32X4##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# s -> (#State# s, Int64X2##) Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# s -> (#State# s, Int8X32##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# s -> (#State# s, Int16X16##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# s -> (#State# s, Int32X8##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# s -> (#State# s, Int64X4##) Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# s -> (#State# s, Int8X64##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# s -> (#State# s, Int16X32##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# s -> (#State# s, Int32X16##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# s -> (#State# s, Int64X8##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# s -> (#State# s, Word8X16##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# s -> (#State# s, Word16X8##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# s -> (#State# s, Word32X4##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# s -> (#State# s, Word64X2##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# s -> (#State# s, Word8X32##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# s -> (#State# s, Word16X16##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# s -> (#State# s, Word32X8##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# s -> (#State# s, Word64X4##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# s -> (#State# s, Word8X64##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# s -> (#State# s, Word16X32##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# s -> (#State# s, Word32X16##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# s -> (#State# s, Word64X8##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# s -> (#State# s, FloatX4##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX2##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# s -> (#State# s, FloatX8##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX4##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# s -> (#State# s, FloatX16##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# s -> (#State# s, DoubleX8##) Source #
Reads vector; offset in scalar elements.
writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s Source #
Write vector; offset in scalar elements.
Prefetch
Prefetch operations: Note how every prefetch operation has a name with the pattern prefetch*N#, where N is either 0,1,2, or 3.
This suffix number, N, is the "locality level" of the prefetch, following the convention in GCC and other compilers. Higher locality numbers correspond to the memory being loaded in more levels of the cpu cache, and being retained after initial use. The naming convention follows the naming convention of the prefetch intrinsic found in the GCC and Clang C compilers.
On the LLVM backend, prefetch*N# uses the LLVM prefetch intrinsic with locality level N. The code generated by LLVM is target architecture dependent, but should agree with the GHC NCG on x86 systems.
On the Sparc and PPC native backends, prefetch*N is a No-Op.
On the x86 NCG, N=0 will generate prefetchNTA, N=1 generates prefetcht2, N=2 generates prefetcht1, and N=3 generates prefetcht0.
For streaming workloads, the prefetch*0 operations are recommended. For workloads which do many reads or writes to a memory location in a short period of time, prefetch*3 operations are recommended.
For further reading about prefetch and associated systems performance optimization, the instruction set and optimization manuals by Intel and other CPU vendors are excellent starting place.
The "Intel 64 and IA-32 Architectures Optimization Reference Manual" is especially a helpful read, even if your software is meant for other CPU architectures or vendor hardware. The manual can be found at http://www.intel.com/content/www/us/en/architecture-and-technology/64-ia-32-architectures-optimization-manual.html .
The prefetch*
family of operations has the order of operations
determined by passing around the State#
token.
To get a "pure" version of these operations, use inlinePerformIO
which is quite safe in this context.
It is important to note that while the prefetch operations will never change the answer to a pure computation, They CAN change the memory locations resident in a CPU cache and that may change the performance and timing characteristics of an application. The prefetch operations are marked has_side_effects=True to reflect that these operations have side effects with respect to the runtime performance characteristics of the resulting code. Additionally, if the prefetchValue operations did not have this attribute, GHC does a float out transformation that results in a let/app violation, at least with the current design.
prefetchByteArray3# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray3# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue3# :: a -> State# s -> State# s Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray2# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue2# :: a -> State# s -> State# s Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray1# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue1# :: a -> State# s -> State# s Source #
prefetchByteArray0# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray0# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue0# :: a -> State# s -> State# s Source #