Copyright | (c) The University of Glasgow 2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
- Representations of some basic types
- The maximum tuple size
- Primitive operations
- Fusion
- Overloaded string literals
- Debugging
- Ids with special behaviour
- Running
RealWorld
state transformers - Safe coercions
- Equality
- Representation polymorphism
- Transform comprehensions
- Event logging
- SpecConstr annotations
- The call stack
- The Constraint kind
- The Any type
- Overloaded lists
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Note: no other base module should import this module.
Synopsis
- data Int = I# Int#
- data Word = W# Word#
- data Float = F# Float#
- data Double = D# Double#
- data Char = C# Char#
- data Ptr a = Ptr Addr#
- data FunPtr a = FunPtr Addr#
- maxTupleSize :: Int
- seq :: a -> b -> b
- realWorld# :: State# RealWorld
- void# :: Void#
- unsafeCoerce# :: a -> b
- nullAddr# :: Addr#
- magicDict :: a
- proxy# :: Proxy# a
- data Addr# :: TYPE AddrRep
- data Array# (a :: Type) :: Type -> TYPE UnliftedRep
- data ByteArray# :: TYPE UnliftedRep
- data Char# :: TYPE WordRep
- data Double# :: TYPE DoubleRep
- data Float# :: TYPE FloatRep
- data Int# :: TYPE IntRep
- data Int32# :: TYPE IntRep
- data Int64# :: TYPE Int64Rep
- data Weak# (a :: Type) :: Type -> TYPE UnliftedRep
- data MutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data MutableByteArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data MVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data RealWorld :: Type
- data StablePtr# (a :: Type) :: Type -> TYPE AddrRep
- data ArrayArray# :: TYPE UnliftedRep
- data MutableArrayArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data State# (a :: Type) :: Type -> TYPE (TupleRep ([] :: [RuntimeRep]))
- data StableName# (a :: Type) :: Type -> TYPE UnliftedRep
- data MutVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data Void# :: TYPE (TupleRep ([] :: [RuntimeRep]))
- data Word# :: TYPE WordRep
- data Word32# :: TYPE WordRep
- data Word64# :: TYPE Word64Rep
- data ThreadId# :: TYPE UnliftedRep
- data BCO# :: TYPE UnliftedRep
- data TVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data Compact# :: TYPE UnliftedRep
- data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] :: [RuntimeRep]))
- data SmallArray# (a :: Type) :: Type -> TYPE UnliftedRep
- data SmallMutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep
- data Int8X16# :: TYPE (VecRep Vec16 Int8ElemRep)
- data Int16X8# :: TYPE (VecRep Vec8 Int16ElemRep)
- data Int32X4# :: TYPE (VecRep Vec4 Int32ElemRep)
- data Int64X2# :: TYPE (VecRep Vec2 Int64ElemRep)
- data Int8X32# :: TYPE (VecRep Vec32 Int8ElemRep)
- data Int16X16# :: TYPE (VecRep Vec16 Int16ElemRep)
- data Int32X8# :: TYPE (VecRep Vec8 Int32ElemRep)
- data Int64X4# :: TYPE (VecRep Vec4 Int64ElemRep)
- data Int8X64# :: TYPE (VecRep Vec64 Int8ElemRep)
- data Int16X32# :: TYPE (VecRep Vec32 Int16ElemRep)
- data Int32X16# :: TYPE (VecRep Vec16 Int32ElemRep)
- data Int64X8# :: TYPE (VecRep Vec8 Int64ElemRep)
- data Word8X16# :: TYPE (VecRep Vec16 Word8ElemRep)
- data Word16X8# :: TYPE (VecRep Vec8 Word16ElemRep)
- data Word32X4# :: TYPE (VecRep Vec4 Word32ElemRep)
- data Word64X2# :: TYPE (VecRep Vec2 Word64ElemRep)
- data Word8X32# :: TYPE (VecRep Vec32 Word8ElemRep)
- data Word16X16# :: TYPE (VecRep Vec16 Word16ElemRep)
- data Word32X8# :: TYPE (VecRep Vec8 Word32ElemRep)
- data Word64X4# :: TYPE (VecRep Vec4 Word64ElemRep)
- data Word8X64# :: TYPE (VecRep Vec64 Word8ElemRep)
- data Word16X32# :: TYPE (VecRep Vec32 Word16ElemRep)
- data Word32X16# :: TYPE (VecRep Vec16 Word32ElemRep)
- data Word64X8# :: TYPE (VecRep Vec8 Word64ElemRep)
- data FloatX4# :: TYPE (VecRep Vec4 FloatElemRep)
- data DoubleX2# :: TYPE (VecRep Vec2 DoubleElemRep)
- data FloatX8# :: TYPE (VecRep Vec8 FloatElemRep)
- data DoubleX4# :: TYPE (VecRep Vec4 DoubleElemRep)
- data FloatX16# :: TYPE (VecRep Vec16 FloatElemRep)
- data DoubleX8# :: TYPE (VecRep Vec8 DoubleElemRep)
- gtChar# :: Char# -> Char# -> Int#
- geChar# :: Char# -> Char# -> Int#
- eqChar# :: Char# -> Char# -> Int#
- neChar# :: Char# -> Char# -> Int#
- ltChar# :: Char# -> Char# -> Int#
- leChar# :: Char# -> Char# -> Int#
- ord# :: Char# -> Int#
- (+#) :: Int# -> Int# -> Int#
- (-#) :: Int# -> Int# -> Int#
- (*#) :: Int# -> Int# -> Int#
- mulIntMayOflo# :: Int# -> Int# -> Int#
- quotInt# :: Int# -> Int# -> Int#
- remInt# :: Int# -> Int# -> Int#
- quotRemInt# :: Int# -> Int# -> (#Int#, Int##)
- andI# :: Int# -> Int# -> Int#
- orI# :: Int# -> Int# -> Int#
- xorI# :: Int# -> Int# -> Int#
- notI# :: Int# -> Int#
- negateInt# :: Int# -> Int#
- addIntC# :: Int# -> Int# -> (#Int#, Int##)
- subIntC# :: Int# -> Int# -> (#Int#, Int##)
- (>#) :: Int# -> Int# -> Int#
- (>=#) :: Int# -> Int# -> Int#
- (==#) :: Int# -> Int# -> Int#
- (/=#) :: Int# -> Int# -> Int#
- (<#) :: Int# -> Int# -> Int#
- (<=#) :: Int# -> Int# -> Int#
- chr# :: Int# -> Char#
- int2Word# :: Int# -> Word#
- int2Float# :: Int# -> Float#
- int2Double# :: Int# -> Double#
- word2Float# :: Word# -> Float#
- word2Double# :: Word# -> Double#
- uncheckedIShiftL# :: Int# -> Int# -> Int#
- uncheckedIShiftRA# :: Int# -> Int# -> Int#
- uncheckedIShiftRL# :: Int# -> Int# -> Int#
- plusWord# :: Word# -> Word# -> Word#
- addWordC# :: Word# -> Word# -> (#Word#, Int##)
- subWordC# :: Word# -> Word# -> (#Word#, Int##)
- plusWord2# :: Word# -> Word# -> (#Word#, Word##)
- minusWord# :: Word# -> Word# -> Word#
- timesWord# :: Word# -> Word# -> Word#
- timesWord2# :: Word# -> Word# -> (#Word#, Word##)
- quotWord# :: Word# -> Word# -> Word#
- remWord# :: Word# -> Word# -> Word#
- quotRemWord# :: Word# -> Word# -> (#Word#, Word##)
- quotRemWord2# :: Word# -> Word# -> Word# -> (#Word#, Word##)
- and# :: Word# -> Word# -> Word#
- or# :: Word# -> Word# -> Word#
- xor# :: Word# -> Word# -> Word#
- not# :: Word# -> Word#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- word2Int# :: Word# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- geWord# :: Word# -> Word# -> Int#
- eqWord# :: Word# -> Word# -> Int#
- neWord# :: Word# -> Word# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- leWord# :: Word# -> Word# -> Int#
- popCnt8# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt64# :: Word# -> Word#
- popCnt# :: Word# -> Word#
- pdep8# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep32# :: Word# -> Word# -> Word#
- pdep64# :: Word# -> Word# -> Word#
- pdep# :: Word# -> Word# -> Word#
- pext8# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext32# :: Word# -> Word# -> Word#
- pext64# :: Word# -> Word# -> Word#
- pext# :: Word# -> Word# -> Word#
- clz8# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz32# :: Word# -> Word#
- clz64# :: Word# -> Word#
- clz# :: Word# -> Word#
- ctz8# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz32# :: Word# -> Word#
- ctz64# :: Word# -> Word#
- ctz# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- byteSwap32# :: Word# -> Word#
- byteSwap64# :: Word# -> Word#
- byteSwap# :: Word# -> Word#
- narrow8Int# :: Int# -> Int#
- narrow16Int# :: Int# -> Int#
- narrow32Int# :: Int# -> Int#
- narrow8Word# :: Word# -> Word#
- narrow16Word# :: Word# -> Word#
- narrow32Word# :: Word# -> Word#
- (>##) :: Double# -> Double# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (<=##) :: Double# -> Double# -> Int#
- (+##) :: Double# -> Double# -> Double#
- (-##) :: Double# -> Double# -> Double#
- (*##) :: Double# -> Double# -> Double#
- (/##) :: Double# -> Double# -> Double#
- negateDouble# :: Double# -> Double#
- fabsDouble# :: Double# -> Double#
- double2Int# :: Double# -> Int#
- double2Float# :: Double# -> Float#
- expDouble# :: Double# -> Double#
- logDouble# :: Double# -> Double#
- sqrtDouble# :: Double# -> Double#
- sinDouble# :: Double# -> Double#
- cosDouble# :: Double# -> Double#
- tanDouble# :: Double# -> Double#
- asinDouble# :: Double# -> Double#
- acosDouble# :: Double# -> Double#
- atanDouble# :: Double# -> Double#
- sinhDouble# :: Double# -> Double#
- coshDouble# :: Double# -> Double#
- tanhDouble# :: Double# -> Double#
- (**##) :: Double# -> Double# -> Double#
- decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)
- decodeDouble_Int64# :: Double# -> (#Int#, Int##)
- gtFloat# :: Float# -> Float# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- leFloat# :: Float# -> Float# -> Int#
- plusFloat# :: Float# -> Float# -> Float#
- minusFloat# :: Float# -> Float# -> Float#
- timesFloat# :: Float# -> Float# -> Float#
- divideFloat# :: Float# -> Float# -> Float#
- negateFloat# :: Float# -> Float#
- fabsFloat# :: Float# -> Float#
- float2Int# :: Float# -> Int#
- expFloat# :: Float# -> Float#
- logFloat# :: Float# -> Float#
- sqrtFloat# :: Float# -> Float#
- sinFloat# :: Float# -> Float#
- cosFloat# :: Float# -> Float#
- tanFloat# :: Float# -> Float#
- asinFloat# :: Float# -> Float#
- acosFloat# :: Float# -> Float#
- atanFloat# :: Float# -> Float#
- sinhFloat# :: Float# -> Float#
- coshFloat# :: Float# -> Float#
- tanhFloat# :: Float# -> Float#
- powerFloat# :: Float# -> Float# -> Float#
- float2Double# :: Float# -> Double#
- decodeFloat_Int# :: Float# -> (#Int#, Int##)
- newArray# :: Int# -> a -> State# d -> (#State# d, MutableArray# d a#)
- sameMutableArray# :: MutableArray# d a -> MutableArray# d a -> Int#
- readArray# :: MutableArray# d a -> Int# -> State# d -> (#State# d, a#)
- writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofArray# :: Array# a -> Int#
- sizeofMutableArray# :: MutableArray# d a -> Int#
- indexArray# :: Array# a -> Int# -> (#a#)
- unsafeFreezeArray# :: MutableArray# d a -> State# d -> (#State# d, Array# a#)
- unsafeThawArray# :: Array# a -> State# d -> (#State# d, MutableArray# d a#)
- copyArray# :: Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyMutableArray# :: MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneArray# :: Array# a -> Int# -> Int# -> Array# a
- cloneMutableArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#)
- freezeArray# :: MutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, Array# a#)
- thawArray# :: Array# a -> Int# -> Int# -> State# d -> (#State# d, MutableArray# d a#)
- casArray# :: MutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#)
- newSmallArray# :: Int# -> a -> State# d -> (#State# d, SmallMutableArray# d a#)
- sameSmallMutableArray# :: SmallMutableArray# d a -> SmallMutableArray# d a -> Int#
- readSmallArray# :: SmallMutableArray# d a -> Int# -> State# d -> (#State# d, a#)
- writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- sizeofSmallArray# :: SmallArray# a -> Int#
- sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int#
- indexSmallArray# :: SmallArray# a -> Int# -> (#a#)
- unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (#State# d, SmallArray# a#)
- unsafeThawSmallArray# :: SmallArray# a -> State# d -> (#State# d, SmallMutableArray# d a#)
- copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copySmallMutableArray# :: SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a
- cloneSmallMutableArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#)
- freezeSmallArray# :: SmallMutableArray# d a -> Int# -> Int# -> State# d -> (#State# d, SmallArray# a#)
- thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# d -> (#State# d, SmallMutableArray# d a#)
- casSmallArray# :: SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (#State# d, Int#, a#)
- newByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#)
- newPinnedByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#)
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- isByteArrayPinned# :: ByteArray# -> Int#
- byteArrayContents# :: ByteArray# -> Addr#
- sameMutableByteArray# :: MutableByteArray# d -> MutableByteArray# d -> Int#
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (#State# d, ByteArray##)
- sizeofByteArray# :: ByteArray# -> Int#
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (#State# d, Int##)
- indexCharArray# :: ByteArray# -> Int# -> Char#
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexInt8Array# :: ByteArray# -> Int# -> Int#
- indexInt16Array# :: ByteArray# -> Int# -> Int#
- indexInt32Array# :: ByteArray# -> Int# -> Int#
- indexInt64Array# :: ByteArray# -> Int# -> Int#
- indexWord8Array# :: ByteArray# -> Int# -> Word#
- indexWord16Array# :: ByteArray# -> Int# -> Word#
- indexWord32Array# :: ByteArray# -> Int# -> Word#
- indexWord64Array# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##)
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##)
- newArrayArray# :: Int# -> State# d -> (#State# d, MutableArrayArray# d#)
- sameMutableArrayArray# :: MutableArrayArray# d -> MutableArrayArray# d -> Int#
- unsafeFreezeArrayArray# :: MutableArrayArray# d -> State# d -> (#State# d, ArrayArray##)
- sizeofArrayArray# :: ArrayArray# -> Int#
- sizeofMutableArrayArray# :: MutableArrayArray# d -> Int#
- indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray#
- indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray#
- readByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ByteArray##)
- readMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#)
- readArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ArrayArray##)
- readMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableArrayArray# d#)
- writeByteArrayArray# :: MutableArrayArray# d -> Int# -> ByteArray# -> State# d -> State# d
- writeMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> MutableByteArray# d -> State# d -> State# d
- writeArrayArrayArray# :: MutableArrayArray# d -> Int# -> ArrayArray# -> State# d -> State# d
- writeMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> State# d -> State# d
- copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d
- plusAddr# :: Addr# -> Int# -> Addr#
- minusAddr# :: Addr# -> Addr# -> Int#
- remAddr# :: Addr# -> Int# -> Int#
- addr2Int# :: Addr# -> Int#
- int2Addr# :: Int# -> Addr#
- gtAddr# :: Addr# -> Addr# -> Int#
- geAddr# :: Addr# -> Addr# -> Int#
- eqAddr# :: Addr# -> Addr# -> Int#
- neAddr# :: Addr# -> Addr# -> Int#
- ltAddr# :: Addr# -> Addr# -> Int#
- leAddr# :: Addr# -> Addr# -> Int#
- indexCharOffAddr# :: Addr# -> Int# -> Char#
- indexWideCharOffAddr# :: Addr# -> Int# -> Char#
- indexIntOffAddr# :: Addr# -> Int# -> Int#
- indexWordOffAddr# :: Addr# -> Int# -> Word#
- indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- indexFloatOffAddr# :: Addr# -> Int# -> Float#
- indexDoubleOffAddr# :: Addr# -> Int# -> Double#
- indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
- indexInt8OffAddr# :: Addr# -> Int# -> Int#
- indexInt16OffAddr# :: Addr# -> Int# -> Int#
- indexInt32OffAddr# :: Addr# -> Int# -> Int#
- indexInt64OffAddr# :: Addr# -> Int# -> Int#
- indexWord8OffAddr# :: Addr# -> Int# -> Word#
- indexWord16OffAddr# :: Addr# -> Int# -> Word#
- indexWord32OffAddr# :: Addr# -> Int# -> Word#
- indexWord64OffAddr# :: Addr# -> Int# -> Word#
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Addr##)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Float##)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Double##)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, StablePtr# a#)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int##)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word##)
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- newMutVar# :: a -> State# d -> (#State# d, MutVar# d a#)
- readMutVar# :: MutVar# d a -> State# d -> (#State# d, a#)
- writeMutVar# :: MutVar# d a -> a -> State# d -> State# d
- sameMutVar# :: MutVar# d a -> MutVar# d a -> Int#
- atomicModifyMutVar# :: MutVar# d a -> (a -> b) -> State# d -> (#State# d, c#)
- casMutVar# :: MutVar# d a -> a -> a -> State# d -> (#State# d, Int#, a#)
- catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- raise# :: b -> a
- raiseIO# :: a -> State# RealWorld -> (#State# RealWorld, b#)
- maskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- maskUninterruptible# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- unmaskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- getMaskingState# :: State# RealWorld -> (#State# RealWorld, Int##)
- atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- retry# :: State# RealWorld -> (#State# RealWorld, a#)
- catchRetry# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- catchSTM# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
- newTVar# :: a -> State# d -> (#State# d, TVar# d a#)
- readTVar# :: TVar# d a -> State# d -> (#State# d, a#)
- readTVarIO# :: TVar# d a -> State# d -> (#State# d, a#)
- writeTVar# :: TVar# d a -> a -> State# d -> State# d
- sameTVar# :: TVar# d a -> TVar# d a -> Int#
- newMVar# :: State# d -> (#State# d, MVar# d a#)
- takeMVar# :: MVar# d a -> State# d -> (#State# d, a#)
- tryTakeMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#)
- putMVar# :: MVar# d a -> a -> State# d -> State# d
- tryPutMVar# :: MVar# d a -> a -> State# d -> (#State# d, Int##)
- readMVar# :: MVar# d a -> State# d -> (#State# d, a#)
- tryReadMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#)
- sameMVar# :: MVar# d a -> MVar# d a -> Int#
- isEmptyMVar# :: MVar# d a -> State# d -> (#State# d, Int##)
- delay# :: Int# -> State# d -> State# d
- waitRead# :: Int# -> State# d -> State# d
- waitWrite# :: Int# -> State# d -> State# d
- fork# :: a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
- forkOn# :: Int# -> a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
- killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
- yield# :: State# RealWorld -> State# RealWorld
- myThreadId# :: State# RealWorld -> (#State# RealWorld, ThreadId##)
- labelThread# :: ThreadId# -> Addr# -> State# RealWorld -> State# RealWorld
- isCurrentThreadBound# :: State# RealWorld -> (#State# RealWorld, Int##)
- noDuplicate# :: State# d -> State# d
- threadStatus# :: ThreadId# -> State# RealWorld -> (#State# RealWorld, Int#, Int#, Int##)
- mkWeak# :: a -> b -> (State# RealWorld -> (#State# RealWorld, c#)) -> State# RealWorld -> (#State# RealWorld, Weak# b#)
- mkWeakNoFinalizer# :: a -> b -> State# RealWorld -> (#State# RealWorld, Weak# b#)
- addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (#State# RealWorld, Int##)
- deRefWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, a#)
- finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, b#)#)
- touch# :: a -> State# RealWorld -> State# RealWorld
- makeStablePtr# :: a -> State# RealWorld -> (#State# RealWorld, StablePtr# a#)
- deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (#State# RealWorld, a#)
- eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int#
- makeStableName# :: a -> State# RealWorld -> (#State# RealWorld, StableName# a#)
- eqStableName# :: StableName# a -> StableName# b -> Int#
- stableNameToInt# :: StableName# a -> Int#
- compactNew# :: Word# -> State# RealWorld -> (#State# RealWorld, Compact##)
- compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld
- compactContains# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, Int##)
- compactContainsAny# :: a -> State# RealWorld -> (#State# RealWorld, Int##)
- compactGetFirstBlock# :: Compact# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##)
- compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##)
- compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr##)
- compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (#State# RealWorld, Compact#, Addr##)
- compactAdd# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#)
- compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#)
- compactSize# :: Compact# -> State# RealWorld -> (#State# RealWorld, Word##)
- reallyUnsafePtrEquality# :: a -> a -> Int#
- par# :: a -> Int#
- spark# :: a -> State# d -> (#State# d, a#)
- seq# :: a -> State# d -> (#State# d, a#)
- getSpark# :: State# d -> (#State# d, Int#, a#)
- numSparks# :: State# d -> (#State# d, Int##)
- dataToTag# :: a -> Int#
- tagToEnum# :: Int# -> a
- addrToAny# :: Addr# -> (#a#)
- anyToAddr# :: a -> State# RealWorld -> (#State# RealWorld, Addr##)
- mkApUpd0# :: BCO# -> (#a#)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (#State# d, BCO##)
- unpackClosure# :: a -> (#Addr#, ByteArray#, Array# b#)
- getApStackVal# :: a -> Int# -> (#Int#, b#)
- getCCSOf# :: a -> State# d -> (#State# d, Addr##)
- getCurrentCCS# :: a -> State# d -> (#State# d, Addr##)
- clearCCS# :: (State# d -> (#State# d, a#)) -> State# d -> (#State# d, a#)
- traceEvent# :: Addr# -> State# d -> State# d
- traceMarker# :: Addr# -> State# d -> State# d
- getThreadAllocationCounter# :: State# RealWorld -> (#State# RealWorld, Int##)
- setThreadAllocationCounter# :: Int# -> State# RealWorld -> State# RealWorld
- broadcastInt8X16# :: Int# -> Int8X16#
- broadcastInt16X8# :: Int# -> Int16X8#
- broadcastInt32X4# :: Int# -> Int32X4#
- broadcastInt64X2# :: Int# -> Int64X2#
- broadcastInt8X32# :: Int# -> Int8X32#
- broadcastInt16X16# :: Int# -> Int16X16#
- broadcastInt32X8# :: Int# -> Int32X8#
- broadcastInt64X4# :: Int# -> Int64X4#
- broadcastInt8X64# :: Int# -> Int8X64#
- broadcastInt16X32# :: Int# -> Int16X32#
- broadcastInt32X16# :: Int# -> Int32X16#
- broadcastInt64X8# :: Int# -> Int64X8#
- broadcastWord8X16# :: Word# -> Word8X16#
- broadcastWord16X8# :: Word# -> Word16X8#
- broadcastWord32X4# :: Word# -> Word32X4#
- broadcastWord64X2# :: Word# -> Word64X2#
- broadcastWord8X32# :: Word# -> Word8X32#
- broadcastWord16X16# :: Word# -> Word16X16#
- broadcastWord32X8# :: Word# -> Word32X8#
- broadcastWord64X4# :: Word# -> Word64X4#
- broadcastWord8X64# :: Word# -> Word8X64#
- broadcastWord16X32# :: Word# -> Word16X32#
- broadcastWord32X16# :: Word# -> Word32X16#
- broadcastWord64X8# :: Word# -> Word64X8#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- packInt8X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X16#
- packInt16X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X8#
- packInt32X4# :: (#Int#, Int#, Int#, Int##) -> Int32X4#
- packInt64X2# :: (#Int#, Int##) -> Int64X2#
- packInt8X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X32#
- packInt16X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X16#
- packInt32X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X8#
- packInt64X4# :: (#Int#, Int#, Int#, Int##) -> Int64X4#
- packInt8X64# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X64#
- packInt16X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X32#
- packInt32X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X16#
- packInt64X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int64X8#
- packWord8X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X16#
- packWord16X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X8#
- packWord32X4# :: (#Word#, Word#, Word#, Word##) -> Word32X4#
- packWord64X2# :: (#Word#, Word##) -> Word64X2#
- packWord8X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X32#
- packWord16X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X16#
- packWord32X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X8#
- packWord64X4# :: (#Word#, Word#, Word#, Word##) -> Word64X4#
- packWord8X64# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X64#
- packWord16X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X32#
- packWord32X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X16#
- packWord64X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word64X8#
- packFloatX4# :: (#Float#, Float#, Float#, Float##) -> FloatX4#
- packDoubleX2# :: (#Double#, Double##) -> DoubleX2#
- packFloatX8# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX8#
- packDoubleX4# :: (#Double#, Double#, Double#, Double##) -> DoubleX4#
- packFloatX16# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX16#
- packDoubleX8# :: (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) -> DoubleX8#
- unpackInt8X16# :: Int8X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X8# :: Int16X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X4# :: Int32X4# -> (#Int#, Int#, Int#, Int##)
- unpackInt64X2# :: Int64X2# -> (#Int#, Int##)
- unpackInt8X32# :: Int8X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X16# :: Int16X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X8# :: Int32X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt64X4# :: Int64X4# -> (#Int#, Int#, Int#, Int##)
- unpackInt8X64# :: Int8X64# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt16X32# :: Int16X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt32X16# :: Int32X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackInt64X8# :: Int64X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##)
- unpackWord8X16# :: Word8X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X8# :: Word16X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X4# :: Word32X4# -> (#Word#, Word#, Word#, Word##)
- unpackWord64X2# :: Word64X2# -> (#Word#, Word##)
- unpackWord8X32# :: Word8X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X16# :: Word16X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X8# :: Word32X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord64X4# :: Word64X4# -> (#Word#, Word#, Word#, Word##)
- unpackWord8X64# :: Word8X64# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord16X32# :: Word16X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord32X16# :: Word32X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackWord64X8# :: Word64X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##)
- unpackFloatX4# :: FloatX4# -> (#Float#, Float#, Float#, Float##)
- unpackDoubleX2# :: DoubleX2# -> (#Double#, Double##)
- unpackFloatX8# :: FloatX8# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##)
- unpackDoubleX4# :: DoubleX4# -> (#Double#, Double#, Double#, Double##)
- unpackFloatX16# :: FloatX16# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##)
- unpackDoubleX8# :: DoubleX8# -> (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##)
- insertInt8X16# :: Int8X16# -> Int# -> Int# -> Int8X16#
- insertInt16X8# :: Int16X8# -> Int# -> Int# -> Int16X8#
- insertInt32X4# :: Int32X4# -> Int# -> Int# -> Int32X4#
- insertInt64X2# :: Int64X2# -> Int# -> Int# -> Int64X2#
- insertInt8X32# :: Int8X32# -> Int# -> Int# -> Int8X32#
- insertInt16X16# :: Int16X16# -> Int# -> Int# -> Int16X16#
- insertInt32X8# :: Int32X8# -> Int# -> Int# -> Int32X8#
- insertInt64X4# :: Int64X4# -> Int# -> Int# -> Int64X4#
- insertInt8X64# :: Int8X64# -> Int# -> Int# -> Int8X64#
- insertInt16X32# :: Int16X32# -> Int# -> Int# -> Int16X32#
- insertInt32X16# :: Int32X16# -> Int# -> Int# -> Int32X16#
- insertInt64X8# :: Int64X8# -> Int# -> Int# -> Int64X8#
- insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16#
- insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8#
- insertWord32X4# :: Word32X4# -> Word# -> Int# -> Word32X4#
- insertWord64X2# :: Word64X2# -> Word# -> Int# -> Word64X2#
- insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32#
- insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16#
- insertWord32X8# :: Word32X8# -> Word# -> Int# -> Word32X8#
- insertWord64X4# :: Word64X4# -> Word# -> Int# -> Word64X4#
- insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64#
- insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32#
- insertWord32X16# :: Word32X16# -> Word# -> Int# -> Word32X16#
- insertWord64X8# :: Word64X8# -> Word# -> Int# -> Word64X8#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt8X64# :: Int8X64# -> Int8X64#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##)
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##)
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchValue0# :: a -> State# d -> State# d
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- uncheckedShiftL64# :: Word# -> Int# -> Word#
- uncheckedShiftRL64# :: Word# -> Int# -> Word#
- uncheckedIShiftL64# :: Int# -> Int# -> Int#
- uncheckedIShiftRA64# :: Int# -> Int# -> Int#
- isTrue# :: Int# -> Bool
- build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- class IsString a where
- fromString :: String -> a
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- lazy :: a -> a
- inline :: a -> a
- oneShot :: (a -> b) -> a -> b
- runRW# :: (State# RealWorld -> o) -> o
- coerce :: Coercible a b => a -> b
- class a ~R# b => Coercible (a :: k0) (b :: k0)
- class a ~# b => (a :: k0) ~~ (b :: k1)
- data TYPE (a :: RuntimeRep) :: RuntimeRep -> Type
- data RuntimeRep
- data VecCount
- data VecElem
- newtype Down a = Down a
- groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
- the :: Eq a => [a] -> a
- traceEvent :: String -> IO ()
- data SpecConstrAnnotation
- currentCallStack :: IO [String]
- data Constraint
- type family Any :: k0 where ...
- class IsList l where
Representations of some basic types
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Bounded Int # | Since: base-2.1 |
Enum Int # | Since: base-2.1 |
Defined in GHC.Enum | |
Eq Int | |
Integral Int # | Since: base-2.0.1 |
Data Int # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source # toConstr :: Int -> Constr Source # dataTypeOf :: Int -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) Source # gmapT :: (forall b. Data b => b -> b) -> Int -> Int Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # | |
Num Int # | Since: base-2.1 |
Ord Int | |
Read Int # | Since: base-2.1 |
Real Int # | Since: base-2.0.1 |
Show Int # | Since: base-2.1 |
Ix Int # | Since: base-2.1 |
FiniteBits Int # | Since: base-4.6.0.0 |
Bits Int # | Since: base-2.1 |
Defined in Data.Bits (.&.) :: Int -> Int -> Int Source # (.|.) :: Int -> Int -> Int Source # xor :: Int -> Int -> Int Source # complement :: Int -> Int Source # shift :: Int -> Int -> Int Source # rotate :: Int -> Int -> Int Source # setBit :: Int -> Int -> Int Source # clearBit :: Int -> Int -> Int Source # complementBit :: Int -> Int -> Int Source # testBit :: Int -> Int -> Bool Source # bitSizeMaybe :: Int -> Maybe Int Source # bitSize :: Int -> Int Source # isSigned :: Int -> Bool Source # shiftL :: Int -> Int -> Int Source # unsafeShiftL :: Int -> Int -> Int Source # shiftR :: Int -> Int -> Int Source # unsafeShiftR :: Int -> Int -> Int Source # rotateL :: Int -> Int -> Int Source # | |
Storable Int # | Since: base-2.1 |
PrintfArg Int # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Int -> FieldFormatter Source # parseFormat :: Int -> ModifierParser Source # | |
Generic1 (URec Int :: k -> Type) # | |
Functor (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Int m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Int a -> m Source # foldr :: (a -> b -> b) -> b -> URec Int a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Int a -> b Source # foldl :: (b -> a -> b) -> b -> URec Int a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Int a -> b Source # foldr1 :: (a -> a -> a) -> URec Int a -> a Source # foldl1 :: (a -> a -> a) -> URec Int a -> a Source # toList :: URec Int a -> [a] Source # null :: URec Int a -> Bool Source # length :: URec Int a -> Int Source # elem :: Eq a => a -> URec Int a -> Bool Source # maximum :: Ord a => URec Int a -> a Source # minimum :: Ord a => URec Int a -> a Source # | |
Traversable (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Int p) # | Since: base-4.9.0.0 |
Ord (URec Int p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Int p -> URec Int p -> Ordering Source # (<) :: URec Int p -> URec Int p -> Bool Source # (<=) :: URec Int p -> URec Int p -> Bool Source # (>) :: URec Int p -> URec Int p -> Bool Source # (>=) :: URec Int p -> URec Int p -> Bool Source # | |
Show (URec Int p) # | Since: base-4.9.0.0 |
Generic (URec Int p) # | |
data URec Int (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Int :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Int p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
Bounded Word # | Since: base-2.1 |
Enum Word # | Since: base-2.1 |
Eq Word | |
Integral Word # | Since: base-2.1 |
Data Word # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source # toConstr :: Word -> Constr Source # dataTypeOf :: Word -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) Source # gmapT :: (forall b. Data b => b -> b) -> Word -> Word Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # | |
Num Word # | Since: base-2.1 |
Ord Word | |
Read Word # | Since: base-4.5.0.0 |
Real Word # | Since: base-2.1 |
Show Word # | Since: base-2.1 |
Ix Word # | Since: base-4.6.0.0 |
FiniteBits Word # | Since: base-4.6.0.0 |
Bits Word # | Since: base-2.1 |
Defined in Data.Bits (.&.) :: Word -> Word -> Word Source # (.|.) :: Word -> Word -> Word Source # xor :: Word -> Word -> Word Source # complement :: Word -> Word Source # shift :: Word -> Int -> Word Source # rotate :: Word -> Int -> Word Source # setBit :: Word -> Int -> Word Source # clearBit :: Word -> Int -> Word Source # complementBit :: Word -> Int -> Word Source # testBit :: Word -> Int -> Bool Source # bitSizeMaybe :: Word -> Maybe Int Source # bitSize :: Word -> Int Source # isSigned :: Word -> Bool Source # shiftL :: Word -> Int -> Word Source # unsafeShiftL :: Word -> Int -> Word Source # shiftR :: Word -> Int -> Word Source # unsafeShiftR :: Word -> Int -> Word Source # rotateL :: Word -> Int -> Word Source # | |
Storable Word # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Word -> Int Source # alignment :: Word -> Int Source # peekElemOff :: Ptr Word -> Int -> IO Word Source # pokeElemOff :: Ptr Word -> Int -> Word -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word Source # pokeByteOff :: Ptr b -> Int -> Word -> IO () Source # | |
PrintfArg Word # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word -> FieldFormatter Source # parseFormat :: Word -> ModifierParser Source # | |
Generic1 (URec Word :: k -> Type) # | |
Functor (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Word m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Word a -> m Source # foldr :: (a -> b -> b) -> b -> URec Word a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Word a -> b Source # foldl :: (b -> a -> b) -> b -> URec Word a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Word a -> b Source # foldr1 :: (a -> a -> a) -> URec Word a -> a Source # foldl1 :: (a -> a -> a) -> URec Word a -> a Source # toList :: URec Word a -> [a] Source # null :: URec Word a -> Bool Source # length :: URec Word a -> Int Source # elem :: Eq a => a -> URec Word a -> Bool Source # maximum :: Ord a => URec Word a -> a Source # minimum :: Ord a => URec Word a -> a Source # | |
Traversable (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Word p) # | Since: base-4.9.0.0 |
Ord (URec Word p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Word p -> URec Word p -> Ordering Source # (<) :: URec Word p -> URec Word p -> Bool Source # (<=) :: URec Word p -> URec Word p -> Bool Source # (>) :: URec Word p -> URec Word p -> Bool Source # (>=) :: URec Word p -> URec Word p -> Bool Source # | |
Show (URec Word p) # | Since: base-4.9.0.0 |
Generic (URec Word p) # | |
data URec Word (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Word :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Word p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
Enum Float # | Since: base-2.1 |
Defined in GHC.Float succ :: Float -> Float Source # pred :: Float -> Float Source # toEnum :: Int -> Float Source # fromEnum :: Float -> Int Source # enumFrom :: Float -> [Float] Source # enumFromThen :: Float -> Float -> [Float] Source # enumFromTo :: Float -> Float -> [Float] Source # enumFromThenTo :: Float -> Float -> Float -> [Float] Source # | |
Eq Float | Note that due to the presence of
Also note that
|
Floating Float # | Since: base-2.1 |
Defined in GHC.Float exp :: Float -> Float Source # log :: Float -> Float Source # sqrt :: Float -> Float Source # (**) :: Float -> Float -> Float Source # logBase :: Float -> Float -> Float Source # sin :: Float -> Float Source # cos :: Float -> Float Source # tan :: Float -> Float Source # asin :: Float -> Float Source # acos :: Float -> Float Source # atan :: Float -> Float Source # sinh :: Float -> Float Source # cosh :: Float -> Float Source # tanh :: Float -> Float Source # asinh :: Float -> Float Source # acosh :: Float -> Float Source # atanh :: Float -> Float Source # log1p :: Float -> Float Source # expm1 :: Float -> Float Source # | |
Fractional Float # | Note that due to the presence of
Since: base-2.1 |
Data Float # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source # toConstr :: Float -> Constr Source # dataTypeOf :: Float -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source # gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # | |
Num Float # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Defined in GHC.Classes | |
Read Float # | Since: base-2.1 |
Real Float # | Since: base-2.1 |
RealFloat Float # | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Float -> Integer Source # floatDigits :: Float -> Int Source # floatRange :: Float -> (Int, Int) Source # decodeFloat :: Float -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Float Source # exponent :: Float -> Int Source # significand :: Float -> Float Source # scaleFloat :: Int -> Float -> Float Source # isNaN :: Float -> Bool Source # isInfinite :: Float -> Bool Source # isDenormalized :: Float -> Bool Source # isNegativeZero :: Float -> Bool Source # | |
RealFrac Float # | Since: base-2.1 |
Show Float # | Since: base-2.1 |
Storable Float # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Float -> Int Source # alignment :: Float -> Int Source # peekElemOff :: Ptr Float -> Int -> IO Float Source # pokeElemOff :: Ptr Float -> Int -> Float -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Float Source # pokeByteOff :: Ptr b -> Int -> Float -> IO () Source # | |
PrintfArg Float # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Float -> FieldFormatter Source # parseFormat :: Float -> ModifierParser Source # | |
Generic1 (URec Float :: k -> Type) # | |
Functor (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Float m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Float a -> m Source # foldr :: (a -> b -> b) -> b -> URec Float a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Float a -> b Source # foldl :: (b -> a -> b) -> b -> URec Float a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Float a -> b Source # foldr1 :: (a -> a -> a) -> URec Float a -> a Source # foldl1 :: (a -> a -> a) -> URec Float a -> a Source # toList :: URec Float a -> [a] Source # null :: URec Float a -> Bool Source # length :: URec Float a -> Int Source # elem :: Eq a => a -> URec Float a -> Bool Source # maximum :: Ord a => URec Float a -> a Source # minimum :: Ord a => URec Float a -> a Source # | |
Traversable (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) Source # sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) Source # mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) Source # sequence :: Monad m => URec Float (m a) -> m (URec Float a) Source # | |
Eq (URec Float p) # | |
Ord (URec Float p) # | |
Defined in GHC.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |
Show (URec Float p) # | |
Generic (URec Float p) # | |
data URec Float (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Float :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Float p) # | |
Defined in GHC.Generics |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Enum Double # | Since: base-2.1 |
Defined in GHC.Float succ :: Double -> Double Source # pred :: Double -> Double Source # toEnum :: Int -> Double Source # fromEnum :: Double -> Int Source # enumFrom :: Double -> [Double] Source # enumFromThen :: Double -> Double -> [Double] Source # enumFromTo :: Double -> Double -> [Double] Source # enumFromThenTo :: Double -> Double -> Double -> [Double] Source # | |
Eq Double | Note that due to the presence of
Also note that
|
Floating Double # | Since: base-2.1 |
Defined in GHC.Float exp :: Double -> Double Source # log :: Double -> Double Source # sqrt :: Double -> Double Source # (**) :: Double -> Double -> Double Source # logBase :: Double -> Double -> Double Source # sin :: Double -> Double Source # cos :: Double -> Double Source # tan :: Double -> Double Source # asin :: Double -> Double Source # acos :: Double -> Double Source # atan :: Double -> Double Source # sinh :: Double -> Double Source # cosh :: Double -> Double Source # tanh :: Double -> Double Source # asinh :: Double -> Double Source # acosh :: Double -> Double Source # atanh :: Double -> Double Source # log1p :: Double -> Double Source # expm1 :: Double -> Double Source # | |
Fractional Double # | Note that due to the presence of
Since: base-2.1 |
Data Double # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source # toConstr :: Double -> Constr Source # dataTypeOf :: Double -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source # gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # | |
Num Double # | Note that due to the presence of
Also note that due to the presence of -0,
Since: base-2.1 |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Defined in GHC.Classes | |
Read Double # | Since: base-2.1 |
Real Double # | Since: base-2.1 |
RealFloat Double # | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Double -> Integer Source # floatDigits :: Double -> Int Source # floatRange :: Double -> (Int, Int) Source # decodeFloat :: Double -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Double Source # exponent :: Double -> Int Source # significand :: Double -> Double Source # scaleFloat :: Int -> Double -> Double Source # isNaN :: Double -> Bool Source # isInfinite :: Double -> Bool Source # isDenormalized :: Double -> Bool Source # isNegativeZero :: Double -> Bool Source # | |
RealFrac Double # | Since: base-2.1 |
Show Double # | Since: base-2.1 |
Storable Double # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Double -> Int Source # alignment :: Double -> Int Source # peekElemOff :: Ptr Double -> Int -> IO Double Source # pokeElemOff :: Ptr Double -> Int -> Double -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Double Source # pokeByteOff :: Ptr b -> Int -> Double -> IO () Source # | |
PrintfArg Double # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Double -> FieldFormatter Source # parseFormat :: Double -> ModifierParser Source # | |
Generic1 (URec Double :: k -> Type) # | |
Functor (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Double m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Double a -> m Source # foldr :: (a -> b -> b) -> b -> URec Double a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Double a -> b Source # foldl :: (b -> a -> b) -> b -> URec Double a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Double a -> b Source # foldr1 :: (a -> a -> a) -> URec Double a -> a Source # foldl1 :: (a -> a -> a) -> URec Double a -> a Source # toList :: URec Double a -> [a] Source # null :: URec Double a -> Bool Source # length :: URec Double a -> Int Source # elem :: Eq a => a -> URec Double a -> Bool Source # maximum :: Ord a => URec Double a -> a Source # minimum :: Ord a => URec Double a -> a Source # | |
Traversable (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) Source # sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) Source # mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) Source # sequence :: Monad m => URec Double (m a) -> m (URec Double a) Source # | |
Eq (URec Double p) # | Since: base-4.9.0.0 |
Ord (URec Double p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |
Show (URec Double p) # | Since: base-4.9.0.0 |
Generic (URec Double p) # | |
data URec Double (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Double :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Double p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and chr
).
Instances
Bounded Char # | Since: base-2.1 |
Enum Char # | Since: base-2.1 |
Eq Char | |
Data Char # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source # toConstr :: Char -> Constr Source # dataTypeOf :: Char -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) Source # gmapT :: (forall b. Data b => b -> b) -> Char -> Char Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # | |
Ord Char | |
Read Char # | Since: base-2.1 |
Show Char # | Since: base-2.1 |
Ix Char # | Since: base-2.1 |
Storable Char # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Char -> Int Source # alignment :: Char -> Int Source # peekElemOff :: Ptr Char -> Int -> IO Char Source # pokeElemOff :: Ptr Char -> Int -> Char -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Char Source # pokeByteOff :: Ptr b -> Int -> Char -> IO () Source # | |
IsChar Char # | Since: base-2.1 |
PrintfArg Char # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |
Generic1 (URec Char :: k -> Type) # | |
Functor (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Char m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Char a -> m Source # foldr :: (a -> b -> b) -> b -> URec Char a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Char a -> b Source # foldl :: (b -> a -> b) -> b -> URec Char a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Char a -> b Source # foldr1 :: (a -> a -> a) -> URec Char a -> a Source # foldl1 :: (a -> a -> a) -> URec Char a -> a Source # toList :: URec Char a -> [a] Source # null :: URec Char a -> Bool Source # length :: URec Char a -> Int Source # elem :: Eq a => a -> URec Char a -> Bool Source # maximum :: Ord a => URec Char a -> a Source # minimum :: Ord a => URec Char a -> a Source # | |
Traversable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Char p) # | Since: base-4.9.0.0 |
Ord (URec Char p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Char p -> URec Char p -> Ordering Source # (<) :: URec Char p -> URec Char p -> Bool Source # (<=) :: URec Char p -> URec Char p -> Bool Source # (>) :: URec Char p -> URec Char p -> Bool Source # (>=) :: URec Char p -> URec Char p -> Bool Source # | |
Show (URec Char p) # | Since: base-4.9.0.0 |
Generic (URec Char p) # | |
data URec Char (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Char :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Char p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
The type a
will often be an instance of class
Storable
which provides the marshalling operations.
However this is not essential, and you can provide your own operations
to access the pointer. For example you might write small foreign
functions to get or set the fields of a C struct
.
Instances
Generic1 (URec (Ptr ()) :: k -> Type) # | |
Eq (Ptr a) # | Since: base-2.1 |
Data a => Data (Ptr a) # | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source # toConstr :: Ptr a -> Constr Source # dataTypeOf :: Ptr a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source # | |
Ord (Ptr a) # | Since: base-2.1 |
Show (Ptr a) # | Since: base-2.1 |
Storable (Ptr a) # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Ptr a -> Int Source # alignment :: Ptr a -> Int Source # peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source # pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source # pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source # | |
Functor (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec (Ptr ()) m -> m Source # foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m Source # foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # toList :: URec (Ptr ()) a -> [a] Source # null :: URec (Ptr ()) a -> Bool Source # length :: URec (Ptr ()) a -> Int Source # elem :: Eq a => a -> URec (Ptr ()) a -> Bool Source # maximum :: Ord a => URec (Ptr ()) a -> a Source # minimum :: Ord a => URec (Ptr ()) a -> a Source # | |
Traversable (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) Source # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) Source # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) Source # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) Source # | |
Eq (URec (Ptr ()) p) # | Since: base-4.9.0.0 |
Ord (URec (Ptr ()) p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |
Generic (URec (Ptr ()) p) # | |
data URec (Ptr ()) (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
A value of type
is a pointer to a function callable
from foreign code. The type FunPtr
aa
will normally be a foreign type,
a function type with zero or more arguments where
- the argument types are marshallable foreign types,
i.e.
Char
,Int
,Double
,Float
,Bool
,Int8
,Int16
,Int32
,Int64
,Word8
,Word16
,Word32
,Word64
,
,Ptr
a
,FunPtr
a
or a renaming of any of these usingStablePtr
anewtype
. - the return type is either a marshallable foreign type or has the form
whereIO
tt
is a marshallable foreign type or()
.
A value of type
may be a pointer to a foreign function,
either returned by another foreign function or imported with a
a static address import likeFunPtr
a
foreign import ccall "stdlib.h &free" p_free :: FunPtr (Ptr a -> IO ())
or a pointer to a Haskell function created using a wrapper stub
declared to produce a FunPtr
of the correct type. For example:
type Compare = Int -> Int -> Bool foreign import ccall "wrapper" mkCompare :: Compare -> IO (FunPtr Compare)
Calls to wrapper stubs like mkCompare
allocate storage, which
should be released with freeHaskellFunPtr
when no
longer required.
To convert FunPtr
values to corresponding Haskell functions, one
can define a dynamic stub for the specific foreign type, e.g.
type IntFunction = CInt -> IO () foreign import ccall "dynamic" mkFun :: FunPtr IntFunction -> IntFunction
Instances
Eq (FunPtr a) # | |
Ord (FunPtr a) # | |
Show (FunPtr a) # | Since: base-2.1 |
Storable (FunPtr a) # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: FunPtr a -> Int Source # alignment :: FunPtr a -> Int Source # peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) Source # pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source # pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source # |
The maximum tuple size
maxTupleSize :: Int Source #
Primitive operations
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
unsafeCoerce# :: a -> b Source #
The function unsafeCoerce#
allows you to side-step the typechecker entirely. That
is, it allows you to coerce any type into any other type. If you use this function,
you had better get it right, otherwise segmentation faults await. It is generally
used when you want to write a program that you know is well-typed, but where Haskell's
type system is not expressive enough to prove that it is well typed.
The following uses of unsafeCoerce#
are supposed to work (i.e. not lead to
spurious compile-time or run-time crashes):
- Casting any lifted type to
Any
- Casting
Any
back to the real type - Casting an unboxed type to another unboxed type of the same size.
(Casting between floating-point and integral types does not work.
See the
GHC.Float
module for functions to do work.) - Casting between two types that have the same runtime representation. One case is when
the two types differ only in "phantom" type parameters, for example
Ptr Int
toPtr Float
, or[Int]
to[Float]
when the list is known to be empty. Also, anewtype
of a typeT
has the same representation at runtime asT
.
Other uses of unsafeCoerce#
are undefined. In particular, you should not use
unsafeCoerce#
to cast a T to an algebraic data type D, unless T is also
an algebraic data type. For example, do not cast Int->Int
to Bool
, even if
you later cast that Bool
back to Int->Int
before applying it. The reasons
have to do with GHC's internal representation details (for the cognoscenti, data values
can be entered but function closures cannot). If you want a safe type to cast things
to, use Any
, which is not an algebraic data type.
Witness for an unboxed Proxy#
value, which has no runtime
representation.
data Addr# :: TYPE AddrRep Source #
An arbitrary machine address assumed to point outside the garbage-collected heap.
data ByteArray# :: TYPE UnliftedRep Source #
data MutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep Source #
data MutableByteArray# (a :: Type) :: Type -> TYPE UnliftedRep Source #
data MVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep Source #
A shared mutable variable (not the same as a MutVar#
!).
(Note: in a non-concurrent implementation, (MVar# a)
can be
represented by (MutVar# (Maybe a))
.)
data RealWorld :: Type Source #
RealWorld
is deeply magical. It is primitive, but it is not
unlifted (hence ptrArg
). We never manipulate values of type
RealWorld
; it's only used in the type system, to parameterise State#
.
data ArrayArray# :: TYPE UnliftedRep Source #
data MutableArrayArray# (a :: Type) :: Type -> TYPE UnliftedRep Source #
data State# (a :: Type) :: Type -> TYPE (TupleRep ([] :: [RuntimeRep])) Source #
State#
is the primitive, unlifted type of states. It has
one type parameter, thus State# RealWorld
, or State# s
,
where s is a type variable. The only purpose of the type parameter
is to keep different state threads separate. It is represented by
nothing at all.
data StableName# (a :: Type) :: Type -> TYPE UnliftedRep Source #
data MutVar# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep Source #
A MutVar#
behaves like a single-element mutable array.
data ThreadId# :: TYPE UnliftedRep Source #
(In a non-concurrent implementation, this can be a singleton
type, whose (unique) value is returned by myThreadId#
. The
other operations can be omitted.)
data BCO# :: TYPE UnliftedRep Source #
Primitive bytecode type.
data Compact# :: TYPE UnliftedRep Source #
data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] :: [RuntimeRep])) Source #
The type constructor Proxy#
is used to bear witness to some
type variable. It's used when you want to pass around proxy values
for doing things like modelling type applications. A Proxy#
is not only unboxed, it also has a polymorphic kind, and has no
runtime representation, being totally free.
data SmallArray# (a :: Type) :: Type -> TYPE UnliftedRep Source #
data SmallMutableArray# (a :: Type) (b :: Type) :: Type -> Type -> TYPE UnliftedRep Source #
data Word16X16# :: TYPE (VecRep Vec16 Word16ElemRep) Source #
data Word16X32# :: TYPE (VecRep Vec32 Word16ElemRep) Source #
data Word32X16# :: TYPE (VecRep Vec16 Word32ElemRep) Source #
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.
remInt# :: Int# -> Int# -> Int# Source #
Satisfies (quotInt# x y) *# y +# (remInt# x y) == x
. The
behavior is undefined if the second argument is zero.
negateInt# :: Int# -> Int# Source #
addIntC# :: Int# -> Int# -> (#Int#, Int##) Source #
Add signed integers reporting overflow.
First member of result is the sum truncated to an Int#
;
second member is zero if the true sum fits in an Int#
,
nonzero if overflow occurred (the sum is either too large
or too small to fit in an Int#
).
subIntC# :: Int# -> Int# -> (#Int#, Int##) Source #
Subtract signed integers reporting overflow.
First member of result is the difference truncated to an Int#
;
second member is zero if the true difference fits in an Int#
,
nonzero if overflow occurred (the difference is either too large
or too small to fit in an Int#
).
int2Float# :: Int# -> Float# Source #
int2Double# :: Int# -> Double# Source #
word2Float# :: Word# -> Float# Source #
word2Double# :: Word# -> Double# Source #
uncheckedIShiftL# :: Int# -> Int# -> Int# Source #
Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRA# :: Int# -> Int# -> Int# Source #
Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRL# :: Int# -> Int# -> Int# Source #
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
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#
.
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.
pdep16# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 16 bits of a word at locations specified by a mask.
pdep32# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 32 bits of a word at locations specified by a mask.
pext8# :: Word# -> Word# -> Word# Source #
Extract bits from lower 8 bits of a word at locations specified by a mask.
pext16# :: Word# -> Word# -> Word# Source #
Extract bits from lower 16 bits of a word at locations specified by a mask.
pext32# :: Word# -> Word# -> Word# Source #
Extract bits from lower 32 bits of a word at locations specified by a mask.
pext64# :: Word# -> Word# -> Word# Source #
Extract bits from a word at locations specified by a mask.
byteSwap16# :: Word# -> Word# Source #
Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.
byteSwap32# :: Word# -> Word# Source #
Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.
byteSwap64# :: Word# -> Word# Source #
Swap bytes in a 64 bits of a word.
narrow8Int# :: Int# -> Int# Source #
narrow16Int# :: Int# -> Int# Source #
narrow32Int# :: Int# -> Int# Source #
narrow8Word# :: Word# -> Word# Source #
narrow16Word# :: Word# -> Word# Source #
narrow32Word# :: Word# -> Word# Source #
negateDouble# :: Double# -> Double# Source #
fabsDouble# :: Double# -> Double# Source #
double2Int# :: Double# -> Int# Source #
Truncates a Double#
value to the nearest Int#
.
Results are undefined if the truncation if truncation yields
a value outside the range of Int#
.
double2Float# :: Double# -> Float# Source #
expDouble# :: Double# -> Double# Source #
logDouble# :: Double# -> Double# Source #
sqrtDouble# :: Double# -> Double# Source #
sinDouble# :: Double# -> Double# Source #
cosDouble# :: Double# -> Double# Source #
tanDouble# :: Double# -> Double# Source #
asinDouble# :: Double# -> Double# Source #
acosDouble# :: Double# -> Double# Source #
atanDouble# :: Double# -> Double# Source #
sinhDouble# :: Double# -> Double# Source #
coshDouble# :: Double# -> Double# Source #
tanhDouble# :: Double# -> Double# Source #
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##) Source #
Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.
decodeDouble_Int64# :: Double# -> (#Int#, Int##) Source #
Decode Double#
into mantissa and base-2 exponent.
negateFloat# :: Float# -> Float# Source #
fabsFloat# :: Float# -> Float# Source #
float2Int# :: Float# -> Int# Source #
Truncates a Float#
value to the nearest Int#
.
Results are undefined if the truncation if truncation yields
a value outside the range of Int#
.
sqrtFloat# :: Float# -> Float# Source #
asinFloat# :: Float# -> Float# Source #
acosFloat# :: Float# -> Float# Source #
atanFloat# :: Float# -> Float# Source #
sinhFloat# :: Float# -> Float# Source #
coshFloat# :: Float# -> Float# Source #
tanhFloat# :: Float# -> Float# Source #
float2Double# :: Float# -> Double# Source #
decodeFloat_Int# :: Float# -> (#Int#, Int##) Source #
Convert to integers.
First Int#
in result is the mantissa; second is the exponent.
newArray# :: 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.
sameMutableArray# :: MutableArray# d a -> MutableArray# d a -> Int# Source #
readArray# :: MutableArray# d a -> Int# -> State# d -> (#State# d, a#) Source #
Read from specified index of mutable array. Result is not yet evaluated.
writeArray# :: MutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
sizeofArray# :: Array# a -> Int# Source #
Return the number of elements in the array.
sizeofMutableArray# :: MutableArray# d a -> Int# Source #
Return the number of elements in the array.
indexArray# :: 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# :: MutableArray# d a -> State# d -> (#State# d, Array# a#) Source #
Make a mutable array immutable, without copying.
unsafeThawArray# :: Array# a -> State# d -> (#State# d, MutableArray# d a#) Source #
Make an immutable array mutable, without copying.
copyArray# :: 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.
copyMutableArray# :: 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.
cloneArray# :: Array# a -> Int# -> Int# -> Array# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
cloneMutableArray# :: MutableArray# 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.
freezeArray# :: 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.
thawArray# :: 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.
casArray# :: MutableArray# 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.
newSmallArray# :: 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.
sameSmallMutableArray# :: SmallMutableArray# d a -> SmallMutableArray# d a -> Int# Source #
readSmallArray# :: SmallMutableArray# d a -> Int# -> State# d -> (#State# d, a#) Source #
Read from specified index of mutable array. Result is not yet evaluated.
writeSmallArray# :: SmallMutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
sizeofSmallArray# :: SmallArray# a -> Int# Source #
Return the number of elements in the array.
sizeofSmallMutableArray# :: SmallMutableArray# d a -> Int# Source #
Return the number of elements in the array.
indexSmallArray# :: SmallArray# a -> Int# -> (#a#) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeSmallArray# :: SmallMutableArray# d a -> State# d -> (#State# d, SmallArray# a#) Source #
Make a mutable array immutable, without copying.
unsafeThawSmallArray# :: SmallArray# a -> State# d -> (#State# d, SmallMutableArray# d a#) Source #
Make an immutable array mutable, without copying.
copySmallArray# :: 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.
copySmallMutableArray# :: 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.
cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
cloneSmallMutableArray# :: SmallMutableArray# 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.
freezeSmallArray# :: 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.
thawSmallArray# :: 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.
casSmallArray# :: 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.
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.
newPinnedByteArray# :: Int# -> State# d -> (#State# d, MutableByteArray# d#) Source #
Create a mutable byte array that the GC guarantees not to move.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (#State# d, MutableByteArray# d#) Source #
Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move.
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 during GC.
byteArrayContents# :: ByteArray# -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
sameMutableByteArray# :: MutableByteArray# d -> MutableByteArray# d -> Int# Source #
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 sizeofMutableArray#
.
resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#) Source #
Resize (unpinned) mutable byte array to new specified size (in bytes).
The returned MutableByteArray#
is either the original
MutableByteArray#
resized in-place or, if not possible, a newly
allocated (unpinned) MutableByteArray#
(with the original content
copied over).
To avoid undefined behaviour, the original MutableByteArray#
shall
not be accessed anymore after a resizeMutableByteArray#
has been
performed. Moreover, no reference to the old one should be kept in order
to allow garbage collection of the original MutableByteArray#
in
case a new MutableByteArray#
had to be allocated.
unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (#State# d, ByteArray##) Source #
Make a mutable byte array immutable, without copying.
sizeofByteArray# :: ByteArray# -> Int# Source #
Return the size of the array in bytes.
sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #
Return the size of the array in bytes. Note that this is deprecated as it is
unsafe in the presence of concurrent resize operations on the same byte
array. See getSizeofMutableByteArray
.
getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (#State# d, Int##) Source #
Return the number of elements in the array.
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
Read 8-bit character; offset in bytes.
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
Read 31-bit character; offset in 4-byte words.
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
indexInt8Array# :: ByteArray# -> Int# -> Int# Source #
Read 8-bit integer; offset in bytes.
indexInt16Array# :: ByteArray# -> Int# -> Int# Source #
Read 16-bit integer; offset in 16-bit words.
indexInt32Array# :: ByteArray# -> Int# -> Int# Source #
Read 32-bit integer; offset in 32-bit words.
indexInt64Array# :: ByteArray# -> Int# -> Int# Source #
Read 64-bit integer; offset in 64-bit words.
indexWord8Array# :: ByteArray# -> Int# -> Word# Source #
Read 8-bit word; offset in bytes.
indexWord16Array# :: ByteArray# -> Int# -> Word# Source #
Read 16-bit word; offset in 16-bit words.
indexWord32Array# :: ByteArray# -> Int# -> Word# Source #
Read 32-bit word; offset in 32-bit words.
indexWord64Array# :: ByteArray# -> Int# -> Word# Source #
Read 64-bit word; offset in 64-bit words.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #
Read 8-bit character; offset in bytes.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #
Read 31-bit character; offset in bytes.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #
Read address; offset in bytes.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #
Read float; offset in bytes.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #
Read double; offset in bytes.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #
Read stable pointer; offset in bytes.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int# Source #
Read 16-bit int; offset in bytes.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int# Source #
Read 32-bit int; offset in bytes.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# Source #
Read 64-bit int; offset in bytes.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #
Read int; offset in bytes.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word# Source #
Read 16-bit word; offset in bytes.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word# Source #
Read 32-bit word; offset in bytes.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# Source #
Read 64-bit word; offset in bytes.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #
Read word; offset in bytes.
readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) Source #
Read 8-bit character; offset in bytes.
readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) Source #
Read 31-bit character; offset in 4-byte words.
readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
Read integer; offset in words.
readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
Read word; offset in words.
readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##) Source #
readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##) Source #
readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##) Source #
readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#) Source #
readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) Source #
readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Char##) Source #
readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Addr##) Source #
readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Float##) Source #
readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Double##) Source #
readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, StablePtr# a#) Source #
readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word##) Source #
writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write 8-bit character; offset in bytes.
writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write 31-bit character; offset in 4-byte words.
writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
writeInt8Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeInt16Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeInt32Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeInt64Array# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWord8Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord16Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord32Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord64Array# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #
compareByteArrays# src1 src1_ofs src2 src2_ofs n
compares
n
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.
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copyByteArray# src src_ofs dst dst_ofs n
copies the range
starting at offset src_ofs
of length n
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.
copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d Source #
setByteArray# ba off len c
sets the byte range [off, off+len]
of
the MutableByteArray#
to the byte c
.
atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array and an offset in Int units, read an element. The index is assumed to be in bounds. Implies a full memory barrier.
atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Given an array and an offset in Int units, write an element. The index is assumed to be in bounds. Implies a full memory barrier.
casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, an offset in Int units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to subtract, atomically substract the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to AND, atomically AND the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to NAND, atomically NAND the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to OR, atomically OR the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (#State# d, Int##) Source #
Given an array, and offset in Int units, and a value to XOR, atomically XOR the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
newArrayArray# :: Int# -> State# d -> (#State# d, MutableArrayArray# d#) Source #
Create a new mutable array of arrays with the specified number of elements, in the specified state thread, with each element recursively referring to the newly created array.
sameMutableArrayArray# :: MutableArrayArray# d -> MutableArrayArray# d -> Int# Source #
unsafeFreezeArrayArray# :: MutableArrayArray# d -> State# d -> (#State# d, ArrayArray##) Source #
Make a mutable array of arrays immutable, without copying.
sizeofArrayArray# :: ArrayArray# -> Int# Source #
Return the number of elements in the array.
sizeofMutableArrayArray# :: MutableArrayArray# d -> Int# Source #
Return the number of elements in the array.
indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# Source #
indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# Source #
readByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ByteArray##) Source #
readMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableByteArray# d#) Source #
readArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, ArrayArray##) Source #
readMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> State# d -> (#State# d, MutableArrayArray# d#) Source #
writeByteArrayArray# :: MutableArrayArray# d -> Int# -> ByteArray# -> State# d -> State# d Source #
writeMutableByteArrayArray# :: MutableArrayArray# d -> Int# -> MutableByteArray# d -> State# d -> State# d Source #
writeArrayArrayArray# :: MutableArrayArray# d -> Int# -> ArrayArray# -> State# d -> State# d Source #
writeMutableArrayArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> State# d -> State# d Source #
copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d Source #
copyMutableArrayArray# :: MutableArrayArray# d -> Int# -> MutableArrayArray# d -> Int# -> Int# -> State# d -> State# d Source #
Copy a range of the first MutableArrayArray# to the specified region in the second MutableArrayArray#. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.
minusAddr# :: Addr# -> Addr# -> Int# Source #
Result is meaningless if two Addr#
s are so far apart that their
difference doesn't fit in an Int#
.
remAddr# :: Addr# -> Int# -> Int# Source #
Return the remainder when the Addr#
arg, treated like an Int#
,
is divided by the Int#
arg.
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #
Reads 31-bit character; offset in 4-byte words.
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
readCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##) Source #
Reads 8-bit character; offset in bytes.
readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Char##) Source #
Reads 31-bit character; offset in 4-byte words.
readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (#State# d, StablePtr# a#) Source #
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
newMutVar# :: a -> State# d -> (#State# d, MutVar# d a#) Source #
Create MutVar#
with specified initial value in specified state thread.
readMutVar# :: MutVar# d a -> State# d -> (#State# d, a#) Source #
Read contents of MutVar#
. Result is not yet evaluated.
catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
maskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
maskUninterruptible# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
unmaskAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
catchRetry# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
catchSTM# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#) Source #
newTVar# :: a -> State# d -> (#State# d, TVar# d a#) Source #
Create a new TVar#
holding a specified initial value.
readTVar# :: TVar# d a -> State# d -> (#State# d, a#) Source #
Read contents of TVar#
. Result is not yet evaluated.
readTVarIO# :: TVar# d a -> State# d -> (#State# d, a#) Source #
Read contents of TVar#
outside an STM transaction
takeMVar# :: MVar# d a -> State# d -> (#State# d, a#) Source #
If MVar#
is empty, block until it becomes full.
Then remove and return its contents, and set it empty.
tryTakeMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#) Source #
If MVar#
is empty, immediately return with integer 0 and value undefined.
Otherwise, return with integer 1 and contents of MVar#
, and set MVar#
empty.
putMVar# :: MVar# d a -> a -> State# d -> State# d Source #
If MVar#
is full, block until it becomes empty.
Then store value arg as its new contents.
tryPutMVar# :: MVar# d a -> a -> State# d -> (#State# d, Int##) Source #
If MVar#
is full, immediately return with integer 0.
Otherwise, store value arg as MVar#
's new contents, and return with integer 1.
readMVar# :: MVar# d a -> State# d -> (#State# d, a#) Source #
If MVar#
is empty, block until it becomes full.
Then read its contents without modifying the MVar, without possibility
of intervention from other threads.
tryReadMVar# :: MVar# d a -> State# d -> (#State# d, Int#, a#) Source #
If MVar#
is empty, immediately return with integer 0 and value undefined.
Otherwise, return with integer 1 and contents of MVar#
.
isEmptyMVar# :: MVar# d a -> State# d -> (#State# d, Int##) Source #
Return 1 if MVar#
is empty; 0 otherwise.
waitRead# :: Int# -> State# d -> State# d Source #
Block until input is available on specified file descriptor.
waitWrite# :: Int# -> State# d -> State# d Source #
Block until output is possible on specified file descriptor.
noDuplicate# :: State# d -> State# d Source #
mkWeak# :: a -> b -> (State# RealWorld -> (#State# RealWorld, c#)) -> State# RealWorld -> (#State# RealWorld, Weak# b#) Source #
mkWeak# k v finalizer s
creates a weak reference to value k
,
with an associated reference to some value v
. If k
is still
alive then v
can be retrieved using deRefWeak#
. Note that
the type of k
must be represented by a pointer (i.e. of kind TYPE 'LiftedRep
or TYPE 'UnliftedRep
).
addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (#State# RealWorld, Int##) Source #
addCFinalizerToWeak# fptr ptr flag eptr w
attaches a C
function pointer fptr
to a weak pointer w
as a finalizer. If
flag
is zero, fptr
will be called with one argument,
ptr
. Otherwise, it will be called with two arguments,
eptr
and ptr
. addCFinalizerToWeak#
returns
1 on success, or 0 if w
is already dead.
finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, b#)#) Source #
Finalize a weak pointer. The return value is an unboxed tuple
containing the new state of the world and an "unboxed Maybe",
represented by an Int#
and a (possibly invalid) finalization
action. An Int#
of 1
indicates that the finalizer is valid. The
return value b
from the finalizer should be ignored.
makeStablePtr# :: a -> State# RealWorld -> (#State# RealWorld, StablePtr# a#) Source #
deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (#State# RealWorld, a#) Source #
eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int# Source #
makeStableName# :: a -> State# RealWorld -> (#State# RealWorld, StableName# a#) Source #
eqStableName# :: StableName# a -> StableName# b -> Int# Source #
stableNameToInt# :: StableName# a -> Int# Source #
compactNew# :: Word# -> State# RealWorld -> (#State# RealWorld, Compact##) Source #
Create a new Compact with the given size (in bytes, not words). The size is rounded up to a multiple of the allocator block size, and capped to one mega block.
compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld Source #
Set the new allocation size of the compact. This value (in bytes) determines the size of each block in the compact chain.
compactGetFirstBlock# :: Compact# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##) Source #
Returns the address and the size (in bytes) of the first block of a compact.
compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr#, Word##) Source #
Given a compact and the address of one its blocks, returns the next block and its size, or #nullAddr if the argument was the last block in the compact.
compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (#State# RealWorld, Addr##) Source #
Attempt to allocate a compact block with the given size (in bytes) at the given address. The first argument is a hint to the allocator, allocation might be satisfied at a different address (which is returned). The resulting block is not known to the GC until compactFixupPointers# is called on it, and care must be taken so that the address does not escape or memory will be leaked.
compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (#State# RealWorld, Compact#, Addr##) Source #
Given the pointer to the first block of a compact, and the address of the root object in the old address space, fix up the internal pointers inside the compact to account for a different position in memory than when it was serialized. This method must be called exactly once after importing a serialized compact, and returns the new compact and the new adjusted root address.
compactAdd# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#) Source #
Recursively add a closure and its transitive closure to a {texttt Compact#}, evaluating any unevaluated components at the same time. Note: {texttt compactAdd#} is not thread-safe, so only one thread may call {texttt compactAdd#} with a particular {texttt Compact#} at any given time. The primop does not enforce any mutual exclusion; the caller is expected to arrange this.
compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (#State# RealWorld, a#) Source #
Like {texttt compactAdd#}, but retains sharing and cycles during compaction.
compactSize# :: Compact# -> State# RealWorld -> (#State# RealWorld, Word##) Source #
Return the size (in bytes) of the total amount of data in the Compact#
reallyUnsafePtrEquality# :: a -> a -> Int# Source #
Returns {texttt 1#} if the given pointers are equal and {texttt 0#} otherwise.
numSparks# :: State# d -> (#State# d, Int##) Source #
Returns the number of sparks in the local spark pool.
dataToTag# :: a -> Int# Source #
tagToEnum# :: Int# -> a Source #
addrToAny# :: Addr# -> (#a#) Source #
Convert an Addr#
to a followable Any type.
anyToAddr# :: a -> State# RealWorld -> (#State# RealWorld, Addr##) Source #
Retrieve the address of any Haskell value. This is essentially an {texttt unsafeCoerce#}, but if implemented as such the core lint pass complains and fails to compile. As a primop, it is opaque to core/stg, and only appears in cmm (where the copy propagation pass will get rid of it). Note that "a" must be a value, not a thunk! It's too late for strictness analysis to enforce this, so you're on your own to guarantee this. Also note that {texttt Addr#} is not a GC pointer - up to you to guarantee that it does not become a dangling pointer immediately after you get it.
mkApUpd0# :: BCO# -> (#a#) Source #
Wrap a BCO in a AP_UPD
thunk which will be updated with the value of
the BCO when evaluated.
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (#State# d, BCO##) Source #
newBCO# instrs lits ptrs arity bitmap
creates a new bytecode object. The
resulting object encodes a function of the given arity with the instructions
encoded in instrs
, and a static reference table usage bitmap given by
bitmap
.
unpackClosure# :: a -> (#Addr#, ByteArray#, Array# b#) Source #
unpackClosure# closure
copies the closure and pointers in the
payload of the given closure into two new arrays, and returns a pointer to
the first word of the closure's info table, a non-pointer array for the raw
bytes of the closure, and a pointer array for the pointers in the payload.
getApStackVal# :: a -> Int# -> (#Int#, b#) Source #
getCurrentCCS# :: a -> State# d -> (#State# d, Addr##) Source #
Returns the current CostCentreStack
(value is NULL
if
not profiling). Takes a dummy argument which can be used to
avoid the call to getCurrentCCS#
being floated out by the
simplifier, which would result in an uninformative stack
("CAF").
clearCCS# :: (State# d -> (#State# d, a#)) -> State# d -> (#State# d, a#) Source #
Run the supplied IO action with an empty CCS. For example, this is used by the interpreter to run an interpreted computation without the call stack showing that it was invoked from GHC.
traceEvent# :: Addr# -> State# d -> State# d Source #
Emits an event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.
traceMarker# :: Addr# -> State# d -> State# d Source #
Emits a marker event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.
getThreadAllocationCounter# :: State# RealWorld -> (#State# RealWorld, Int##) Source #
Retrieves the allocation counter for the current thread.
setThreadAllocationCounter# :: Int# -> State# RealWorld -> State# RealWorld Source #
Sets the allocation counter for the current thread to the given value.
broadcastInt8X16# :: Int# -> Int8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X8# :: Int# -> Int16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X4# :: Int# -> Int32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X2# :: Int# -> Int64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X32# :: Int# -> Int8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X16# :: Int# -> Int16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X8# :: Int# -> Int32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X4# :: Int# -> Int64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X64# :: Int# -> Int8X64# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X32# :: Int# -> Int16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X16# :: Int# -> Int32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X8# :: Int# -> Int64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X16# :: Word# -> Word8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X8# :: Word# -> Word16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X4# :: Word# -> Word32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X2# :: Word# -> Word64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X32# :: Word# -> Word8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X16# :: Word# -> Word16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X8# :: Word# -> Word32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X4# :: Word# -> Word64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X64# :: Word# -> Word8X64# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X32# :: Word# -> Word16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X16# :: Word# -> Word32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X8# :: Word# -> Word64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX4# :: Float# -> FloatX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX2# :: Double# -> DoubleX2# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX8# :: Float# -> FloatX8# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX4# :: Double# -> DoubleX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX16# :: Float# -> FloatX16# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX8# :: Double# -> DoubleX8# Source #
Broadcast a scalar to all elements of a vector.
packInt8X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X4# :: (#Int#, Int#, Int#, Int##) -> Int32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X2# :: (#Int#, Int##) -> Int64X2# Source #
Pack the elements of an unboxed tuple into a vector.
packInt8X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X32# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X4# :: (#Int#, Int#, Int#, Int##) -> Int64X4# Source #
Pack the elements of an unboxed tuple into a vector.
packInt8X64# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int8X64# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X32# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int16X32# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X16# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X8# :: (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) -> Int64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X4# :: (#Word#, Word#, Word#, Word##) -> Word32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X2# :: (#Word#, Word##) -> Word64X2# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X32# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X4# :: (#Word#, Word#, Word#, Word##) -> Word64X4# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X64# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word8X64# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X32# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word16X32# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X16# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X8# :: (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) -> Word64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX4# :: (#Float#, Float#, Float#, Float##) -> FloatX4# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX2# :: (#Double#, Double##) -> DoubleX2# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX8# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX8# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX4# :: (#Double#, Double#, Double#, Double##) -> DoubleX4# Source #
Pack the elements of an unboxed tuple into a vector.
packFloatX16# :: (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) -> FloatX16# Source #
Pack the elements of an unboxed tuple into a vector.
packDoubleX8# :: (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) -> DoubleX8# Source #
Pack the elements of an unboxed tuple into a vector.
unpackInt8X16# :: Int8X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X8# :: Int16X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X4# :: Int32X4# -> (#Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X2# :: Int64X2# -> (#Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt8X32# :: Int8X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X16# :: Int16X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X8# :: Int32X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X4# :: Int64X4# -> (#Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt8X64# :: Int8X64# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X32# :: Int16X32# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X16# :: Int32X16# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X8# :: Int64X8# -> (#Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X16# :: Word8X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X8# :: Word16X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X4# :: Word32X4# -> (#Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X2# :: Word64X2# -> (#Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X32# :: Word8X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X16# :: Word16X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X8# :: Word32X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X4# :: Word64X4# -> (#Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X64# :: Word8X64# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X32# :: Word16X32# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X16# :: Word32X16# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X8# :: Word64X8# -> (#Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX4# :: FloatX4# -> (#Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX2# :: DoubleX2# -> (#Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX8# :: FloatX8# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX4# :: DoubleX4# -> (#Double#, Double#, Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackFloatX16# :: FloatX16# -> (#Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float##) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackDoubleX8# :: DoubleX8# -> (#Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double##) Source #
Unpack the elements of a vector into an unboxed tuple. #
insertInt8X16# :: Int8X16# -> Int# -> Int# -> Int8X16# Source #
Insert a scalar at the given position in a vector.
insertInt16X8# :: Int16X8# -> Int# -> Int# -> Int16X8# Source #
Insert a scalar at the given position in a vector.
insertInt32X4# :: Int32X4# -> Int# -> Int# -> Int32X4# Source #
Insert a scalar at the given position in a vector.
insertInt64X2# :: Int64X2# -> Int# -> Int# -> Int64X2# Source #
Insert a scalar at the given position in a vector.
insertInt8X32# :: Int8X32# -> Int# -> Int# -> Int8X32# Source #
Insert a scalar at the given position in a vector.
insertInt16X16# :: Int16X16# -> Int# -> Int# -> Int16X16# Source #
Insert a scalar at the given position in a vector.
insertInt32X8# :: Int32X8# -> Int# -> Int# -> Int32X8# Source #
Insert a scalar at the given position in a vector.
insertInt64X4# :: Int64X4# -> Int# -> Int# -> Int64X4# Source #
Insert a scalar at the given position in a vector.
insertInt8X64# :: Int8X64# -> Int# -> Int# -> Int8X64# Source #
Insert a scalar at the given position in a vector.
insertInt16X32# :: Int16X32# -> Int# -> Int# -> Int16X32# Source #
Insert a scalar at the given position in a vector.
insertInt32X16# :: Int32X16# -> Int# -> Int# -> Int32X16# Source #
Insert a scalar at the given position in a vector.
insertInt64X8# :: Int64X8# -> Int# -> Int# -> Int64X8# Source #
Insert a scalar at the given position in a vector.
insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16# Source #
Insert a scalar at the given position in a vector.
insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8# Source #
Insert a scalar at the given position in a vector.
insertWord32X4# :: Word32X4# -> Word# -> Int# -> Word32X4# Source #
Insert a scalar at the given position in a vector.
insertWord64X2# :: Word64X2# -> Word# -> Int# -> Word64X2# Source #
Insert a scalar at the given position in a vector.
insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32# Source #
Insert a scalar at the given position in a vector.
insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16# Source #
Insert a scalar at the given position in a vector.
insertWord32X8# :: Word32X8# -> Word# -> Int# -> Word32X8# Source #
Insert a scalar at the given position in a vector.
insertWord64X4# :: Word64X4# -> Word# -> Int# -> Word64X4# Source #
Insert a scalar at the given position in a vector.
insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64# Source #
Insert a scalar at the given position in a vector.
insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32# Source #
Insert a scalar at the given position in a vector.
insertWord32X16# :: Word32X16# -> Word# -> Int# -> Word32X16# Source #
Insert a scalar at the given position in a vector.
insertWord64X8# :: Word64X8# -> Word# -> Int# -> Word64X8# Source #
Insert a scalar at the given position in a vector.
insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# Source #
Insert a scalar at the given position in a vector.
insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# Source #
Insert a scalar at the given position in a vector.
insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# Source #
Insert a scalar at the given position in a vector.
insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# Source #
Insert a scalar at the given position in a vector.
insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# Source #
Insert a scalar at the given position in a vector.
insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# Source #
Insert a scalar at the given position in a vector.
plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Add two vectors element-wise.
plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Add two vectors element-wise.
plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Add two vectors element-wise.
minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Subtract two vectors element-wise.
minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Subtract two vectors element-wise.
minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Subtract two vectors element-wise.
timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Multiply two vectors element-wise.
timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Multiply two vectors element-wise.
timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Multiply two vectors element-wise.
quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Rounds towards zero element-wise.
quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Rounds towards zero element-wise.
quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Rounds towards zero element-wise.
remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #
Satisfies (quot# x y) times# y plus# (rem# x y) == x
.
negateInt8X16# :: Int8X16# -> Int8X16# Source #
Negate element-wise.
negateInt16X8# :: Int16X8# -> Int16X8# Source #
Negate element-wise.
negateInt32X4# :: Int32X4# -> Int32X4# Source #
Negate element-wise.
negateInt64X2# :: Int64X2# -> Int64X2# Source #
Negate element-wise.
negateInt8X32# :: Int8X32# -> Int8X32# Source #
Negate element-wise.
negateInt16X16# :: Int16X16# -> Int16X16# Source #
Negate element-wise.
negateInt32X8# :: Int32X8# -> Int32X8# Source #
Negate element-wise.
negateInt64X4# :: Int64X4# -> Int64X4# Source #
Negate element-wise.
negateInt8X64# :: Int8X64# -> Int8X64# Source #
Negate element-wise.
negateInt16X32# :: Int16X32# -> Int16X32# Source #
Negate element-wise.
negateInt32X16# :: Int32X16# -> Int32X16# Source #
Negate element-wise.
negateInt64X8# :: Int64X8# -> Int64X8# Source #
Negate element-wise.
negateFloatX4# :: FloatX4# -> FloatX4# Source #
Negate element-wise.
negateDoubleX2# :: DoubleX2# -> DoubleX2# Source #
Negate element-wise.
negateFloatX8# :: FloatX8# -> FloatX8# Source #
Negate element-wise.
negateDoubleX4# :: DoubleX4# -> DoubleX4# Source #
Negate element-wise.
negateFloatX16# :: FloatX16# -> FloatX16# Source #
Negate element-wise.
negateDoubleX8# :: DoubleX8# -> DoubleX8# Source #
Negate element-wise.
indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array.
indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array.
indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array.
indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array.
indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array.
indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array.
indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array.
indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array.
indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array.
indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array.
indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array.
indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array.
indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array.
indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array.
indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array.
indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array.
indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array.
indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array.
indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array.
indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array.
indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array.
indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array.
indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array.
indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array.
indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array.
indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array.
indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array.
indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array.
indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array.
indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array.
readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##) Source #
Read a vector from specified index of mutable array.
readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##) Source #
Read a vector from specified index of mutable array.
readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##) Source #
Read a vector from specified index of mutable array.
readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##) Source #
Read a vector from specified index of mutable array.
readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##) Source #
Read a vector from specified index of mutable array.
readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##) Source #
Read a vector from specified index of mutable array.
readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##) Source #
Read a vector from specified index of mutable array.
readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##) Source #
Read a vector from specified index of mutable array.
readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##) Source #
Read a vector from specified index of mutable array.
readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##) Source #
Read a vector from specified index of mutable array.
readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##) Source #
Read a vector from specified index of mutable array.
readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##) Source #
Read a vector from specified index of mutable array.
readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##) Source #
Read a vector from specified index of mutable array.
readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##) Source #
Read a vector from specified index of mutable array.
readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##) Source #
Read a vector from specified index of mutable array.
readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##) Source #
Read a vector from specified index of mutable array.
readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##) Source #
Read a vector from specified index of mutable array.
readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##) Source #
Read a vector from specified index of mutable array.
readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##) Source #
Read a vector from specified index of mutable array.
readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##) Source #
Read a vector from specified index of mutable array.
readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##) Source #
Read a vector from specified index of mutable array.
readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##) Source #
Read a vector from specified index of mutable array.
readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##) Source #
Read a vector from specified index of mutable array.
readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##) Source #
Read a vector from specified index of mutable array.
readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##) Source #
Read a vector from specified index of mutable array.
readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##) Source #
Read a vector from specified index of mutable array.
readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##) Source #
Read a vector from specified index of mutable array.
readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##) Source #
Read a vector from specified index of mutable array.
readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##) Source #
Read a vector from specified index of mutable array.
readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##) Source #
Read a vector from specified index of mutable array.
writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in bytes.
indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in bytes.
indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in bytes.
readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##) Source #
Reads vector; offset in bytes.
readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##) Source #
Reads vector; offset in bytes.
readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##) Source #
Reads vector; offset in bytes.
readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##) Source #
Reads vector; offset in bytes.
readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##) Source #
Reads vector; offset in bytes.
readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##) Source #
Reads vector; offset in bytes.
readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##) Source #
Reads vector; offset in bytes.
readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##) Source #
Reads vector; offset in bytes.
readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##) Source #
Reads vector; offset in bytes.
readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##) Source #
Reads vector; offset in bytes.
readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##) Source #
Reads vector; offset in bytes.
readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##) Source #
Reads vector; offset in bytes.
readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##) Source #
Reads vector; offset in bytes.
readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##) Source #
Reads vector; offset in bytes.
readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##) Source #
Reads vector; offset in bytes.
readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##) Source #
Reads vector; offset in bytes.
readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##) Source #
Reads vector; offset in bytes.
readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##) Source #
Reads vector; offset in bytes.
readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##) Source #
Reads vector; offset in bytes.
readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##) Source #
Reads vector; offset in bytes.
readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##) Source #
Reads vector; offset in bytes.
readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##) Source #
Reads vector; offset in bytes.
readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##) Source #
Reads vector; offset in bytes.
readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##) Source #
Reads vector; offset in bytes.
readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##) Source #
Reads vector; offset in bytes.
readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##) Source #
Reads vector; offset in bytes.
readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##) Source #
Reads vector; offset in bytes.
readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##) Source #
Reads vector; offset in bytes.
readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##) Source #
Reads vector; offset in bytes.
readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##) Source #
Reads vector; offset in bytes.
writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in bytes.
writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int8X64##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int16X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int32X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Int64X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word8X64##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word16X32##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word32X16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, Word64X8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX2##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX4##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, FloatX16##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (#State# d, DoubleX8##) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (#State# d, Int8X16##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (#State# d, Int16X8##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (#State# d, Int32X4##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (#State# d, Int64X2##) Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (#State# d, Int8X32##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (#State# d, Int16X16##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (#State# d, Int32X8##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (#State# d, Int64X4##) Source #
Reads vector; offset in scalar elements.
readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (#State# d, Int8X64##) Source #
Reads vector; offset in scalar elements.
readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (#State# d, Int16X32##) Source #
Reads vector; offset in scalar elements.
readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (#State# d, Int32X16##) Source #
Reads vector; offset in scalar elements.
readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (#State# d, Int64X8##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (#State# d, Word8X16##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (#State# d, Word16X8##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (#State# d, Word32X4##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (#State# d, Word64X2##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (#State# d, Word8X32##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (#State# d, Word16X16##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (#State# d, Word32X8##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (#State# d, Word64X4##) Source #
Reads vector; offset in scalar elements.
readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (#State# d, Word8X64##) Source #
Reads vector; offset in scalar elements.
readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (#State# d, Word16X32##) Source #
Reads vector; offset in scalar elements.
readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (#State# d, Word32X16##) Source #
Reads vector; offset in scalar elements.
readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (#State# d, Word64X8##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (#State# d, FloatX4##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX2##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (#State# d, FloatX8##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX4##) Source #
Reads vector; offset in scalar elements.
readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (#State# d, FloatX16##) Source #
Reads vector; offset in scalar elements.
readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (#State# d, DoubleX8##) Source #
Reads vector; offset in scalar elements.
writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchValue3# :: a -> State# d -> State# d Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchValue2# :: a -> State# d -> State# d Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchValue1# :: a -> State# d -> State# d Source #
prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchValue0# :: a -> State# d -> State# d Source #
shiftL# :: Word# -> Int# -> Word# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word# Source #
Shift the argument right by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic) (although an arithmetic right shift wouldn't make sense for Word#)
iShiftL# :: Int# -> Int# -> Int# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int# Source #
Shift the argument right (signed) by the specified number of bits (which must be non-negative). The RA means "right, arithmetic" (as opposed to RL for logical)
iShiftRL# :: Int# -> Int# -> Int# Source #
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic)
isTrue# :: Int# -> Bool Source #
Alias for tagToEnum#
. Returns True if its parameter is 1# and False
if it is 0#.
Fusion
Overloaded string literals
class IsString a where Source #
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a Source #
Instances
a ~ Char => IsString [a] # |
Since: base-2.1 |
Defined in Data.String fromString :: String -> [a] Source # | |
IsString a => IsString (Identity a) # | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Identity a Source # | |
IsString a => IsString (Const a b) # | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b Source # |
Debugging
breakpoint :: a -> a Source #
breakpointCond :: Bool -> a -> a Source #
Ids with special behaviour
The lazy
function restrains strictness analysis a little. The
call lazy e
means the same as e
, but lazy
has a magical
property so far as strictness analysis is concerned: it is lazy in
its first argument, even though its semantics is strict. After
strictness analysis has run, calls to lazy
are inlined to be the
identity function.
This behaviour is occasionally useful when controlling evaluation
order. Notably, lazy
is used in the library definition of
par
:
par :: a -> b -> b par x y = case (par# x) of _ -> lazy y
If lazy
were not lazy, par
would look strict in y
which
would defeat the whole purpose of par
.
The call inline f
arranges that f
is inlined, regardless of
its size. More precisely, the call inline f
rewrites to the
right-hand side of f
's definition. This allows the programmer to
control inlining from a particular call site rather than the
definition site of the function (c.f. INLINE
pragmas).
This inlining occurs regardless of the argument to the call or the
size of f
's definition; it is unconditional. The main caveat is
that f
's definition must be visible to the compiler; it is
therefore recommended to mark the function with an INLINABLE
pragma at its definition so that GHC guarantees to record its
unfolding regardless of size.
If no inlining takes place, the inline
function expands to the
identity function in Phase zero, so its use imposes no overhead.
oneShot :: (a -> b) -> a -> b Source #
The oneShot
function can be used to give a hint to the compiler that its
argument will be called at most once, which may (or may not) enable certain
optimizations. It can be useful to improve the performance of code in continuation
passing style.
If oneShot
is used wrongly, then it may be that computations whose result
that would otherwise be shared are re-evaluated every time they are used. Otherwise,
the use of oneShot
is safe.
oneShot
is representation polymorphic: the type variables may refer to lifted
or unlifted types.
Running RealWorld
state transformers
runRW# :: (State# RealWorld -> o) -> o Source #
Apply a function to a 'State# RealWorld' token. When manually applying
a function to realWorld#
, it is necessary to use NOINLINE
to prevent
semantically undesirable floating. runRW#
is inlined, but only very late
in compilation after all floating is complete.
Safe coercions
These are available from the Trustworthy module Data.Coerce as well
Since: base-4.7.0.0
coerce :: Coercible a b => a -> b Source #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
class a ~R# b => Coercible (a :: k0) (b :: k0) Source #
Coercible
is a two-parameter class that has instances for types a
and b
if
the compiler can infer that they have the same representation. This class
does not have regular instances; instead they are created on-the-fly during
type-checking. Trying to manually declare an instance of Coercible
is an error.
Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:
instance Coercible a a
Furthermore, for every type constructor there is
an instance that allows to coerce under the type constructor. For
example, let D
be a prototypical type constructor (data
or
newtype
) with three type arguments, which have roles nominal
,
representational
resp. phantom
. Then there is an instance of
the form
instance Coercible b b' => Coercible (D a b c) (D a b' c')
Note that the nominal
type arguments are equal, the
representational
type arguments can differ, but need to have a
Coercible
instance themself, and the phantom
type arguments can be
changed arbitrarily.
The third kind of instance exists for every newtype NT = MkNT T
and
comes in two variants, namely
instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b
This instance is only usable if the constructor MkNT
is in scope.
If, as a library author of a type constructor like Set a
, you
want to prevent a user of your module to write
coerce :: Set T -> Set NT
,
you need to set the role of Set
's type parameter to nominal
,
by writing
type role Set nominal
For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.
Since: ghc-prim-4.7.0.0
Equality
class a ~# b => (a :: k0) ~~ (b :: k1) Source #
Lifted, heterogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By heterogeneous, the two
types a
and b
might have different kinds. Because ~~
can
appear unexpectedly in error messages to users who do not care
about the difference between heterogeneous equality ~~
and
homogeneous equality ~
, this is printed as ~
unless
-fprint-equality-relations
is set.
Representation polymorphism
data TYPE (a :: RuntimeRep) :: RuntimeRep -> Type Source #
Instances
Functor f => Generic1 (f :.: g :: k -> Type) # | |
Functor f => Generic1 (Compose f g :: k -> Type) # | |
Monad (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Monad (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Functor (V1 :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Applicative (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Foldable (V1 :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => V1 m -> m Source # foldMap :: Monoid m => (a -> m) -> V1 a -> m Source # foldr :: (a -> b -> b) -> b -> V1 a -> b Source # foldr' :: (a -> b -> b) -> b -> V1 a -> b Source # foldl :: (b -> a -> b) -> b -> V1 a -> b Source # foldl' :: (b -> a -> b) -> b -> V1 a -> b Source # foldr1 :: (a -> a -> a) -> V1 a -> a Source # foldl1 :: (a -> a -> a) -> V1 a -> a Source # toList :: V1 a -> [a] Source # length :: V1 a -> Int Source # elem :: Eq a => a -> V1 a -> Bool Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # | |
Foldable (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => U1 m -> m Source # foldMap :: Monoid m => (a -> m) -> U1 a -> m Source # foldr :: (a -> b -> b) -> b -> U1 a -> b Source # foldr' :: (a -> b -> b) -> b -> U1 a -> b Source # foldl :: (b -> a -> b) -> b -> U1 a -> b Source # foldl' :: (b -> a -> b) -> b -> U1 a -> b Source # foldr1 :: (a -> a -> a) -> U1 a -> a Source # foldl1 :: (a -> a -> a) -> U1 a -> a Source # toList :: U1 a -> [a] Source # length :: U1 a -> Int Source # elem :: Eq a => a -> U1 a -> Bool Source # maximum :: Ord a => U1 a -> a Source # minimum :: Ord a => U1 a -> a Source # | |
Foldable (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m Source # foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source # foldr :: (a -> b -> b) -> b -> Proxy a -> b Source # foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source # foldl :: (b -> a -> b) -> b -> Proxy a -> b Source # foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source # foldr1 :: (a -> a -> a) -> Proxy a -> a Source # foldl1 :: (a -> a -> a) -> Proxy a -> a Source # toList :: Proxy a -> [a] Source # null :: Proxy a -> Bool Source # length :: Proxy a -> Int Source # elem :: Eq a => a -> Proxy a -> Bool Source # maximum :: Ord a => Proxy a -> a Source # minimum :: Ord a => Proxy a -> a Source # | |
Traversable (V1 :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
MonadPlus (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Alternative (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
MonadZip (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
MonadZip (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Show2 (Const :: Type -> Type -> Type) # | Since: base-4.9.0.0 |
Read2 (Const :: Type -> Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) Source # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] Source # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) Source # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] Source # | |
Ord2 (Const :: Type -> Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq2 (Const :: Type -> Type -> Type) # | Since: base-4.9.0.0 |
Show1 (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Read1 (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] Source # | |
Ord1 (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq1 (Proxy :: Type -> Type) # | Since: base-4.9.0.0 |
Bifunctor (Const :: Type -> Type -> Type) # | Since: base-4.8.0.0 |
Bifoldable (Const :: Type -> Type -> Type) # | Since: base-4.10.0.0 |
Bitraversable (Const :: Type -> Type -> Type) # | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source # | |
Contravariant (V1 :: Type -> Type) # | |
Contravariant (U1 :: Type -> Type) # | |
Contravariant (Proxy :: Type -> Type) # | |
Generic1 [] # | |
Generic1 Maybe # | |
Generic1 Par1 # | |
Generic1 NonEmpty # | |
Generic1 Down # | |
Generic1 Product # | |
Generic1 Sum # | |
Generic1 Dual # | |
Generic1 Last # | |
Generic1 First # | |
Generic1 Identity # | |
Generic1 ZipList # | |
Generic1 Option # | |
Generic1 WrappedMonoid # | |
Defined in Data.Semigroup type Rep1 WrappedMonoid :: k -> Type Source # from1 :: WrappedMonoid a -> Rep1 WrappedMonoid a Source # to1 :: Rep1 WrappedMonoid a -> WrappedMonoid a Source # | |
Generic1 Last # | |
Generic1 First # | |
Generic1 Max # | |
Generic1 Min # | |
Generic1 Complex # | |
Category Op # | |
Generic1 (Either a :: Type -> Type) # | |
Generic1 ((,) a :: Type -> Type) # | |
Generic1 (WrappedMonad m :: Type -> Type) # | |
Defined in Control.Applicative type Rep1 (WrappedMonad m) :: k -> Type Source # from1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source # to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source # | |
Generic1 (Arg a :: Type -> Type) # | |
Monad m => Category (Kleisli m :: Type -> Type -> Type) # | Since: base-3.0 |
Generic1 ((,,) a b :: Type -> Type) # | |
Generic1 (WrappedArrow a b :: Type -> Type) # | |
Defined in Control.Applicative type Rep1 (WrappedArrow a b) :: k -> Type Source # from1 :: WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source # to1 :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source # | |
Category ((->) :: Type -> Type -> Type) # | Since: base-3.0 |
Generic1 ((,,,) a b c :: Type -> Type) # | |
Generic1 ((,,,,) a b c d :: Type -> Type) # | |
Generic1 ((,,,,,) a b c d e :: Type -> Type) # | |
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) # | |
Monad f => Monad (Rec1 f) # | Since: base-4.9.0.0 |
Monad f => Monad (Alt f) # | Since: base-4.8.0.0 |
Monad f => Monad (Ap f) # | Since: base-4.12.0.0 |
Data p => Data (V1 p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) Source # toConstr :: V1 p -> Constr Source # dataTypeOf :: V1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # | |
Data p => Data (U1 p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) Source # toConstr :: U1 p -> Constr Source # dataTypeOf :: U1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # | |
Data t => Data (Proxy t) # | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) Source # toConstr :: Proxy t -> Constr Source # dataTypeOf :: Proxy t -> DataType Source # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) Source # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # | |
Functor f => Functor (Rec1 f) # | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Functor f => Functor (Alt f) # | Since: base-4.8.0.0 |
Functor f => Functor (Ap f) # | Since: base-4.12.0.0 |
Functor (Const m :: Type -> Type) # | Since: base-2.1 |
MonadFix f => MonadFix (Rec1 f) # | Since: base-4.9.0.0 |
MonadFix f => MonadFix (Alt f) # | Since: base-4.8.0.0 |
MonadFix f => MonadFix (Ap f) # | Since: base-4.12.0.0 |
MonadFail f => MonadFail (Ap f) # | Since: base-4.12.0.0 |
Applicative f => Applicative (Rec1 f) # | Since: base-4.9.0.0 |
Applicative f => Applicative (Alt f) # | Since: base-4.8.0.0 |
Applicative f => Applicative (Ap f) # | Since: base-4.12.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) # | Since: base-2.0.1 |
Foldable f => Foldable (Rec1 f) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => Rec1 f m -> m Source # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source # foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source # toList :: Rec1 f a -> [a] Source # null :: Rec1 f a -> Bool Source # length :: Rec1 f a -> Int Source # elem :: Eq a => a -> Rec1 f a -> Bool Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # | |
Foldable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Char m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Char a -> m Source # foldr :: (a -> b -> b) -> b -> URec Char a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Char a -> b Source # foldl :: (b -> a -> b) -> b -> URec Char a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Char a -> b Source # foldr1 :: (a -> a -> a) -> URec Char a -> a Source # foldl1 :: (a -> a -> a) -> URec Char a -> a Source # toList :: URec Char a -> [a] Source # null :: URec Char a -> Bool Source # length :: URec Char a -> Int Source # elem :: Eq a => a -> URec Char a -> Bool Source # maximum :: Ord a => URec Char a -> a Source # minimum :: Ord a => URec Char a -> a Source # | |
Foldable (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Double m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Double a -> m Source # foldr :: (a -> b -> b) -> b -> URec Double a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Double a -> b Source # foldl :: (b -> a -> b) -> b -> URec Double a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Double a -> b Source # foldr1 :: (a -> a -> a) -> URec Double a -> a Source # foldl1 :: (a -> a -> a) -> URec Double a -> a Source # toList :: URec Double a -> [a] Source # null :: URec Double a -> Bool Source # length :: URec Double a -> Int Source # elem :: Eq a => a -> URec Double a -> Bool Source # maximum :: Ord a => URec Double a -> a Source # minimum :: Ord a => URec Double a -> a Source # | |
Foldable (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Float m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Float a -> m Source # foldr :: (a -> b -> b) -> b -> URec Float a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Float a -> b Source # foldl :: (b -> a -> b) -> b -> URec Float a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Float a -> b Source # foldr1 :: (a -> a -> a) -> URec Float a -> a Source # foldl1 :: (a -> a -> a) -> URec Float a -> a Source # toList :: URec Float a -> [a] Source # null :: URec Float a -> Bool Source # length :: URec Float a -> Int Source # elem :: Eq a => a -> URec Float a -> Bool Source # maximum :: Ord a => URec Float a -> a Source # minimum :: Ord a => URec Float a -> a Source # | |
Foldable (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Int m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Int a -> m Source # foldr :: (a -> b -> b) -> b -> URec Int a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Int a -> b Source # foldl :: (b -> a -> b) -> b -> URec Int a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Int a -> b Source # foldr1 :: (a -> a -> a) -> URec Int a -> a Source # foldl1 :: (a -> a -> a) -> URec Int a -> a Source # toList :: URec Int a -> [a] Source # null :: URec Int a -> Bool Source # length :: URec Int a -> Int Source # elem :: Eq a => a -> URec Int a -> Bool Source # maximum :: Ord a => URec Int a -> a Source # minimum :: Ord a => URec Int a -> a Source # | |
Foldable (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Word m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Word a -> m Source # foldr :: (a -> b -> b) -> b -> URec Word a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Word a -> b Source # foldl :: (b -> a -> b) -> b -> URec Word a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Word a -> b Source # foldr1 :: (a -> a -> a) -> URec Word a -> a Source # foldl1 :: (a -> a -> a) -> URec Word a -> a Source # toList :: URec Word a -> [a] Source # null :: URec Word a -> Bool Source # length :: URec Word a -> Int Source # elem :: Eq a => a -> URec Word a -> Bool Source # maximum :: Ord a => URec Word a -> a Source # minimum :: Ord a => URec Word a -> a Source # | |
Foldable (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec (Ptr ()) m -> m Source # foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m Source # foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b Source # foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b Source # foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a Source # toList :: URec (Ptr ()) a -> [a] Source # null :: URec (Ptr ()) a -> Bool Source # length :: URec (Ptr ()) a -> Int Source # elem :: Eq a => a -> URec (Ptr ()) a -> Bool Source # maximum :: Ord a => URec (Ptr ()) a -> a Source # minimum :: Ord a => URec (Ptr ()) a -> a Source # | |
Foldable f => Foldable (Alt f) # | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |
Foldable f => Foldable (Ap f) # | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Ap f m -> m Source # foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source # foldr :: (a -> b -> b) -> b -> Ap f a -> b Source # foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source # foldl :: (b -> a -> b) -> b -> Ap f a -> b Source # foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source # foldr1 :: (a -> a -> a) -> Ap f a -> a Source # foldl1 :: (a -> a -> a) -> Ap f a -> a Source # toList :: Ap f a -> [a] Source # null :: Ap f a -> Bool Source # length :: Ap f a -> Int Source # elem :: Eq a => a -> Ap f a -> Bool Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # | |
Foldable (Const m :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 Source # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldr :: (a -> b -> b) -> b -> Const m a -> b Source # foldr' :: (a -> b -> b) -> b -> Const m a -> b Source # foldl :: (b -> a -> b) -> b -> Const m a -> b Source # foldl' :: (b -> a -> b) -> b -> Const m a -> b Source # foldr1 :: (a -> a -> a) -> Const m a -> a Source # foldl1 :: (a -> a -> a) -> Const m a -> a Source # toList :: Const m a -> [a] Source # null :: Const m a -> Bool Source # length :: Const m a -> Int Source # elem :: Eq a => a -> Const m a -> Bool Source # maximum :: Ord a => Const m a -> a Source # minimum :: Ord a => Const m a -> a Source # | |
Traversable f => Traversable (Rec1 f) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) Source # sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) Source # mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) Source # sequence :: Monad m => URec Double (m a) -> m (URec Double a) Source # | |
Traversable (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) Source # sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) Source # mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) Source # sequence :: Monad m => URec Float (m a) -> m (URec Float a) Source # | |
Traversable (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) Source # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) Source # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) Source # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) Source # | |
Traversable f => Traversable (Alt f) # | Since: base-4.12.0.0 |
Traversable f => Traversable (Ap f) # | Since: base-4.12.0.0 |
Traversable (Const m :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
MonadPlus f => MonadPlus (Rec1 f) # | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (Alt f) # | Since: base-4.8.0.0 |
MonadPlus f => MonadPlus (Ap f) # | Since: base-4.12.0.0 |
Alternative f => Alternative (Rec1 f) # | Since: base-4.9.0.0 |
Alternative f => Alternative (Alt f) # | Since: base-4.8.0.0 |
Alternative f => Alternative (Ap f) # | Since: base-4.12.0.0 |
MonadZip f => MonadZip (Rec1 f) # | Since: base-4.9.0.0 |
MonadZip f => MonadZip (Alt f) # | Since: base-4.8.0.0 |
Show a => Show1 (Const a :: Type -> Type) # | Since: base-4.9.0.0 |
Read a => Read1 (Const a :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source # | |
Ord a => Ord1 (Const a :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq a => Eq1 (Const a :: Type -> Type) # | Since: base-4.9.0.0 |
Bifunctor (K1 i :: Type -> Type -> Type) # | Since: base-4.9.0.0 |
Bifoldable (K1 i :: Type -> Type -> Type) # | Since: base-4.10.0.0 |
Bitraversable (K1 i :: Type -> Type -> Type) # | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) Source # | |
Contravariant f => Contravariant (Rec1 f) # | |
Contravariant f => Contravariant (Alt f) # | |
Contravariant (Const a :: Type -> Type) # | |
(Applicative f, Bounded a) => Bounded (Ap f a) # | Since: base-4.12.0.0 |
(Monad f, Monad g) => Monad (f :*: g) # | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (Product f g) # | Since: base-4.9.0.0 |
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) Source # toConstr :: Rec1 f p -> Constr Source # dataTypeOf :: Rec1 f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) Source # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # | |
(a ~ b, Data a) => Data (a :~: b) # | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) Source # toConstr :: (a :~: b) -> Constr Source # dataTypeOf :: (a :~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # | |
(Coercible a b, Data a, Data b) => Data (Coercion a b) # | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Coercion a b -> c (Coercion a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion a b) Source # toConstr :: Coercion a b -> Constr Source # dataTypeOf :: Coercion a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Coercion a b -> Coercion a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Coercion a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # | |
(Data (f a), Data a, Typeable f) => Data (Alt f a) # | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |
(Data (f a), Data a, Typeable f) => Data (Ap f a) # | Since: base-4.12.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) Source # toConstr :: Ap f a -> Constr Source # dataTypeOf :: Ap f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # | |
Functor (K1 i c :: Type -> Type) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :*: g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Sum f g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Product f g) # | Since: base-4.9.0.0 |
(Applicative f, Num a) => Num (Ap f a) # | Since: base-4.12.0.0 |
(MonadFix f, MonadFix g) => MonadFix (f :*: g) # | Since: base-4.9.0.0 |
(MonadFix f, MonadFix g) => MonadFix (Product f g) # | Since: base-4.9.0.0 |
IsString a => IsString (Const a b) # | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b Source # | |
Monoid c => Applicative (K1 i c :: Type -> Type) # | Since: base-4.12.0.0 |
(Applicative f, Applicative g) => Applicative (f :*: g) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Applicative f, Applicative g) => Applicative (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product pure :: a -> Product f g a Source # (<*>) :: Product f g (a -> b) -> Product f g a -> Product f g b Source # liftA2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c Source # (*>) :: Product f g a -> Product f g b -> Product f g b Source # (<*) :: Product f g a -> Product f g b -> Product f g a Source # | |
Foldable (K1 i c :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => K1 i c m -> m Source # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldr1 :: (a -> a -> a) -> K1 i c a -> a Source # foldl1 :: (a -> a -> a) -> K1 i c a -> a Source # toList :: K1 i c a -> [a] Source # null :: K1 i c a -> Bool Source # length :: K1 i c a -> Int Source # elem :: Eq a => a -> K1 i c a -> Bool Source # maximum :: Ord a => K1 i c a -> a Source # minimum :: Ord a => K1 i c a -> a Source # | |
(Foldable f, Foldable g) => Foldable (f :+: g) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :+: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source # toList :: (f :+: g) a -> [a] Source # null :: (f :+: g) a -> Bool Source # length :: (f :+: g) a -> Int Source # elem :: Eq a => a -> (f :+: g) a -> Bool Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # | |
(Foldable f, Foldable g) => Foldable (f :*: g) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :*: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source # toList :: (f :*: g) a -> [a] Source # null :: (f :*: g) a -> Bool Source # length :: (f :*: g) a -> Int Source # elem :: Eq a => a -> (f :*: g) a -> Bool Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # | |
(Foldable f, Foldable g) => Foldable (Sum f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum fold :: Monoid m => Sum f g m -> m Source # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m Source # foldr :: (a -> b -> b) -> b -> Sum f g a -> b Source # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b Source # foldl :: (b -> a -> b) -> b -> Sum f g a -> b Source # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b Source # foldr1 :: (a -> a -> a) -> Sum f g a -> a Source # foldl1 :: (a -> a -> a) -> Sum f g a -> a Source # toList :: Sum f g a -> [a] Source # null :: Sum f g a -> Bool Source # length :: Sum f g a -> Int Source # elem :: Eq a => a -> Sum f g a -> Bool Source # maximum :: Ord a => Sum f g a -> a Source # minimum :: Ord a => Sum f g a -> a Source # | |
(Foldable f, Foldable g) => Foldable (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product fold :: Monoid m => Product f g m -> m Source # foldMap :: Monoid m => (a -> m) -> Product f g a -> m Source # foldr :: (a -> b -> b) -> b -> Product f g a -> b Source # foldr' :: (a -> b -> b) -> b -> Product f g a -> b Source # foldl :: (b -> a -> b) -> b -> Product f g a -> b Source # foldl' :: (b -> a -> b) -> b -> Product f g a -> b Source # foldr1 :: (a -> a -> a) -> Product f g a -> a Source # foldl1 :: (a -> a -> a) -> Product f g a -> a Source # toList :: Product f g a -> [a] Source # null :: Product f g a -> Bool Source # length :: Product f g a -> Int Source # elem :: Eq a => a -> Product f g a -> Bool Source # maximum :: Ord a => Product f g a -> a Source # minimum :: Ord a => Product f g a -> a Source # | |
Traversable (K1 i c :: Type -> Type) # | Since: base-4.9.0.0 |
(Traversable f, Traversable g) => Traversable (f :+: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (f :*: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Sum f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Traversable f, Traversable g) => Traversable (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) Source # sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) Source # mapM :: Monad m => (a -> m b) -> Product f g a -> m (Product f g b) Source # sequence :: Monad m => Product f g (m a) -> m (Product f g a) Source # | |
Alternative f => Semigroup (Alt f a) # | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) # | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) # | Since: base-4.8.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) # | Since: base-4.12.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) # | Since: base-4.9.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) # | Since: base-4.9.0.0 |
(Alternative f, Alternative g) => Alternative (f :*: g) # | Since: base-4.9.0.0 |
(Alternative f, Alternative g) => Alternative (Product f g) # | Since: base-4.9.0.0 |
(MonadZip f, MonadZip g) => MonadZip (f :*: g) # | Since: base-4.9.0.0 |
(MonadZip f, MonadZip g) => MonadZip (Product f g) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Sum f g) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Product f g) # | Since: base-4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Sum f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Sum f g a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] Source # | |
(Read1 f, Read1 g) => Read1 (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product f g a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] Source # | |
(Ord1 f, Ord1 g) => Ord1 (Sum f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Ord1 f, Ord1 g) => Ord1 (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Eq1 f, Eq1 g) => Eq1 (Sum f g) # | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Product f g) # | Since: base-4.9.0.0 |
Contravariant (K1 i c :: Type -> Type) # | |
(Contravariant f, Contravariant g) => Contravariant (f :+: g) # | |
(Contravariant f, Contravariant g) => Contravariant (f :*: g) # | |
(Contravariant f, Contravariant g) => Contravariant (Sum f g) # | |
(Contravariant f, Contravariant g) => Contravariant (Product f g) # | |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) # | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) # | Since: base-4.9.0.0 |
Monad f => Monad (M1 i c f) # | Since: base-4.9.0.0 |
(Typeable i, Data p, Data c) => Data (K1 i c p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) Source # toConstr :: K1 i c p -> Constr Source # dataTypeOf :: K1 i c p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) Source # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # | |
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) Source # toConstr :: (f :+: g) p -> Constr Source # dataTypeOf :: (f :+: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # | |
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) Source # toConstr :: (f :*: g) p -> Constr Source # dataTypeOf :: (f :*: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # | |
Functor f => Functor (M1 i c f) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :.: g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Compose f g) # | Since: base-4.9.0.0 |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product compare :: Product f g a -> Product f g a -> Ordering Source # (<) :: Product f g a -> Product f g a -> Bool Source # (<=) :: Product f g a -> Product f g a -> Bool Source # (>) :: Product f g a -> Product f g a -> Bool Source # (>=) :: Product f g a -> Product f g a -> Bool Source # max :: Product f g a -> Product f g a -> Product f g a Source # min :: Product f g a -> Product f g a -> Product f g a Source # | |
(Read1 f, Read1 g, Read a) => Read (Sum f g a) # | Since: base-4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Product f g a) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Sum f g a) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Product f g a) # | Since: base-4.9.0.0 |
MonadFix f => MonadFix (M1 i c f) # | Since: base-4.9.0.0 |
Applicative f => Applicative (M1 i c f) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Applicative f, Applicative g) => Applicative (f :.: g) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Applicative f, Applicative g) => Applicative (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose pure :: a -> Compose f g a Source # (<*>) :: Compose f g (a -> b) -> Compose f g a -> Compose f g b Source # liftA2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c Source # (*>) :: Compose f g a -> Compose f g b -> Compose f g b Source # (<*) :: Compose f g a -> Compose f g b -> Compose f g a Source # | |
Foldable f => Foldable (M1 i c f) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => M1 i c f m -> m Source # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source # foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source # toList :: M1 i c f a -> [a] Source # null :: M1 i c f a -> Bool Source # length :: M1 i c f a -> Int Source # elem :: Eq a => a -> M1 i c f a -> Bool Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # | |
(Foldable f, Foldable g) => Foldable (f :.: g) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :.: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source # toList :: (f :.: g) a -> [a] Source # null :: (f :.: g) a -> Bool Source # length :: (f :.: g) a -> Int Source # elem :: Eq a => a -> (f :.: g) a -> Bool Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # | |
(Foldable f, Foldable g) => Foldable (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose fold :: Monoid m => Compose f g m -> m Source # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m Source # foldr :: (a -> b -> b) -> b -> Compose f g a -> b Source # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b Source # foldl :: (b -> a -> b) -> b -> Compose f g a -> b Source # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b Source # foldr1 :: (a -> a -> a) -> Compose f g a -> a Source # foldl1 :: (a -> a -> a) -> Compose f g a -> a Source # toList :: Compose f g a -> [a] Source # null :: Compose f g a -> Bool Source # length :: Compose f g a -> Int Source # elem :: Eq a => a -> Compose f g a -> Bool Source # maximum :: Ord a => Compose f g a -> a Source # minimum :: Ord a => Compose f g a -> a Source # | |
Traversable f => Traversable (M1 i c f) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (f :.: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose traverse :: Applicative f0 => (a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source # sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 (Compose f g a) Source # mapM :: Monad m => (a -> m b) -> Compose f g a -> m (Compose f g b) Source # sequence :: Monad m => Compose f g (m a) -> m (Compose f g a) Source # | |
MonadPlus f => MonadPlus (M1 i c f) # | Since: base-4.9.0.0 |
Alternative f => Alternative (M1 i c f) # | Since: base-4.9.0.0 |
(Alternative f, Applicative g) => Alternative (f :.: g) # | Since: base-4.9.0.0 |
(Alternative f, Applicative g) => Alternative (Compose f g) # | Since: base-4.9.0.0 |
MonadZip f => MonadZip (M1 i c f) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Compose f g) # | Since: base-4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose f g a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose f g a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] Source # | |
(Ord1 f, Ord1 g) => Ord1 (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Eq1 f, Eq1 g) => Eq1 (Compose f g) # | Since: base-4.9.0.0 |
Contravariant f => Contravariant (M1 i c f) # | |
(Functor f, Contravariant g) => Contravariant (f :.: g) # | |
(Functor f, Contravariant g) => Contravariant (Compose f g) # | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) # | Since: base-4.9.0.0 |
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) Source # toConstr :: M1 i c f p -> Constr Source # dataTypeOf :: M1 i c f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) Source # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # | |
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) # | Since: base-4.9.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) Source # toConstr :: (f :.: g) p -> Constr Source # dataTypeOf :: (f :.: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose compare :: Compose f g a -> Compose f g a -> Ordering Source # (<) :: Compose f g a -> Compose f g a -> Bool Source # (<=) :: Compose f g a -> Compose f g a -> Bool Source # (>) :: Compose f g a -> Compose f g a -> Bool Source # (>=) :: Compose f g a -> Compose f g a -> Bool Source # max :: Compose f g a -> Compose f g a -> Compose f g a Source # min :: Compose f g a -> Compose f g a -> Compose f g a Source # | |
(Read1 f, Read1 g, Read a) => Read (Compose f g a) # | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Compose f g a) # | Since: base-4.9.0.0 |
type Rep1 (f :.: g :: k -> Type) # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep1 (Compose f g :: k -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
type Rep1 [] # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 [] = D1 (MetaData "[]" "GHC.Types" "ghc-prim" False) (C1 (MetaCons "[]" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons ":" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 []))) | |
type Rep1 Maybe # | Since: base-4.6.0.0 |
type Rep1 Par1 # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep1 NonEmpty # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 NonEmpty = D1 (MetaData "NonEmpty" "GHC.Base" "base" False) (C1 (MetaCons ":|" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 []))) | |
type Rep1 Down # | Since: base-4.12.0.0 |
Defined in GHC.Generics | |
type Rep1 Product # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Sum # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Dual # | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
type Rep1 Last # | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
type Rep1 First # | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
type Rep1 Identity # | Since: base-4.8.0.0 |
Defined in Data.Functor.Identity | |
type Rep1 ZipList # | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Rep1 Option # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 WrappedMonoid # | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep1 WrappedMonoid = D1 (MetaData "WrappedMonoid" "Data.Semigroup" "base" True) (C1 (MetaCons "WrapMonoid" PrefixI True) (S1 (MetaSel (Just "unwrapMonoid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep1 Last # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 First # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Max # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Min # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
type Rep1 Complex # | Since: base-4.9.0.0 |
Defined in Data.Complex type Rep1 Complex = D1 (MetaData "Complex" "Data.Complex" "base" False) (C1 (MetaCons ":+" (InfixI NotAssociative 6) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1)) | |
type Rep1 (Either a :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep1 ((,) a :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,) a :: Type -> Type) = D1 (MetaData "(,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,)" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep1 (WrappedMonad m :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Control.Applicative type Rep1 (WrappedMonad m :: Type -> Type) = D1 (MetaData "WrappedMonad" "Control.Applicative" "base" True) (C1 (MetaCons "WrapMonad" PrefixI True) (S1 (MetaSel (Just "unwrapMonad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 m))) | |
type Rep1 (Arg a :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep1 (Arg a :: Type -> Type) = D1 (MetaData "Arg" "Data.Semigroup" "base" False) (C1 (MetaCons "Arg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep1 ((,,) a b :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,,) a b :: Type -> Type) = D1 (MetaData "(,,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,,)" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))) | |
type Rep1 (WrappedArrow a b :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Control.Applicative type Rep1 (WrappedArrow a b :: Type -> Type) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (a b)))) | |
type Rep1 ((,,,) a b c :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,,,) a b c :: Type -> Type) = D1 (MetaData "(,,,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,,,)" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))) | |
type Rep1 ((,,,,) a b c d :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,,,,) a b c d :: Type -> Type) = D1 (MetaData "(,,,,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,,,,)" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 d) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)))) | |
type Rep1 ((,,,,,) a b c d e :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,,,,,) a b c d e :: Type -> Type) = D1 (MetaData "(,,,,,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,,,,,)" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 d) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)))) | |
type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) # | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) = D1 (MetaData "(,,,,,,)" "GHC.Tuple" "ghc-prim" False) (C1 (MetaCons "(,,,,,,)" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c))) :*: ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 d) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 f) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)))) |
data RuntimeRep Source #
GHC maintains a property that the kind of all inhabited types
(as distinct from type constructors or type-level data) tells us
the runtime representation of values of that type. This datatype
encodes the choice of runtime value.
Note that TYPE
is parameterised by RuntimeRep
; this is precisely
what we mean by the fact that a type's kind encodes the runtime
representation.
For boxed values (that is, values that are represented by a pointer), a further distinction is made, between lifted types (that contain ⊥), and unlifted ones (that don't).
VecRep VecCount VecElem | a SIMD vector type |
TupleRep [RuntimeRep] | An unboxed tuple of the given reps |
SumRep [RuntimeRep] | An unboxed sum of the given reps |
LiftedRep | lifted; represented by a pointer |
UnliftedRep | unlifted; represented by a pointer |
IntRep | signed, word-sized value |
WordRep | unsigned, word-sized value |
Int64Rep | signed, 64-bit value (on 32-bit only) |
Word64Rep | unsigned, 64-bit value (on 32-bit only) |
AddrRep | A pointer, but not to a Haskell value |
FloatRep | a 32-bit floating point number |
DoubleRep | a 64-bit floating point number |
Instances
Show RuntimeRep # | Since: base-4.11.0.0 |
Length of a SIMD vector type
Instances
Bounded VecCount # | Since: base-4.10.0.0 |
Enum VecCount # | Since: base-4.10.0.0 |
Defined in GHC.Enum succ :: VecCount -> VecCount Source # pred :: VecCount -> VecCount Source # toEnum :: Int -> VecCount Source # fromEnum :: VecCount -> Int Source # enumFrom :: VecCount -> [VecCount] Source # enumFromThen :: VecCount -> VecCount -> [VecCount] Source # enumFromTo :: VecCount -> VecCount -> [VecCount] Source # enumFromThenTo :: VecCount -> VecCount -> VecCount -> [VecCount] Source # | |
Show VecCount # | Since: base-4.11.0.0 |
Element of a SIMD vector type
Int8ElemRep | |
Int16ElemRep | |
Int32ElemRep | |
Int64ElemRep | |
Word8ElemRep | |
Word16ElemRep | |
Word32ElemRep | |
Word64ElemRep | |
FloatElemRep | |
DoubleElemRep |
Instances
Bounded VecElem # | Since: base-4.10.0.0 |
Enum VecElem # | Since: base-4.10.0.0 |
Defined in GHC.Enum succ :: VecElem -> VecElem Source # pred :: VecElem -> VecElem Source # toEnum :: Int -> VecElem Source # fromEnum :: VecElem -> Int Source # enumFrom :: VecElem -> [VecElem] Source # enumFromThen :: VecElem -> VecElem -> [VecElem] Source # enumFromTo :: VecElem -> VecElem -> [VecElem] Source # enumFromThenTo :: VecElem -> VecElem -> VecElem -> [VecElem] Source # | |
Show VecElem # | Since: base-4.11.0.0 |
Transform comprehensions
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).
If Down
aa
has an
instance associated with it then comparing two
values thus wrapped will give you the opposite of their normal sort order.
This is particularly useful when sorting in generalised list comprehensions,
as in: Ord
then sortWith by
Down
x
Since: base-4.6.0.0
Down a |
Instances
Monad Down # | Since: base-4.11.0.0 |
Functor Down # | Since: base-4.11.0.0 |
MonadFix Down # | Since: base-4.12.0.0 |
Applicative Down # | Since: base-4.11.0.0 |
Foldable Down # | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Down m -> m Source # foldMap :: Monoid m => (a -> m) -> Down a -> m Source # foldr :: (a -> b -> b) -> b -> Down a -> b Source # foldr' :: (a -> b -> b) -> b -> Down a -> b Source # foldl :: (b -> a -> b) -> b -> Down a -> b Source # foldl' :: (b -> a -> b) -> b -> Down a -> b Source # foldr1 :: (a -> a -> a) -> Down a -> a Source # foldl1 :: (a -> a -> a) -> Down a -> a Source # toList :: Down a -> [a] Source # null :: Down a -> Bool Source # length :: Down a -> Int Source # elem :: Eq a => a -> Down a -> Bool Source # maximum :: Ord a => Down a -> a Source # minimum :: Ord a => Down a -> a Source # | |
Traversable Down # | Since: base-4.12.0.0 |
MonadZip Down # | Since: base-4.12.0.0 |
Show1 Down # | Since: base-4.12.0.0 |
Read1 Down # | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] Source # | |
Ord1 Down # | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Eq1 Down # | Since: base-4.12.0.0 |
Eq a => Eq (Down a) # | Since: base-4.6.0.0 |
Data a => Data (Down a) # | Since: base-4.12.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Down a -> c (Down a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Down a) Source # toConstr :: Down a -> Constr Source # dataTypeOf :: Down a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Down a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Down a)) Source # gmapT :: (forall b. Data b => b -> b) -> Down a -> Down a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Down a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Down a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) Source # | |
Num a => Num (Down a) # | Since: base-4.11.0.0 |
Ord a => Ord (Down a) # | Since: base-4.6.0.0 |
Defined in Data.Ord | |
Read a => Read (Down a) # | Since: base-4.7.0.0 |
Show a => Show (Down a) # | Since: base-4.7.0.0 |
Generic (Down a) # | |
Semigroup a => Semigroup (Down a) # | Since: base-4.11.0.0 |
Monoid a => Monoid (Down a) # | Since: base-4.11.0.0 |
Generic1 Down # | |
type Rep (Down a) # | Since: base-4.12.0.0 |
Defined in GHC.Generics | |
type Rep1 Down # | Since: base-4.12.0.0 |
Defined in GHC.Generics |
groupWith :: Ord b => (a -> b) -> [a] -> [[a]] Source #
The groupWith
function uses the user supplied function which
projects an element out of every list element in order to first sort the
input list and then to form groups by equality on these projected elements
sortWith :: Ord b => (a -> b) -> [a] -> [a] Source #
The sortWith
function sorts a list of elements using the
user supplied function to project something out of each element
the :: Eq a => [a] -> a Source #
the
ensures that all the elements of the list are identical
and then returns that unique element
Event logging
traceEvent :: String -> IO () Source #
Deprecated: Use traceEvent
or traceEventIO
SpecConstr annotations
data SpecConstrAnnotation Source #
Instances
The call stack
currentCallStack :: IO [String] Source #
Returns a [String]
representing the current call stack. This
can be useful for debugging.
The implementation uses the call-stack simulation maintained by the
profiler, so it only works if the program was compiled with -prof
and contains suitable SCC annotations (e.g. by using -fprof-auto
).
Otherwise, the list returned is likely to be empty or
uninformative.
Since: base-4.5.0.0
The Constraint kind
data Constraint Source #
The kind of constraints, like Show a
The Any type
type family Any :: k0 where ... Source #
The type constructor Any
is type to which you can unsafely coerce any
lifted type, and back. More concretely, for a lifted type t
and
value x :: t
, -- unsafeCoerce (unsafeCoerce x :: Any) :: t
is equivalent
to x
.
Overloaded lists
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
fromList :: [Item l] -> l Source #
The fromList
function constructs the structure l
from the given
list of Item l
fromListN :: Int -> [Item l] -> l Source #
The fromListN
function takes the input list's length as a hint. Its
behaviour should be equivalent to fromList
. The hint can be used to
construct the structure l
more efficiently compared to fromList
. If
the given hint does not equal to the input list's length the behaviour of
fromListN
is not specified.
toList :: l -> [Item l] Source #
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.