Maintainer | ghc-devs@haskell.org |
---|---|
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
- Builtin syntax
- The word size story.
- Char#
- Int8#
- Word8#
- Int16#
- Word16#
- Int32#
- Word32#
- Int64#
- Word64#
- Int#
- Word#
- Narrowings
- Double#
- Float#
- Fused multiply-add operations
- Arrays
- Small Arrays
- Byte Arrays
- Addr#
- Mutable variables
- Exceptions
- Continuations
- STM-accessible Mutable Variables
- Synchronized Mutable Variables
- Synchronized I/O Ports
- Delay/wait operations
- Concurrency primitives
- Weak pointers
- Stable pointers and names
- Compact normal form
- Unsafe pointer equality
- Parallelism
- Controlling object lifetime
- Tag to enum stuff
- Bytecode operations
- Misc
- Info Table Origin
- Etc
- Safe coercions
- SIMD Vectors
- Prefetch
- RuntimeRep polymorphism in continuation-style primops
GHC's primitive types and operations. Use GHC.Exts from the base package instead of importing this module directly.
Synopsis
- data FUN
- data Char# :: TYPE 'WordRep
- 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 Int8# :: TYPE 'Int8Rep
- int8ToInt# :: Int8# -> Int#
- intToInt8# :: Int# -> Int8#
- negateInt8# :: Int8# -> Int8#
- plusInt8# :: Int8# -> Int8# -> Int8#
- subInt8# :: Int8# -> Int8# -> Int8#
- timesInt8# :: Int8# -> Int8# -> Int8#
- quotInt8# :: Int8# -> Int8# -> Int8#
- remInt8# :: Int8# -> Int8# -> Int8#
- quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
- uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
- int8ToWord8# :: Int8# -> Word8#
- eqInt8# :: Int8# -> Int8# -> Int#
- geInt8# :: Int8# -> Int8# -> Int#
- gtInt8# :: Int8# -> Int8# -> Int#
- leInt8# :: Int8# -> Int8# -> Int#
- ltInt8# :: Int8# -> Int8# -> Int#
- neInt8# :: Int8# -> Int8# -> Int#
- data Word8# :: TYPE 'Word8Rep
- word8ToWord# :: Word8# -> Word#
- wordToWord8# :: Word# -> Word8#
- plusWord8# :: Word8# -> Word8# -> Word8#
- subWord8# :: Word8# -> Word8# -> Word8#
- timesWord8# :: Word8# -> Word8# -> Word8#
- quotWord8# :: Word8# -> Word8# -> Word8#
- remWord8# :: Word8# -> Word8# -> Word8#
- quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #)
- andWord8# :: Word8# -> Word8# -> Word8#
- orWord8# :: Word8# -> Word8# -> Word8#
- xorWord8# :: Word8# -> Word8# -> Word8#
- notWord8# :: Word8# -> Word8#
- uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
- uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
- word8ToInt8# :: Word8# -> Int8#
- eqWord8# :: Word8# -> Word8# -> Int#
- geWord8# :: Word8# -> Word8# -> Int#
- gtWord8# :: Word8# -> Word8# -> Int#
- leWord8# :: Word8# -> Word8# -> Int#
- ltWord8# :: Word8# -> Word8# -> Int#
- neWord8# :: Word8# -> Word8# -> Int#
- data Int16# :: TYPE 'Int16Rep
- int16ToInt# :: Int16# -> Int#
- intToInt16# :: Int# -> Int16#
- negateInt16# :: Int16# -> Int16#
- plusInt16# :: Int16# -> Int16# -> Int16#
- subInt16# :: Int16# -> Int16# -> Int16#
- timesInt16# :: Int16# -> Int16# -> Int16#
- quotInt16# :: Int16# -> Int16# -> Int16#
- remInt16# :: Int16# -> Int16# -> Int16#
- quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
- uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
- int16ToWord16# :: Int16# -> Word16#
- eqInt16# :: Int16# -> Int16# -> Int#
- geInt16# :: Int16# -> Int16# -> Int#
- gtInt16# :: Int16# -> Int16# -> Int#
- leInt16# :: Int16# -> Int16# -> Int#
- ltInt16# :: Int16# -> Int16# -> Int#
- neInt16# :: Int16# -> Int16# -> Int#
- data Word16# :: TYPE 'Word16Rep
- word16ToWord# :: Word16# -> Word#
- wordToWord16# :: Word# -> Word16#
- plusWord16# :: Word16# -> Word16# -> Word16#
- subWord16# :: Word16# -> Word16# -> Word16#
- timesWord16# :: Word16# -> Word16# -> Word16#
- quotWord16# :: Word16# -> Word16# -> Word16#
- remWord16# :: Word16# -> Word16# -> Word16#
- quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #)
- andWord16# :: Word16# -> Word16# -> Word16#
- orWord16# :: Word16# -> Word16# -> Word16#
- xorWord16# :: Word16# -> Word16# -> Word16#
- notWord16# :: Word16# -> Word16#
- uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
- uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
- word16ToInt16# :: Word16# -> Int16#
- eqWord16# :: Word16# -> Word16# -> Int#
- geWord16# :: Word16# -> Word16# -> Int#
- gtWord16# :: Word16# -> Word16# -> Int#
- leWord16# :: Word16# -> Word16# -> Int#
- ltWord16# :: Word16# -> Word16# -> Int#
- neWord16# :: Word16# -> Word16# -> Int#
- data Int32# :: TYPE 'Int32Rep
- int32ToInt# :: Int32# -> Int#
- intToInt32# :: Int# -> Int32#
- negateInt32# :: Int32# -> Int32#
- plusInt32# :: Int32# -> Int32# -> Int32#
- subInt32# :: Int32# -> Int32# -> Int32#
- timesInt32# :: Int32# -> Int32# -> Int32#
- quotInt32# :: Int32# -> Int32# -> Int32#
- remInt32# :: Int32# -> Int32# -> Int32#
- quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
- uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
- int32ToWord32# :: Int32# -> Word32#
- eqInt32# :: Int32# -> Int32# -> Int#
- geInt32# :: Int32# -> Int32# -> Int#
- gtInt32# :: Int32# -> Int32# -> Int#
- leInt32# :: Int32# -> Int32# -> Int#
- ltInt32# :: Int32# -> Int32# -> Int#
- neInt32# :: Int32# -> Int32# -> Int#
- data Word32# :: TYPE 'Word32Rep
- word32ToWord# :: Word32# -> Word#
- wordToWord32# :: Word# -> Word32#
- plusWord32# :: Word32# -> Word32# -> Word32#
- subWord32# :: Word32# -> Word32# -> Word32#
- timesWord32# :: Word32# -> Word32# -> Word32#
- quotWord32# :: Word32# -> Word32# -> Word32#
- remWord32# :: Word32# -> Word32# -> Word32#
- quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #)
- andWord32# :: Word32# -> Word32# -> Word32#
- orWord32# :: Word32# -> Word32# -> Word32#
- xorWord32# :: Word32# -> Word32# -> Word32#
- notWord32# :: Word32# -> Word32#
- uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
- uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
- word32ToInt32# :: Word32# -> Int32#
- eqWord32# :: Word32# -> Word32# -> Int#
- geWord32# :: Word32# -> Word32# -> Int#
- gtWord32# :: Word32# -> Word32# -> Int#
- leWord32# :: Word32# -> Word32# -> Int#
- ltWord32# :: Word32# -> Word32# -> Int#
- neWord32# :: Word32# -> Word32# -> Int#
- data Int64# :: TYPE 'Int64Rep
- int64ToInt# :: Int64# -> Int#
- intToInt64# :: Int# -> Int64#
- negateInt64# :: Int64# -> Int64#
- plusInt64# :: Int64# -> Int64# -> Int64#
- subInt64# :: Int64# -> Int64# -> Int64#
- timesInt64# :: Int64# -> Int64# -> Int64#
- quotInt64# :: Int64# -> Int64# -> Int64#
- remInt64# :: Int64# -> Int64# -> Int64#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
- int64ToWord64# :: Int64# -> Word64#
- eqInt64# :: Int64# -> Int64# -> Int#
- geInt64# :: Int64# -> Int64# -> Int#
- gtInt64# :: Int64# -> Int64# -> Int#
- leInt64# :: Int64# -> Int64# -> Int#
- ltInt64# :: Int64# -> Int64# -> Int#
- neInt64# :: Int64# -> Int64# -> Int#
- data Word64# :: TYPE 'Word64Rep
- word64ToWord# :: Word64# -> Word#
- wordToWord64# :: Word# -> Word64#
- plusWord64# :: Word64# -> Word64# -> Word64#
- subWord64# :: Word64# -> Word64# -> Word64#
- timesWord64# :: Word64# -> Word64# -> Word64#
- quotWord64# :: Word64# -> Word64# -> Word64#
- remWord64# :: Word64# -> Word64# -> Word64#
- and64# :: Word64# -> Word64# -> Word64#
- or64# :: Word64# -> Word64# -> Word64#
- xor64# :: Word64# -> Word64# -> Word64#
- not64# :: Word64# -> Word64#
- uncheckedShiftL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
- word64ToInt64# :: Word64# -> Int64#
- eqWord64# :: Word64# -> Word64# -> Int#
- geWord64# :: Word64# -> Word64# -> Int#
- gtWord64# :: Word64# -> Word64# -> Int#
- leWord64# :: Word64# -> Word64# -> Int#
- ltWord64# :: Word64# -> Word64# -> Int#
- neWord64# :: Word64# -> Word64# -> Int#
- data Int# :: TYPE 'IntRep
- (+#) :: Int# -> Int# -> Int#
- (-#) :: Int# -> Int# -> Int#
- (*#) :: Int# -> Int# -> Int#
- timesInt2# :: 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# :: TYPE 'WordRep
- plusWord# :: Word# -> Word# -> Word#
- addWordC# :: Word# -> Word# -> (# Word#, Int# #)
- subWordC# :: Word# -> Word# -> (# Word#, Int# #)
- plusWord2# :: Word# -> Word# -> (# Word#, Word# #)
- minusWord# :: Word# -> Word# -> Word#
- timesWord# :: Word# -> Word# -> Word#
- timesWord2# :: Word# -> Word# -> (# Word#, Word# #)
- quotWord# :: Word# -> Word# -> Word#
- remWord# :: Word# -> Word# -> Word#
- quotRemWord# :: Word# -> Word# -> (# Word#, Word# #)
- quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
- and# :: Word# -> Word# -> Word#
- or# :: Word# -> Word# -> Word#
- xor# :: Word# -> Word# -> Word#
- not# :: Word# -> Word#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- word2Int# :: Word# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- geWord# :: Word# -> Word# -> Int#
- eqWord# :: Word# -> Word# -> Int#
- neWord# :: Word# -> Word# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- leWord# :: Word# -> Word# -> Int#
- popCnt8# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt64# :: Word64# -> Word#
- popCnt# :: Word# -> Word#
- pdep8# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep32# :: Word# -> Word# -> Word#
- pdep64# :: Word64# -> Word64# -> Word64#
- pdep# :: Word# -> Word# -> Word#
- pext8# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext32# :: Word# -> Word# -> Word#
- pext64# :: Word64# -> Word64# -> Word64#
- pext# :: Word# -> Word# -> Word#
- clz8# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz32# :: Word# -> Word#
- clz64# :: Word64# -> Word#
- clz# :: Word# -> Word#
- ctz8# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz32# :: Word# -> Word#
- ctz64# :: Word64# -> Word#
- ctz# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- byteSwap32# :: Word# -> Word#
- byteSwap64# :: Word64# -> Word64#
- byteSwap# :: Word# -> Word#
- bitReverse8# :: Word# -> Word#
- bitReverse16# :: Word# -> Word#
- bitReverse32# :: Word# -> Word#
- bitReverse64# :: Word64# -> Word64#
- bitReverse# :: Word# -> Word#
- narrow8Int# :: Int# -> Int#
- narrow16Int# :: Int# -> Int#
- narrow32Int# :: Int# -> Int#
- narrow8Word# :: Word# -> Word#
- narrow16Word# :: Word# -> Word#
- narrow32Word# :: Word# -> Word#
- data Double# :: TYPE 'DoubleRep
- (>##) :: Double# -> Double# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (<=##) :: Double# -> Double# -> Int#
- minDouble# :: Double# -> Double# -> Double#
- maxDouble# :: Double# -> Double# -> Double#
- (+##) :: 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#
- expm1Double# :: Double# -> Double#
- logDouble# :: Double# -> Double#
- log1pDouble# :: 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#
- asinhDouble# :: Double# -> Double#
- acoshDouble# :: Double# -> Double#
- atanhDouble# :: Double# -> Double#
- (**##) :: Double# -> Double# -> Double#
- decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #)
- decodeDouble_Int64# :: Double# -> (# Int64#, Int# #)
- castDoubleToWord64# :: Double# -> Word64#
- castWord64ToDouble# :: Word64# -> Double#
- data Float# :: TYPE 'FloatRep
- gtFloat# :: Float# -> Float# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- leFloat# :: Float# -> Float# -> Int#
- minFloat# :: Float# -> Float# -> Float#
- maxFloat# :: Float# -> Float# -> Float#
- 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#
- expm1Float# :: Float# -> Float#
- logFloat# :: Float# -> Float#
- log1pFloat# :: 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#
- asinhFloat# :: Float# -> Float#
- acoshFloat# :: Float# -> Float#
- atanhFloat# :: Float# -> Float#
- powerFloat# :: Float# -> Float# -> Float#
- float2Double# :: Float# -> Double#
- decodeFloat_Int# :: Float# -> (# Int#, Int# #)
- castFloatToWord32# :: Float# -> Word32#
- castWord32ToFloat# :: Word32# -> Float#
- fmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fnmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fnmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fnmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fnmsubDouble# :: Double# -> Double# -> Double# -> Double#
- data Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
- readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int#
- sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int#
- indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #)
- unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #)
- unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #)
- copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a
- cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #)
- thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #)
- shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d
- readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int#
- sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int#
- getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #)
- indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #)
- unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #)
- unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #)
- copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a
- cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #)
- thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- data ByteArray# :: UnliftedType
- data MutableByteArray# a :: UnliftedType
- newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- isByteArrayPinned# :: ByteArray# -> Int#
- isByteArrayWeaklyPinned# :: ByteArray# -> Int#
- isMutableByteArrayWeaklyPinned# :: MutableByteArray# d -> Int#
- byteArrayContents# :: ByteArray# -> Addr#
- mutableByteArrayContents# :: MutableByteArray# d -> Addr#
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
- unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #)
- sizeofByteArray# :: ByteArray# -> Int#
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #)
- indexCharArray# :: ByteArray# -> Int# -> Char#
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexInt8Array# :: ByteArray# -> Int# -> Int8#
- indexWord8Array# :: ByteArray# -> Int# -> Word8#
- indexInt16Array# :: ByteArray# -> Int# -> Int16#
- indexWord16Array# :: ByteArray# -> Int# -> Word16#
- indexInt32Array# :: ByteArray# -> Int# -> Int32#
- indexWord32Array# :: ByteArray# -> Int# -> Word32#
- indexInt64Array# :: ByteArray# -> Int# -> Int64#
- indexWord64Array# :: ByteArray# -> Int# -> Word64#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #)
- casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #)
- casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #)
- casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #)
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- data Addr# :: TYPE 'AddrRep
- 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# -> Int8#
- indexWord8OffAddr# :: Addr# -> Int# -> Word8#
- indexInt16OffAddr# :: Addr# -> Int# -> Int16#
- indexWord16OffAddr# :: Addr# -> Int# -> Word16#
- indexInt32OffAddr# :: Addr# -> Int# -> Int32#
- indexWord32OffAddr# :: Addr# -> Int# -> Word32#
- indexInt64OffAddr# :: Addr# -> Int# -> Int64#
- indexWord64OffAddr# :: Addr# -> Int# -> Word64#
- indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int#
- indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word#
- indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr#
- indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float#
- indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double#
- indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a
- indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16#
- indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16#
- indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32#
- indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32#
- indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64#
- indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64#
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #)
- atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #)
- atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #)
- atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #)
- fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #)
- atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d
- data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #)
- readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #)
- writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d
- atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #)
- atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
- atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #)
- casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #)
- catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> b
- raiseUnderflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raiseOverflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raiseDivZero# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b
- raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #)
- maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- unmaskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #)
- data PromptTag# a :: UnliftedType
- newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #)
- prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- control0# :: forall {r :: RuntimeRep} a (b :: TYPE r). PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #)
- data TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #)
- catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #)
- readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d
- data MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #)
- takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d
- tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #)
- readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #)
- data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
- readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #)
- writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #)
- delay# :: Int# -> State# d -> State# d
- waitRead# :: Int# -> State# d -> State# d
- waitWrite# :: Int# -> State# d -> State# d
- data State# a :: ZeroBitType
- data RealWorld
- data ThreadId# :: UnliftedType
- fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, 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# -> ByteArray# -> State# RealWorld -> State# RealWorld
- isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #)
- noDuplicate# :: State# d -> State# d
- threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #)
- threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #)
- listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #)
- data Weak# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #)
- deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #)
- finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
- touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d
- data StablePtr# (a :: TYPE ('BoxedRep l)) :: TYPE 'AddrRep
- data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #)
- deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #)
- eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int#
- makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
- stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int#
- data Compact# :: UnliftedType
- 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# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int#
- par# :: a -> Int#
- spark# :: a -> State# d -> (# State# d, a #)
- getSpark# :: State# d -> (# State# d, Int#, a #)
- numSparks# :: State# d -> (# State# d, Int# #)
- keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) d (b :: TYPE r). a -> State# d -> (State# d -> b) -> b
- dataToTagSmall# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> Int#
- dataToTagLarge# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> Int#
- tagToEnum# :: Int# -> a
- data BCO
- addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #)
- anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #)
- mkApUpd0# :: BCO -> (# a #)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
- unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #)
- closureSize# :: a -> Int#
- getApStackVal# :: a -> Int# -> (# Int#, b #)
- getCCSOf# :: a -> State# d -> (# State# d, Addr# #)
- getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #)
- clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #)
- whereFrom# :: a -> Addr# -> State# d -> (# State# d, Int# #)
- data FUN
- realWorld# :: State# RealWorld
- void# :: (# #)
- data Proxy# (a :: k) :: ZeroBitType
- proxy# :: forall {k} (a :: k). Proxy# a
- seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b
- traceEvent# :: Addr# -> State# d -> State# d
- traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d
- traceMarker# :: Addr# -> State# d -> State# d
- setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld
- data StackSnapshot# :: UnliftedType
- coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
- data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep)
- data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep)
- data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep)
- data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep)
- data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep)
- data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep)
- data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep)
- data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep)
- data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep)
- data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep)
- data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep)
- data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep)
- data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep)
- data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep)
- data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep)
- data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep)
- data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep)
- data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep)
- data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep)
- data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep)
- data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep)
- data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep)
- data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep)
- data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep)
- data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep)
- data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep)
- data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep)
- data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep)
- data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep)
- data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep)
- broadcastInt8X16# :: Int8# -> Int8X16#
- broadcastInt16X8# :: Int16# -> Int16X8#
- broadcastInt32X4# :: Int32# -> Int32X4#
- broadcastInt64X2# :: Int64# -> Int64X2#
- broadcastInt8X32# :: Int8# -> Int8X32#
- broadcastInt16X16# :: Int16# -> Int16X16#
- broadcastInt32X8# :: Int32# -> Int32X8#
- broadcastInt64X4# :: Int64# -> Int64X4#
- broadcastInt8X64# :: Int8# -> Int8X64#
- broadcastInt16X32# :: Int16# -> Int16X32#
- broadcastInt32X16# :: Int32# -> Int32X16#
- broadcastInt64X8# :: Int64# -> Int64X8#
- broadcastWord8X16# :: Word8# -> Word8X16#
- broadcastWord16X8# :: Word16# -> Word16X8#
- broadcastWord32X4# :: Word32# -> Word32X4#
- broadcastWord64X2# :: Word64# -> Word64X2#
- broadcastWord8X32# :: Word8# -> Word8X32#
- broadcastWord16X16# :: Word16# -> Word16X16#
- broadcastWord32X8# :: Word32# -> Word32X8#
- broadcastWord64X4# :: Word64# -> Word64X4#
- broadcastWord8X64# :: Word8# -> Word8X64#
- broadcastWord16X32# :: Word16# -> Word16X32#
- broadcastWord32X16# :: Word32# -> Word32X16#
- broadcastWord64X8# :: Word64# -> Word64X8#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16#
- packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8#
- packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4#
- packInt64X2# :: (# Int64#, Int64# #) -> Int64X2#
- packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32#
- packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16#
- packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8#
- packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4#
- packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64#
- packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32#
- packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16#
- packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8#
- packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16#
- packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8#
- packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4#
- packWord64X2# :: (# Word64#, Word64# #) -> Word64X2#
- packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32#
- packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16#
- packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8#
- packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4#
- packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64#
- packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32#
- packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16#
- packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> 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# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #)
- unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #)
- unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #)
- unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #)
- unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #)
- unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #)
- unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #)
- unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #)
- 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# -> Int8# -> Int# -> Int8X16#
- insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8#
- insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4#
- insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2#
- insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32#
- insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16#
- insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8#
- insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4#
- insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64#
- insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32#
- insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16#
- insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8#
- insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16#
- insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8#
- insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4#
- insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2#
- insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32#
- insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16#
- insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8#
- insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4#
- insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64#
- insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32#
- insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16#
- insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt8X64# :: Int8X64# -> Int8X64#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- fmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#
- fmaddDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#
- fmaddFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8#
- fmaddDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4#
- fmaddFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16#
- fmaddDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8#
- fmsubFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#
- fmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#
- fmsubFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8#
- fmsubDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4#
- fmsubFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16#
- fmsubDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8#
- fnmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#
- fnmaddDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#
- fnmaddFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8#
- fnmaddDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4#
- fnmaddFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16#
- fnmaddDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8#
- fnmsubFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#
- fnmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#
- fnmsubFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8#
- fnmsubDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4#
- fnmsubFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16#
- fnmsubDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8#
- shuffleInt8X16# :: Int8X16# -> Int8X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X16#
- shuffleInt16X8# :: Int16X8# -> Int16X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X8#
- shuffleInt32X4# :: Int32X4# -> Int32X4# -> (# Int#, Int#, Int#, Int# #) -> Int32X4#
- shuffleInt64X2# :: Int64X2# -> Int64X2# -> (# Int#, Int# #) -> Int64X2#
- shuffleInt8X32# :: Int8X32# -> 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# #) -> Int8X32#
- shuffleInt16X16# :: Int16X16# -> Int16X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X16#
- shuffleInt32X8# :: Int32X8# -> Int32X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X8#
- shuffleInt64X4# :: Int64X4# -> Int64X4# -> (# Int#, Int#, Int#, Int# #) -> Int64X4#
- shuffleInt8X64# :: Int8X64# -> 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# #) -> Int8X64#
- shuffleInt16X32# :: Int16X32# -> 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# #) -> Int16X32#
- shuffleInt32X16# :: Int32X16# -> Int32X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X16#
- shuffleInt64X8# :: Int64X8# -> Int64X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int64X8#
- shuffleWord8X16# :: Word8X16# -> Word8X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X16#
- shuffleWord16X8# :: Word16X8# -> Word16X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X8#
- shuffleWord32X4# :: Word32X4# -> Word32X4# -> (# Int#, Int#, Int#, Int# #) -> Word32X4#
- shuffleWord64X2# :: Word64X2# -> Word64X2# -> (# Int#, Int# #) -> Word64X2#
- shuffleWord8X32# :: Word8X32# -> Word8X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X32#
- shuffleWord16X16# :: Word16X16# -> Word16X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X16#
- shuffleWord32X8# :: Word32X8# -> Word32X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word32X8#
- shuffleWord64X4# :: Word64X4# -> Word64X4# -> (# Int#, Int#, Int#, Int# #) -> Word64X4#
- shuffleWord8X64# :: Word8X64# -> Word8X64# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X64#
- shuffleWord16X32# :: Word16X32# -> Word16X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X32#
- shuffleWord32X16# :: Word32X16# -> Word32X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word32X16#
- shuffleWord64X8# :: Word64X8# -> Word64X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word64X8#
- shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
- shuffleDoubleX2# :: DoubleX2# -> DoubleX2# -> (# Int#, Int# #) -> DoubleX2#
- shuffleFloatX8# :: FloatX8# -> FloatX8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> FloatX8#
- shuffleDoubleX4# :: DoubleX4# -> DoubleX4# -> (# Int#, Int#, Int#, Int# #) -> DoubleX4#
- shuffleFloatX16# :: FloatX16# -> FloatX16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> FloatX16#
- shuffleDoubleX8# :: DoubleX8# -> DoubleX8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> DoubleX8#
- minInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- maxInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- maxInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- maxInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- maxInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- maxInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- maxInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- maxInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- maxInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- maxInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- maxInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- maxInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- maxInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- maxWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- maxWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- maxWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- maxWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- maxWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- maxWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- maxWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- maxWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- maxWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- maxWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- maxWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- maxWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- maxFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- maxDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- maxFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- maxDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- maxFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- maxDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue0# :: a -> State# d -> State# d
Builtin syntax
The builtin function type, written in infix form as a % m -> b
.
Values of this type are functions taking inputs of type a
and
producing outputs of type b
. The multiplicity of the input is
m
.
Note that
permits representation polymorphism in both
FUN
m a ba
and b
, so that types like
can still be
well-kinded.Int#
-> Int#
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 RTS ghcautoconf.h
parameter
SIZEOF_HSWORD
, i.e., 32 bits on 32-bit machines, 64
bits on 64-bit machines.
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.
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.
Int8#
Operations on 8-bit integers.
int8ToInt# :: Int8# -> Int# Source #
intToInt8# :: Int# -> Int8# Source #
negateInt8# :: Int8# -> Int8# Source #
int8ToWord8# :: Int8# -> Word8# Source #
Word8#
Operations on 8-bit unsigned words.
word8ToWord# :: Word8# -> Word# Source #
wordToWord8# :: Word# -> Word8# Source #
word8ToInt8# :: Word8# -> Int8# Source #
Int16#
Operations on 16-bit integers.
int16ToInt# :: Int16# -> Int# Source #
intToInt16# :: Int# -> Int16# Source #
negateInt16# :: Int16# -> Int16# Source #
int16ToWord16# :: Int16# -> Word16# Source #
Word16#
Operations on 16-bit unsigned words.
word16ToWord# :: Word16# -> Word# Source #
wordToWord16# :: Word# -> Word16# Source #
notWord16# :: Word16# -> Word16# Source #
word16ToInt16# :: Word16# -> Int16# Source #
Int32#
Operations on 32-bit integers.
int32ToInt# :: Int32# -> Int# Source #
intToInt32# :: Int# -> Int32# Source #
negateInt32# :: Int32# -> Int32# Source #
int32ToWord32# :: Int32# -> Word32# Source #
Word32#
Operations on 32-bit unsigned words.
word32ToWord# :: Word32# -> Word# Source #
wordToWord32# :: Word# -> Word32# Source #
notWord32# :: Word32# -> Word32# Source #
word32ToInt32# :: Word32# -> Int32# Source #
Int64#
Operations on 64-bit signed words.
int64ToInt# :: Int64# -> Int# Source #
intToInt64# :: Int# -> Int64# Source #
negateInt64# :: Int64# -> Int64# Source #
int64ToWord64# :: Int64# -> Word64# Source #
Word64#
Operations on 64-bit unsigned words.
word64ToWord# :: Word64# -> Word# Source #
wordToWord64# :: Word# -> Word64# Source #
word64ToInt64# :: Word64# -> Int64# Source #
Int#
Operations on native-size integers (32+ bits).
timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) Source #
Return a triple (isHighNeeded,high,low) where high and low are respectively the high and low bits of the double-word result. isHighNeeded is a cheap way to test if the high word is a sign-extension of the low word (isHighNeeded = 0#) or not (isHighNeeded = 1#).
mulIntMayOflo# :: Int# -> Int# -> Int# Source #
Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommended implementation is to do a 32 x 32 -> 64 signed multiply, and subtract result[63:32] from (result[31] >>signed 31). If this is zero, meaning that the upper word is merely a sign extension of the lower one, no overflow can occur.
On a 64-bit platform it is not always possible to acquire the top 64 bits of the result. Therefore, a recommended implementation is to take the absolute value of both operands, and return 0 iff bits[63:31] of them are zero, since that means that their magnitudes fit within 31 bits, so the magnitude of the product must fit into 62 bits.
If in doubt, return non-zero, but do make an effort to create the
correct answer for small args, since otherwise the performance of
(*) :: Integer -> Integer -> Integer
will be poor.
quotInt# :: Int# -> Int# -> Int# Source #
Rounds towards zero. The behavior is undefined if the second argument is zero.
negateInt# :: Int# -> Int# Source #
Unary negation.
Since the negative Int#
range extends one further than the
positive range, negateInt#
of the most negative number is an
identity operation. This way, negateInt#
is always its own inverse.
int2Float# :: Int# -> Float# Source #
Convert an Int#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Float#
1# == 1.0#
int2Double# :: Int# -> Double# Source #
Convert an Int#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Double#
1# == 1.0##
word2Float# :: Word# -> Float# Source #
Convert an Word#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Float#
1## == 1.0#
word2Double# :: Word# -> Double# Source #
Convert an Word#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Double#
1## == 1.0##
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 (32+ bits).
addWordC# :: Word# -> Word# -> (# Word#, Int# #) Source #
Add unsigned integers reporting overflow.
The first element of the pair is the result. The second element is
the carry flag, which is nonzero on overflow. See also plusWord2#
.
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.
plusWord2# :: Word# -> Word# -> (# Word#, Word# #) Source #
Add unsigned integers, with the high part (carry) in the first
component of the returned pair and the low part in the second
component of the pair. See also addWordC#
.
quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) Source #
Takes high word of dividend, then low word of dividend, then divisor. Requires that high word < divisor.
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.
pdep8# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep16# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep32# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep64# :: Word64# -> Word64# -> Word64# Source #
Deposit bits to a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep# :: Word# -> Word# -> Word# Source #
Deposit bits to a word at locations specified by a mask, aka parallel bit deposit.
Software emulation:
pdep :: Word -> Word -> Word pdep src mask = go 0 src mask where go :: Word -> Word -> Word -> Word go result _ 0 = result go result src mask = go newResult newSrc newMask where maskCtz = countTrailingZeros mask newResult = if testBit src 0 then setBit result maskCtz else result newSrc = src `shiftR` 1 newMask = clearBit mask maskCtz
Since: ghc-prim-0.5.2.0
pext8# :: Word# -> Word# -> Word# Source #
Extract bits from lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext16# :: Word# -> Word# -> Word# Source #
Extract bits from lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext32# :: Word# -> Word# -> Word# Source #
Extract bits from lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext64# :: Word64# -> Word64# -> Word64# Source #
Extract bits from a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext# :: Word# -> Word# -> Word# Source #
Extract bits from a word at locations specified by a mask, aka parallel bit extract.
Software emulation:
pext :: Word -> Word -> Word pext src mask = loop 0 0 0 where loop i count result | i >= finiteBitSize (0 :: Word) = result | testBit mask i = loop (i + 1) (count + 1) (if testBit src i then setBit result count else result) | otherwise = loop (i + 1) count result
Since: ghc-prim-0.5.2.0
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# :: Word64# -> Word64# Source #
Swap bytes in a 64 bits of a word.
bitReverse8# :: Word# -> Word# Source #
Reverse the order of the bits in a 8-bit word.
bitReverse16# :: Word# -> Word# Source #
Reverse the order of the bits in a 16-bit word.
bitReverse32# :: Word# -> Word# Source #
Reverse the order of the bits in a 32-bit word.
bitReverse64# :: Word64# -> Word64# Source #
Reverse the order of the bits in a 64-bit word.
bitReverse# :: Word# -> Word# Source #
Reverse the order of the bits in 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 #
double2Float# :: Double# -> Float# Source #
expDouble# :: Double# -> Double# Source #
expm1Double# :: Double# -> Double# Source #
logDouble# :: Double# -> Double# Source #
log1pDouble# :: 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 #
asinhDouble# :: Double# -> Double# Source #
acoshDouble# :: Double# -> Double# Source #
atanhDouble# :: 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# -> (# Int64#, 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 #
expm1Float# :: Float# -> Float# Source #
log1pFloat# :: Float# -> Float# Source #
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 #
asinhFloat# :: Float# -> Float# Source #
acoshFloat# :: Float# -> Float# Source #
atanhFloat# :: 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.
Fused multiply-add operations
The fused multiply-add primops fmaddFloat#
and fmaddDouble#
implement the operation
\[ \lambda\ x\ y\ z \rightarrow x * y + z \]
with a single floating-point rounding operation at the end, as opposed to rounding twice (which can accumulate rounding errors).
These primops can be compiled directly to a single machine instruction on architectures that support them. Currently, these are:
- x86 with CPUs that support the FMA3 extended instruction set (which includes most processors since 2013).
- PowerPC.
- AArch64.
This requires users pass the '-mfma' flag to GHC. Otherwise, the primop is implemented by falling back to the C standard library, which might perform software emulation (this may yield results that are not IEEE compliant on some platforms).
The additional operations fmsubFloat#
/fmsubDouble#
,
fnmaddFloat#
fnmaddDouble#
and fnmsubFloat#
fnmsubDouble#
provide
variants on fmaddFloat#
/fmaddDouble#
in which some signs are changed:
\[ \begin{aligned} \mathrm{fmadd}\ x\ y\ z &= \phantom{+} x * y + z \\[8pt] \mathrm{fmsub}\ x\ y\ z &= \phantom{+} x * y - z \\[8pt] \mathrm{fnmadd}\ x\ y\ z &= - x * y + z \\[8pt] \mathrm{fnmsub}\ x\ y\ z &= - x * y - z \end{aligned} \]
fmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
fmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fnmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fnmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
fmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
fmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fnmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fnmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
Arrays
Operations on Array#
.
data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# Source #
Return the number of elements in the array.
sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# Source #
Return the number of elements in the array.
indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #) Source #
Read from the specified index of an immutable array. The result is packaged into an unboxed unary tuple; the result itself is not yet evaluated. Pattern matching on the tuple forces the indexing of the array to happen but does not evaluate the element itself. Evaluating the thunk prevents additional thunks from building up on the heap. Avoiding these thunks, in turn, reduces references to the argument array, allowing it to be garbage collected more promptly.
unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) Source #
Make a mutable array immutable, without copying.
unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) Source #
Make an immutable array mutable, without copying.
copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. In the case where the source and destination are the same array the source and destination regions may overlap.
Warning: this can fail with an unchecked exception.
cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Given an array, an offset, the expected old value, and
the new value, perform an atomic compare and swap (i.e. write the new
value if the current value and the old value are the same pointer).
Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns
the element at the offset after the operation completes. This means that
on a success the new value is returned, and on a failure the actual old
value (not the expected one) is returned. Implies a full memory barrier.
The use of a pointer equality on a boxed value makes this function harder
to use correctly than casIntArray#
. All of the difficulties
of using reallyUnsafePtrEquality#
correctly apply to
casArray#
as well.
Warning: this can fail with an unchecked exception.
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 :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d Source #
Shrink mutable array to new specified size, in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofSmallMutableArray#
.
Assuming the non-profiling RTS, for the copying garbage collector (default) this primitive compiles to an O(1) operation in C--, modifying the array in-place. For the non-moving garbage collector, however, the time is proportional to the number of elements shrinked out. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.6.1
readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# Source #
Return the number of elements in the array.
sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# Source #
Deprecated: Use getSizeofSmallMutableArray#
instead
Return the number of elements in the array. Deprecated, it is
unsafe in the presence of shrinkSmallMutableArray#
and resizeSmallMutableArray#
operations on the same small mutable array.
getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkSmallMutableArray#
and resizeSmallMutableArray#
.
Since: ghc-prim-0.6.1
indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) Source #
Make a mutable array immutable, without copying.
unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Make an immutable array mutable, without copying.
copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Unsafe, machine-level atomic compare and swap on an element within an array.
See the documentation of casArray#
.
Warning: this can fail with an unchecked exception.
Byte Arrays
A ByteArray#
is a region of
raw memory in the garbage-collected heap, which is not
scanned for pointers.
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# :: UnliftedType Source #
A boxed, unlifted datatype representing a region of raw memory in the garbage-collected heap, which is not scanned for pointers during garbage collection.
It is created by freezing a MutableByteArray#
with unsafeFreezeByteArray#
.
Freezing is essentially a no-op, as MutableByteArray#
and ByteArray#
share the same heap structure under the hood.
The immutable and mutable variants are commonly used for scenarios requiring high-performance data structures,
like Text
, Primitive Vector
, Unboxed Array
, and ShortByteString
.
Another application of fundamental importance is Integer
, which is backed by ByteArray#
.
The representation on the heap of a Byte Array is:
+------------+-----------------+-----------------------+ | | | | | HEADER | SIZE (in bytes) | PAYLOAD | | | | | +------------+-----------------+-----------------------+
To obtain a pointer to actual payload (e.g., for FFI purposes) use byteArrayContents#
or mutableByteArrayContents#
.
Alternatively, enabling the UnliftedFFITypes
extension
allows to mention ByteArray#
and MutableByteArray#
in FFI type signatures directly.
data MutableByteArray# a :: UnliftedType Source #
A mutable ByteAray#
. It can be created in three ways:
newByteArray#
: Create an unpinned array.newPinnedByteArray#
: This will create a pinned array,newAlignedPinnedByteArray#
: This will create a pinned array, with a custom alignment.
Unpinned arrays can be moved around during garbage collection, so you must not store or pass pointers to these values if there is a chance for the garbage collector to kick in. That said, even unpinned arrays can be passed to unsafe FFI calls, because no garbage collection happens during these unsafe calls (see Guaranteed Call Safety in the GHC Manual). For safe FFI calls, byte arrays must be not only pinned, but also kept alive by means of the keepAlive# function for the duration of a call (that's because garbage collection cannot move a pinned array, but is free to scrap it altogether).
newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Create a new mutable byte array of specified size (in bytes), in the specified state thread. The size of the memory underlying the array will be rounded up to the platform's word size.
newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newByteArray#
but GC guarantees not to move it.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newPinnedByteArray#
but allow specifying an arbitrary
alignment, which must be a power of two.
Warning: this can fail with an unchecked exception.
isMutableByteArrayPinned# :: MutableByteArray# d -> 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.
isByteArrayWeaklyPinned# :: ByteArray# -> Int# Source #
Similar to isByteArrayPinned#
. Weakly pinned byte arrays are allowed
to be copied into compact regions by the user, potentially invalidating
the results of earlier calls to byteArrayContents#
.
See the section `Pinned Byte Arrays` in the user guide for more information.
This function also returns true for regular pinned bytearrays.
isMutableByteArrayWeaklyPinned# :: MutableByteArray# d -> Int# Source #
isByteArrayWeaklyPinned#
but for mutable arrays.
byteArrayContents# :: ByteArray# -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
mutableByteArrayContents# :: MutableByteArray# d -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
Shrink mutable byte array to new specified size (in bytes), in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofMutableByteArray#
.
Assuming the non-profiling RTS, this primitive compiles to an O(1) operation in C--, modifying the array in-place. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.4.0.0
resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Resize mutable byte array to new specified size (in bytes), shrinking or growing it.
The returned MutableByteArray#
is either the original
MutableByteArray#
resized in-place or, if not possible, a newly
allocated (unpinned) MutableByteArray#
(with the original content
copied over).
To avoid undefined behaviour, the original MutableByteArray#
shall
not be accessed anymore after a resizeMutableByteArray#
has been
performed. Moreover, no reference to the old one should be kept in order
to allow garbage collection of the original MutableByteArray#
in
case a new MutableByteArray#
had to be allocated.
Since: ghc-prim-0.4.0.0
unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Source #
Make a mutable byte array immutable, without copying.
unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Make an immutable byte array mutable, without copying.
Since: ghc-prim-0.12.0.0
sizeofByteArray# :: ByteArray# -> Int# Source #
Return the size of the array in bytes.
sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #
Deprecated: Use getSizeofMutableByteArray#
instead
Return the size of the array in bytes. Deprecated, it is
unsafe in the presence of shrinkMutableByteArray#
and resizeMutableByteArray#
operations on the same mutable byte
array.
getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkMutableByteArray#
and resizeMutableByteArray#
.
Since: ghc-prim-0.5.0.0
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character from immutable array; offset in bytes.
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character from immutable array; offset in 4-byte words.
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer from immutable array; offset in machine words.
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable array; offset in machine words.
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address from immutable array; offset in machine words.
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable array; offset in 4-byte words.
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable array; offset in 8-byte words.
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable array; offset in machine words.
indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #
Read an 8-bit signed integer from immutable array; offset in bytes.
indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer from immutable array; offset in bytes.
indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable array; offset in 2-byte words.
indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable array; offset in 2-byte words.
indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable array; offset in 4-byte words.
indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable array; offset in 4-byte words.
indexInt64Array# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable array; offset in 8-byte words.
indexWord64Array# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable array; offset in 8-byte words.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character from immutable array; offset in bytes.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character from immutable array; offset in bytes.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer from immutable array; offset in bytes.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address from immutable array; offset in bytes.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable array; offset in bytes.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable array; offset in bytes.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable array; offset in bytes.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable array; offset in bytes.
readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #
compares
compareByteArrays#
src1 src1_ofs src2 src2_ofs nn
bytes starting at offset src1_ofs
in the first
ByteArray#
src1
to the range of n
bytes
(i.e. same length) starting at offset src2_ofs
of the second
ByteArray#
src2
. Both arrays must fully contain the
specified ranges, but this is not checked. Returns an Int#
less than, equal to, or greater than zero if the range is found,
respectively, to be byte-wise lexicographically less than, to
match, or be greater than the second range.
Since: ghc-prim-0.5.2.0
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range
starting at offset copyByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
ByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain
the specified ranges, but this is not checked. The two arrays must
not be the same array in different states, but this is not checked
either.
Warning: this can fail with an unchecked exception.
copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the
range starting at offset copyMutableByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are
allowed to overlap, although this is only possible when the same
array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range starting at offset copyMutableByteArrayNonOverlapping#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from
the MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are not
allowed to overlap, but this is also not checked.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the ByteArray# to the memory range starting at the Addr#. The ByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the ByteArray# (e.g. if the ByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the MutableByteArray# to the memory range starting at the Addr#. The MutableByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Copy a memory range starting at the Addr# to the specified range in the MutableByteArray#. The memory region at Addr# and the ByteArray# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddr#
src dest lenlen
bytes
from src
to dest
. These two memory ranges are allowed to overlap.
Analogous to the standard C function memmove
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddrNonOverlapping#
src dest lenlen
bytes
from src
to dest
. As the name suggests, these two memory ranges
must not overlap, although this pre-condition is not checked.
Analogous to the standard C function memcpy
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d Source #
sets the byte range setByteArray#
ba off len c[off, off+len)
of
the MutableByteArray#
to the byte c
.
Warning: this can fail with an unchecked exception.
setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld Source #
sets all of the bytes in
setAddrRange#
dest len c[dest, dest+len)
to the value c
.
Analogous to the standard C function memset
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array and an offset in machine words, read an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Given an array and an offset in machine words, write an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, an offset in machine words, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) Source #
Given an array, an offset in bytes, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) Source #
Given an array, an offset in 16 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) Source #
Given an array, an offset in 32 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) Source #
Given an array, an offset in 64 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
Addr#
data Addr# :: TYPE 'AddrRep Source #
An arbitrary machine address assumed to point outside the garbage-collected heap.
addr2Int# :: Addr# -> Int# Source #
Coerce directly from address to int. Users are discouraged from using this operation as it makes little sense on platforms with tagged pointers.
int2Addr# :: Int# -> Addr# Source #
Coerce directly from int to address. Users are discouraged from using this operation as it makes little sense on platforms with tagged pointers.
indexCharOffAddr# :: Addr# -> Int# -> Char# Source #
Read an 8-bit character from immutable address; offset in bytes.
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexIntOffAddr# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWordOffAddr# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source #
Read a machine address from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexFloatOffAddr# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt8OffAddr# :: Addr# -> Int# -> Int8# Source #
Read an 8-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddr# :: Addr# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer from immutable address; offset in bytes.
indexInt16OffAddr# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord16OffAddr# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt32OffAddr# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord32OffAddr# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt64OffAddr# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord64OffAddr# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char# Source #
Read an 8-bit character from immutable address; offset in bytes.
indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character from immutable address; offset in bytes.
indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# Source #
Read a machine address from immutable address; offset in bytes.
indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable address; offset in bytes.
indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable address; offset in bytes.
indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable address; offset in bytes.
indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable address; offset in bytes.
readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.
Warning: this can fail with an unchecked exception.
atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.
Warning: this can fail with an unchecked exception.
atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
Compare and swap on a word-sized memory location.
Use as: s -> atomicCasAddrAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) Source #
Compare and swap on a word-sized and aligned memory location.
Use as: s -> atomicCasWordAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) Source #
Compare and swap on a 8 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr8# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) Source #
Compare and swap on a 16 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr16# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) Source #
Compare and swap on a 32 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr32# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) Source #
Compare and swap on a 64 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr64# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #) Source #
Given an address, read a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d Source #
Given an address, write a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
Mutable variables
Operations on MutVar#s.
data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
A MutVar#
behaves like a single-element mutable array.
newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) Source #
Create MutVar#
with specified initial value in specified state thread.
readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of MutVar#
. Result is not yet evaluated.
writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d Source #
Write contents of MutVar#
.
atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) Source #
Atomically exchange the value of a MutVar#
.
atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) Source #
Modify the contents of a MutVar#
, returning the previous
contents x :: a
and the result of applying the given function to the
previous contents f x :: c
.
The data
type c
(not a newtype
!) must be a record whose first field
is of lifted type a :: Type
and is not unpacked. For example, product
types c ~ Solo a
or c ~ (a, b)
work well. If the record type is both
monomorphic and strict in its first field, it's recommended to mark the
latter {-# NOUNPACK #-}
explicitly.
Under the hood atomicModifyMutVar2#
atomically replaces a pointer to an
old x :: a
with a pointer to a selector thunk fst r
, where
fst
is a selector for the first field of the record and r
is a
function application thunk r = f x
.
atomicModifyIORef2Native
from atomic-modify-general
package makes an
effort to reflect restrictions on c
faithfully, providing a
well-typed high-level wrapper.