Copyright | (c) The University of Glasgow 1992-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | ghc-devs@haskell.org |
Stability | internal |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Basic data types and classes.
Synopsis
- isTrue# :: Int# -> Bool
- newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
- type KindBndr = Int
- data KindRep
- data Module = Module TrName TrName
- type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ...
- data Ordering
- data SPEC
- data TrName
- data TyCon = TyCon Word64# Word64# Module TrName Int# KindRep
- data TypeLitSort
- type Void# = (# #)
- data CONSTRAINT (a :: RuntimeRep)
- data TYPE (a :: RuntimeRep)
- type family Any :: k where ...
- data Bool
- data Char = C# Char#
- class a ~R# b => Coercible (a :: k) (b :: k)
- type Constraint = CONSTRAINT LiftedRep
- data DictBox a = a => MkDictBox
- data Double = D# Double#
- data DoubleBox (a :: TYPE 'DoubleRep) = MkDoubleBox a
- data Float = F# Float#
- data FloatBox (a :: TYPE 'FloatRep) = MkFloatBox a
- data Int = I# Int#
- data IntBox (a :: TYPE 'IntRep) = MkIntBox a
- data Levity
- type LiftedRep = 'BoxedRep 'Lifted
- data List a
- data Multiplicity
- data RuntimeRep
- data Symbol
- type Type = TYPE LiftedRep
- type UnliftedRep = 'BoxedRep 'Unlifted
- type UnliftedType = TYPE UnliftedRep
- data VecCount
- data VecElem
- data Word = W# Word#
- data WordBox (a :: TYPE 'WordRep) = MkWordBox a
- type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep])
- type ZeroBitType = TYPE ZeroBitRep
- class a ~# b => (a :: k) ~ (b :: k)
- class a ~# b => (a :: k0) ~~ (b :: k1)
- (*#) :: Int# -> Int# -> Int#
- (*##) :: Double# -> Double# -> Double#
- (**##) :: Double# -> Double# -> Double#
- (+#) :: Int# -> Int# -> Int#
- (+##) :: Double# -> Double# -> Double#
- (-#) :: Int# -> Int# -> Int#
- (-##) :: Double# -> Double# -> Double#
- (/##) :: Double# -> Double# -> Double#
- (/=#) :: Int# -> Int# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (<#) :: Int# -> Int# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (<=#) :: Int# -> Int# -> Int#
- (<=##) :: Double# -> Double# -> Int#
- (==#) :: Int# -> Int# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (>#) :: Int# -> Int# -> Int#
- (>##) :: Double# -> Double# -> Int#
- (>=#) :: Int# -> Int# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- acosDouble# :: Double# -> Double#
- acosFloat# :: Float# -> Float#
- acoshDouble# :: Double# -> Double#
- acoshFloat# :: Float# -> Float#
- addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #)
- addIntC# :: Int# -> Int# -> (# Int#, Int# #)
- addWordC# :: Word# -> Word# -> (# Word#, Int# #)
- addr2Int# :: Addr# -> Int#
- addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #)
- and# :: Word# -> Word# -> Word#
- and64# :: Word64# -> Word64# -> Word64#
- andI# :: Int# -> Int# -> Int#
- andWord16# :: Word16# -> Word16# -> Word16#
- andWord32# :: Word32# -> Word32# -> Word32#
- andWord8# :: Word8# -> Word8# -> Word8#
- anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #)
- asinDouble# :: Double# -> Double#
- asinFloat# :: Float# -> Float#
- asinhDouble# :: Double# -> Double#
- asinhFloat# :: Float# -> Float#
- atanDouble# :: Double# -> Double#
- atanFloat# :: Float# -> Float#
- atanhDouble# :: Double# -> Double#
- atanhFloat# :: Float# -> Float#
- atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #)
- atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #)
- atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #)
- atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #)
- atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #)
- atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
- atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #)
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #)
- atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d
- atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- bitReverse# :: Word# -> Word#
- bitReverse16# :: Word# -> Word#
- bitReverse32# :: Word# -> Word#
- bitReverse64# :: Word64# -> Word64#
- bitReverse8# :: Word# -> Word#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastInt16X16# :: Int16# -> Int16X16#
- broadcastInt16X32# :: Int16# -> Int16X32#
- broadcastInt16X8# :: Int16# -> Int16X8#
- broadcastInt32X16# :: Int32# -> Int32X16#
- broadcastInt32X4# :: Int32# -> Int32X4#
- broadcastInt32X8# :: Int32# -> Int32X8#
- broadcastInt64X2# :: Int64# -> Int64X2#
- broadcastInt64X4# :: Int64# -> Int64X4#
- broadcastInt64X8# :: Int64# -> Int64X8#
- broadcastInt8X16# :: Int8# -> Int8X16#
- broadcastInt8X32# :: Int8# -> Int8X32#
- broadcastInt8X64# :: Int8# -> Int8X64#
- broadcastWord16X16# :: Word16# -> Word16X16#
- broadcastWord16X32# :: Word16# -> Word16X32#
- broadcastWord16X8# :: Word16# -> Word16X8#
- broadcastWord32X16# :: Word32# -> Word32X16#
- broadcastWord32X4# :: Word32# -> Word32X4#
- broadcastWord32X8# :: Word32# -> Word32X8#
- broadcastWord64X2# :: Word64# -> Word64X2#
- broadcastWord64X4# :: Word64# -> Word64X4#
- broadcastWord64X8# :: Word64# -> Word64X8#
- broadcastWord8X16# :: Word8# -> Word8X16#
- broadcastWord8X32# :: Word8# -> Word8X32#
- broadcastWord8X64# :: Word8# -> Word8X64#
- byteArrayContents# :: ByteArray# -> Addr#
- byteSwap# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- byteSwap32# :: Word# -> Word#
- byteSwap64# :: Word64# -> Word64#
- casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #)
- casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #)
- casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #)
- casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #)
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #)
- casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- castDoubleToWord64# :: Double# -> Word64#
- castFloatToWord32# :: Float# -> Word32#
- castWord32ToFloat# :: Word32# -> Float#
- castWord64ToDouble# :: Word64# -> Double#
- catch# :: forall {k :: Levity} a (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- chr# :: Int# -> Char#
- clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #)
- cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a
- cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a
- cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- closureSize# :: a -> Int#
- clz# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz32# :: Word# -> Word#
- clz64# :: Word64# -> Word#
- clz8# :: Word# -> Word#
- coerce :: Coercible a b => a -> b
- compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #)
- compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #)
- compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #)
- compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld
- compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #)
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- control0# :: PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #)
- copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d
- cosDouble# :: Double# -> Double#
- cosFloat# :: Float# -> Float#
- coshDouble# :: Double# -> Double#
- coshFloat# :: Float# -> Float#
- ctz# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz32# :: Word# -> Word#
- ctz64# :: Word64# -> Word#
- ctz8# :: Word# -> Word#
- deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #)
- deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #)
- decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #)
- decodeDouble_Int64# :: Double# -> (# Int64#, Int# #)
- decodeFloat_Int# :: Float# -> (# Int#, Int# #)
- delay# :: Int# -> State# d -> State# d
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloat# :: Float# -> Float# -> Float#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- double2Float# :: Double# -> Float#
- double2Int# :: Double# -> Int#
- eqAddr# :: Addr# -> Addr# -> Int#
- eqChar# :: Char# -> Char# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- eqInt16# :: Int16# -> Int16# -> Int#
- eqInt32# :: Int32# -> Int32# -> Int#
- eqInt64# :: Int64# -> Int64# -> Int#
- eqInt8# :: Int8# -> Int8# -> Int#
- eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int#
- eqWord# :: Word# -> Word# -> Int#
- eqWord16# :: Word16# -> Word16# -> Int#
- eqWord32# :: Word32# -> Word32# -> Int#
- eqWord64# :: Word64# -> Word64# -> Int#
- eqWord8# :: Word8# -> Word8# -> Int#
- expDouble# :: Double# -> Double#
- expFloat# :: Float# -> Float#
- expm1Double# :: Double# -> Double#
- expm1Float# :: Float# -> Float#
- fabsDouble# :: Double# -> Double#
- fabsFloat# :: Float# -> Float#
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
- float2Double# :: Float# -> Double#
- float2Int# :: Float# -> Int#
- fmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fnmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fnmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fnmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fnmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fork# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- forkOn# :: Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #)
- freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #)
- geAddr# :: Addr# -> Addr# -> Int#
- geChar# :: Char# -> Char# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- geInt16# :: Int16# -> Int16# -> Int#
- geInt32# :: Int32# -> Int32# -> Int#
- geInt64# :: Int64# -> Int64# -> Int#
- geInt8# :: Int8# -> Int8# -> Int#
- geWord# :: Word# -> Word# -> Int#
- geWord16# :: Word16# -> Word16# -> Int#
- geWord32# :: Word32# -> Word32# -> Int#
- geWord64# :: Word64# -> Word64# -> Int#
- geWord8# :: Word8# -> Word8# -> Int#
- getApStackVal# :: a -> Int# -> (# Int#, b #)
- getCCSOf# :: a -> State# d -> (# State# d, Addr# #)
- getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #)
- getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #)
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #)
- getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #)
- getSpark# :: State# d -> (# State# d, Int#, a #)
- gtAddr# :: Addr# -> Addr# -> Int#
- gtChar# :: Char# -> Char# -> Int#
- gtFloat# :: Float# -> Float# -> Int#
- gtInt16# :: Int16# -> Int16# -> Int#
- gtInt32# :: Int32# -> Int32# -> Int#
- gtInt64# :: Int64# -> Int64# -> Int#
- gtInt8# :: Int8# -> Int8# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- gtWord16# :: Word16# -> Word16# -> Int#
- gtWord32# :: Word32# -> Word32# -> Int#
- gtWord64# :: Word64# -> Word64# -> Int#
- gtWord8# :: Word8# -> Word8# -> Int#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #)
- indexCharArray# :: ByteArray# -> Int# -> Char#
- indexCharOffAddr# :: Addr# -> Int# -> Char#
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- indexDoubleOffAddr# :: Addr# -> Int# -> Double#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexFloatOffAddr# :: Addr# -> Int# -> Float#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexInt16Array# :: ByteArray# -> Int# -> Int16#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt16OffAddr# :: Addr# -> Int# -> Int16#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt32Array# :: ByteArray# -> Int# -> Int32#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt32OffAddr# :: Addr# -> Int# -> Int32#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt64Array# :: ByteArray# -> Int# -> Int64#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexInt64OffAddr# :: Addr# -> Int# -> Int64#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexInt8Array# :: ByteArray# -> Int# -> Int8#
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt8OffAddr# :: Addr# -> Int# -> Int8#
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexIntOffAddr# :: Addr# -> Int# -> Int#
- indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #)
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexWideCharOffAddr# :: Addr# -> Int# -> Char#
- indexWord16Array# :: ByteArray# -> Int# -> Word16#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord16OffAddr# :: Addr# -> Int# -> Word16#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord32Array# :: ByteArray# -> Int# -> Word32#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord32OffAddr# :: Addr# -> Int# -> Word32#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord64Array# :: ByteArray# -> Int# -> Word64#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexWord64OffAddr# :: Addr# -> Int# -> Word64#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexWord8Array# :: ByteArray# -> Int# -> Word8#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord8OffAddr# :: Addr# -> Int# -> Word8#
- indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr#
- indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double#
- indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float#
- indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int#
- indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16#
- indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32#
- indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64#
- indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a
- indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word#
- indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16#
- indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32#
- indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexWordOffAddr# :: Addr# -> Int# -> Word#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16#
- insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32#
- insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8#
- insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16#
- insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4#
- insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8#
- insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2#
- insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4#
- insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8#
- insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16#
- insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32#
- insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64#
- insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16#
- insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32#
- insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8#
- insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16#
- insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4#
- insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8#
- insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2#
- insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4#
- insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8#
- insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16#
- insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32#
- insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64#
- int16ToInt# :: Int16# -> Int#
- int16ToWord16# :: Int16# -> Word16#
- int2Addr# :: Int# -> Addr#
- int2Double# :: Int# -> Double#
- int2Float# :: Int# -> Float#
- int2Word# :: Int# -> Word#
- int32ToInt# :: Int32# -> Int#
- int32ToWord32# :: Int32# -> Word32#
- int64ToInt# :: Int64# -> Int#
- int64ToWord64# :: Int64# -> Word64#
- int8ToInt# :: Int8# -> Int#
- int8ToWord8# :: Int8# -> Word8#
- intToInt16# :: Int# -> Int16#
- intToInt32# :: Int# -> Int32#
- intToInt64# :: Int# -> Int64#
- intToInt8# :: Int# -> Int8#
- isByteArrayPinned# :: ByteArray# -> Int#
- isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #)
- isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #)
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- keepAlive# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d b. a -> State# d -> (State# d -> b) -> b
- killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
- labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld
- leAddr# :: Addr# -> Addr# -> Int#
- leChar# :: Char# -> Char# -> Int#
- leFloat# :: Float# -> Float# -> Int#
- leInt16# :: Int16# -> Int16# -> Int#
- leInt32# :: Int32# -> Int32# -> Int#
- leInt64# :: Int64# -> Int64# -> Int#
- leInt8# :: Int8# -> Int8# -> Int#
- leWord# :: Word# -> Word# -> Int#
- leWord16# :: Word16# -> Word16# -> Int#
- leWord32# :: Word32# -> Word32# -> Int#
- leWord64# :: Word64# -> Word64# -> Int#
- leWord8# :: Word8# -> Word8# -> Int#
- leftSection :: forall {n :: Multiplicity} a b. (a %n -> b) -> a %n -> b
- listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #)
- log1pDouble# :: Double# -> Double#
- log1pFloat# :: Float# -> Float#
- logDouble# :: Double# -> Double#
- logFloat# :: Float# -> Float#
- ltAddr# :: Addr# -> Addr# -> Int#
- ltChar# :: Char# -> Char# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- ltInt16# :: Int16# -> Int16# -> Int#
- ltInt32# :: Int32# -> Int32# -> Int#
- ltInt64# :: Int64# -> Int64# -> Int#
- ltInt8# :: Int8# -> Int8# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- ltWord16# :: Word16# -> Word16# -> Int#
- ltWord32# :: Word32# -> Word32# -> Int#
- ltWord64# :: Word64# -> Word64# -> Int#
- ltWord8# :: Word8# -> Word8# -> Int#
- makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
- makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #)
- maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- minusAddr# :: Addr# -> Addr# -> Int#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusFloat# :: Float# -> Float# -> Float#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusWord# :: Word# -> Word# -> Word#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- mkApUpd0# :: BCO -> (# a #)
- mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- mulIntMayOflo# :: Int# -> Int# -> Int#
- mutableByteArrayContents# :: MutableByteArray# d -> Addr#
- myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #)
- narrow16Int# :: Int# -> Int#
- narrow16Word# :: Word# -> Word#
- narrow32Int# :: Int# -> Int#
- narrow32Word# :: Word# -> Word#
- narrow8Int# :: Int# -> Int#
- narrow8Word# :: Word# -> Word#
- neAddr# :: Addr# -> Addr# -> Int#
- neChar# :: Char# -> Char# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- neInt16# :: Int16# -> Int16# -> Int#
- neInt32# :: Int32# -> Int32# -> Int#
- neInt64# :: Int64# -> Int64# -> Int#
- neInt8# :: Int8# -> Int8# -> Int#
- neWord# :: Word# -> Word# -> Int#
- neWord16# :: Word16# -> Word16# -> Int#
- neWord32# :: Word32# -> Word32# -> Int#
- neWord64# :: Word64# -> Word64# -> Int#
- neWord8# :: Word8# -> Word8# -> Int#
- negateDouble# :: Double# -> Double#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- negateFloat# :: Float# -> Float#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateInt# :: Int# -> Int#
- negateInt16# :: Int16# -> Int16#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt32# :: Int32# -> Int32#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt64# :: Int64# -> Int64#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateInt8# :: Int8# -> Int8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt8X64# :: Int8X64# -> Int8X64#
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
- newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
- newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #)
- newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #)
- newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #)
- newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #)
- newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #)
- noDuplicate# :: State# d -> State# d
- not# :: Word# -> Word#
- not64# :: Word64# -> Word64#
- notI# :: Int# -> Int#
- notWord16# :: Word16# -> Word16#
- notWord32# :: Word32# -> Word32#
- notWord8# :: Word8# -> Word8#
- nullAddr# :: Addr#
- numSparks# :: State# d -> (# State# d, Int# #)
- or# :: Word# -> Word# -> Word#
- or64# :: Word64# -> Word64# -> Word64#
- orI# :: Int# -> Int# -> Int#
- orWord16# :: Word16# -> Word16# -> Word16#
- orWord32# :: Word32# -> Word32# -> Word32#
- orWord8# :: Word8# -> Word8# -> Word8#
- ord# :: Char# -> Int#
- packDoubleX2# :: (# Double#, Double# #) -> DoubleX2#
- packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4#
- packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8#
- packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16#
- packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4#
- packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8#
- packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16#
- packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32#
- packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8#
- packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16#
- packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4#
- packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8#
- packInt64X2# :: (# Int64#, Int64# #) -> Int64X2#
- packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4#
- packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8#
- packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16#
- packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32#
- packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64#
- packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16#
- packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32#
- packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8#
- packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16#
- packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4#
- packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8#
- packWord64X2# :: (# Word64#, Word64# #) -> Word64X2#
- packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4#
- packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8#
- packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16#
- packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32#
- packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64#
- par# :: a -> Int#
- pdep# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep32# :: Word# -> Word# -> Word#
- pdep64# :: Word64# -> Word64# -> Word64#
- pdep8# :: Word# -> Word# -> Word#
- pext# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext32# :: Word# -> Word# -> Word#
- pext64# :: Word64# -> Word64# -> Word64#
- pext8# :: Word# -> Word# -> Word#
- plusAddr# :: Addr# -> Int# -> Addr#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- plusFloat# :: Float# -> Float# -> Float#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusInt16# :: Int16# -> Int16# -> Int16#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt32# :: Int32# -> Int32# -> Int32#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt64# :: Int64# -> Int64# -> Int64#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusInt8# :: Int8# -> Int8# -> Int8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusWord# :: Word# -> Word# -> Word#
- plusWord16# :: Word16# -> Word16# -> Word16#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord2# :: Word# -> Word# -> (# Word#, Word# #)
- plusWord32# :: Word32# -> Word32# -> Word32#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord64# :: Word64# -> Word64# -> Word64#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusWord8# :: Word8# -> Word8# -> Word8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- popCnt# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt64# :: Word64# -> Word#
- popCnt8# :: Word# -> Word#
- powerFloat# :: Float# -> Float# -> Float#
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchValue0# :: a -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- proxy# :: forall {k} (a :: k). Proxy# a
- putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d
- quotInt# :: Int# -> Int# -> Int#
- quotInt16# :: Int16# -> Int16# -> Int16#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt32# :: Int32# -> Int32# -> Int32#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt64# :: Int64# -> Int64# -> Int64#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotInt8# :: Int8# -> Int8# -> Int8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotRemInt# :: Int# -> Int# -> (# Int#, Int# #)
- quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
- quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
- quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
- quotRemWord# :: Word# -> Word# -> (# Word#, Word# #)
- quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #)
- quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
- quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #)
- quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #)
- quotWord# :: Word# -> Word# -> Word#
- quotWord16# :: Word16# -> Word16# -> Word16#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord32# :: Word32# -> Word32# -> Word32#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord64# :: Word64# -> Word64# -> Word64#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- quotWord8# :: Word8# -> Word8# -> Word8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- raise# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> b
- raiseDivZero# :: (# #) -> b
- raiseIO# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> State# RealWorld -> (# State# RealWorld, b #)
- raiseOverflow# :: (# #) -> b
- raiseUnderflow# :: (# #) -> b
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #)
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #)
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #)
- readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #)
- readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- realWorld# :: State# RealWorld
- reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int#
- remAddr# :: Addr# -> Int# -> Int#
- remInt# :: Int# -> Int# -> Int#
- remInt16# :: Int16# -> Int16# -> Int16#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt32# :: Int32# -> Int32# -> Int32#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt64# :: Int64# -> Int64# -> Int64#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remInt8# :: Int8# -> Int8# -> Int8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remWord# :: Word# -> Word# -> Word#
- remWord16# :: Word16# -> Word16# -> Word16#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord32# :: Word32# -> Word32# -> Word32#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord64# :: Word64# -> Word64# -> Word64#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remWord8# :: Word8# -> Word8# -> Word8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #)
- rightSection :: forall {n :: Multiplicity} {o :: Multiplicity} a b c. (a %n -> b %o -> c) -> b %o -> a %n -> c
- seq :: a -> b -> b
- setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d
- sinDouble# :: Double# -> Double#
- sinFloat# :: Float# -> Float#
- sinhDouble# :: Double# -> Double#
- sinhFloat# :: Float# -> Float#
- sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int#
- sizeofByteArray# :: ByteArray# -> Int#
- sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int#
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int#
- sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int#
- spark# :: a -> State# d -> (# State# d, a #)
- sqrtDouble# :: Double# -> Double#
- sqrtFloat# :: Float# -> Float#
- stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int#
- subInt16# :: Int16# -> Int16# -> Int16#
- subInt32# :: Int32# -> Int32# -> Int32#
- subInt64# :: Int64# -> Int64# -> Int64#
- subInt8# :: Int8# -> Int8# -> Int8#
- subIntC# :: Int# -> Int# -> (# Int#, Int# #)
- subWord16# :: Word16# -> Word16# -> Word16#
- subWord32# :: Word32# -> Word32# -> Word32#
- subWord64# :: Word64# -> Word64# -> Word64#
- subWord8# :: Word8# -> Word8# -> Word8#
- subWordC# :: Word# -> Word# -> (# Word#, Int# #)
- tagToEnum# :: Int# -> a
- takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- tanDouble# :: Double# -> Double#
- tanFloat# :: Float# -> Float#
- tanhDouble# :: Double# -> Double#
- tanhFloat# :: Float# -> Float#
- thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #)
- threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #)
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesFloat# :: Float# -> Float# -> Float#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesInt16# :: Int16# -> Int16# -> Int16#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #)
- timesInt32# :: Int32# -> Int32# -> Int32#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt64# :: Int64# -> Int64# -> Int64#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesInt8# :: Int8# -> Int8# -> Int8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesWord# :: Word# -> Word# -> Word#
- timesWord16# :: Word16# -> Word16# -> Word16#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord2# :: Word# -> Word# -> (# Word#, Word# #)
- timesWord32# :: Word32# -> Word32# -> Word32#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord64# :: Word64# -> Word64# -> Word64#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesWord8# :: Word8# -> Word8# -> Word8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d
- traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d
- traceEvent# :: Addr# -> State# d -> State# d
- traceMarker# :: Addr# -> State# d -> State# d
- tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #)
- tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- uncheckedIShiftL# :: Int# -> Int# -> Int#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA# :: Int# -> Int# -> Int#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRL# :: Int# -> Int# -> Int#
- uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- uncheckedShiftL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
- uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
- uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
- uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
- uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
- uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
- unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #)
- unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #)
- unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #)
- unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #)
- unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #)
- unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #)
- unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #)
- unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #)
- unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #)
- unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #)
- unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #)
- unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #)
- unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #)
- unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #)
- unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #)
- unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
- unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #)
- unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #)
- unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #)
- unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #)
- void# :: (# #)
- waitRead# :: Int# -> State# d -> State# d
- waitWrite# :: Int# -> State# d -> State# d
- word16ToInt16# :: Word16# -> Int16#
- word16ToWord# :: Word16# -> Word#
- word2Double# :: Word# -> Double#
- word2Float# :: Word# -> Float#
- word2Int# :: Word# -> Int#
- word32ToInt32# :: Word32# -> Int32#
- word32ToWord# :: Word32# -> Word#
- word64ToInt64# :: Word64# -> Int64#
- word64ToWord# :: Word64# -> Word#
- word8ToInt8# :: Word8# -> Int8#
- word8ToWord# :: Word8# -> Word#
- wordToWord16# :: Word# -> Word16#
- wordToWord32# :: Word# -> Word32#
- wordToWord64# :: Word# -> Word64#
- wordToWord8# :: Word# -> Word8#
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #)
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d
- writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d
- writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- xor# :: Word# -> Word# -> Word#
- xor64# :: Word64# -> Word64# -> Word64#
- xorI# :: Int# -> Int# -> Int#
- xorWord16# :: Word16# -> Word16# -> Word16#
- xorWord32# :: Word32# -> Word32# -> Word32#
- xorWord8# :: Word8# -> Word8# -> Word8#
- yield# :: State# RealWorld -> State# RealWorld
- data Addr# :: TYPE 'AddrRep
- data Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data BCO
- data ByteArray# :: UnliftedType
- data CONSTRAINT (a :: RuntimeRep)
- data Char# :: TYPE 'WordRep
- data Compact# :: UnliftedType
- data Double# :: TYPE 'DoubleRep
- data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep)
- data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep)
- data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep)
- data FUN
- data Float# :: TYPE 'FloatRep
- data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep)
- data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep)
- data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep)
- data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data Int# :: TYPE 'IntRep
- data Int16# :: TYPE 'Int16Rep
- data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep)
- data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep)
- data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep)
- data Int32# :: TYPE 'Int32Rep
- data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep)
- data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep)
- data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep)
- data Int64# :: TYPE 'Int64Rep
- data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep)
- data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep)
- data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep)
- data Int8# :: TYPE 'Int8Rep
- data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep)
- data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep)
- data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep)
- data MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableByteArray# a :: UnliftedType
- data PromptTag# a :: UnliftedType
- data Proxy# (a :: k) :: ZeroBitType
- data RealWorld
- data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data StablePtr# (a :: TYPE ('BoxedRep l)) :: TYPE 'AddrRep
- data StackSnapshot# :: UnliftedType
- data State# a :: ZeroBitType
- data TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data TYPE (a :: RuntimeRep)
- data ThreadId# :: UnliftedType
- data Weak# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data Word# :: TYPE 'WordRep
- data Word16# :: TYPE 'Word16Rep
- data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep)
- data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep)
- data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep)
- data Word32# :: TYPE 'Word32Rep
- data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep)
- data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep)
- data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep)
- data Word64# :: TYPE 'Word64Rep
- data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep)
- data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep)
- data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep)
- data Word8# :: TYPE 'Word8Rep
- data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep)
- data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep)
- data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep)
- module GHC.Prim.Ext
- module GHC.Prim.PtrEq
- module GHC.Internal.Err
- module GHC.Internal.Maybe
- class IP (x :: Symbol) a | x -> a where
- ip :: a
- class Eq a where
- class Eq a => Ord a where
- eqInt :: Int -> Int -> Bool
- neInt :: Int -> Int -> Bool
- eqWord :: Word -> Word -> Bool
- neWord :: Word -> Word -> Bool
- eqChar :: Char -> Char -> Bool
- neChar :: Char -> Char -> Bool
- eqFloat :: Float -> Float -> Bool
- eqDouble :: Double -> Double -> Bool
- gtInt :: Int -> Int -> Bool
- geInt :: Int -> Int -> Bool
- leInt :: Int -> Int -> Bool
- ltInt :: Int -> Int -> Bool
- compareInt :: Int -> Int -> Ordering
- compareInt# :: Int# -> Int# -> Ordering
- gtWord :: Word -> Word -> Bool
- geWord :: Word -> Word -> Bool
- leWord :: Word -> Word -> Bool
- ltWord :: Word -> Word -> Bool
- compareWord :: Word -> Word -> Ordering
- compareWord# :: Word# -> Word# -> Ordering
- unpackCString# :: Addr# -> [Char]
- unpackAppendCString# :: Addr# -> [Char] -> [Char]
- unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a
- cstringLength# :: Addr# -> Int#
- unpackCStringUtf8# :: Addr# -> [Char]
- unpackAppendCStringUtf8# :: Addr# -> [Char] -> [Char]
- unpackFoldrCStringUtf8# :: Addr# -> (Char -> a -> a) -> a -> a
- unpackNBytes# :: Addr# -> Int# -> [Char]
- inline :: a -> a
- noinline :: a -> a
- lazy :: a -> a
- oneShot :: (a -> b) -> a -> b
- runRW# :: (State# RealWorld -> o) -> o
- seq# :: a -> State# s -> (# State# s, a #)
- class DataToTag (a :: TYPE ('BoxedRep lev)) where
- dataToTag# :: a -> Int#
- class WithDict cls meth where
- withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- data Void
- absurd :: Void -> a
- vacuous :: Functor f => f Void -> f a
- class Semigroup a where
- class Semigroup a => Monoid a where
- class Functor (f :: Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- when :: Applicative f => Bool -> f () -> f ()
- sequence :: Monad m => [m a] -> m [a]
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- ap :: Monad m => m (a -> b) -> m a -> m b
- class Applicative f => Alternative (f :: Type -> Type) where
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- data NonEmpty a = a :| [a]
- foldr :: (a -> b -> b) -> b -> [a] -> b
- build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- map :: (a -> b) -> [a] -> [b]
- mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
- (++) :: [a] -> [a] -> [a]
- type String = [Char]
- unsafeChr :: Int -> Char
- ord :: Char -> Int
- eqString :: String -> String -> Bool
- minInt :: Int
- maxInt :: Int
- otherwise :: Bool
- id :: a -> a
- assert :: Bool -> a -> a
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- data Opaque = O a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: (a -> b) -> a -> b
- ($!) :: (a -> b) -> a -> b
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- returnIO :: a -> IO a
- bindIO :: IO a -> (a -> IO b) -> IO b
- thenIO :: IO a -> IO b -> IO b
- failIO :: String -> IO a
- unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #)
- getTag :: forall {lev :: Levity} (a :: TYPE ('BoxedRep lev)). DataToTag a => a -> Int#
- quotInt :: Int -> Int -> Int
- remInt :: Int -> Int -> Int
- divInt :: Int -> Int -> Int
- modInt :: Int -> Int -> Int
- quotRemInt :: Int -> Int -> (Int, Int)
- divModInt :: Int -> Int -> (Int, Int)
- shift_mask :: Int# -> Int# -> Int#
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- divInt# :: Int# -> Int# -> Int#
- divInt8# :: Int8# -> Int8# -> Int8#
- divInt16# :: Int16# -> Int16# -> Int16#
- divInt32# :: Int32# -> Int32# -> Int32#
- modInt# :: Int# -> Int# -> Int#
- modInt8# :: Int8# -> Int8# -> Int8#
- modInt16# :: Int16# -> Int16# -> Int16#
- modInt32# :: Int32# -> Int32# -> Int32#
- divModInt# :: Int# -> Int# -> (# Int#, Int# #)
- divModInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
- divModInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
- divModInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
Documentation
isTrue# :: Int# -> Bool Source #
Alias for tagToEnum#
. Returns True if its parameter is 1# and False
if it is 0#.
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to
Main.main
in your program. When your program is run, the I/O will
be performed. It isn't possible to perform I/O from an arbitrary
function, unless that function is itself in the IO
monad and called
at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation
or the >>
and >>=
operations from the Monad
class.
Instances
The representation produced by GHC for conjuring up the kind of a
TypeRep
.
type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ... Source #
Instances
SPEC
is used by GHC in the SpecConstr
pass in order to inform
the compiler when to be particularly aggressive. In particular, it
tells GHC to specialize regardless of size or the number of
specializations. However, not all loops fall into this category.
Libraries can specify this by using SPEC
data type to inform which
loops should be aggressively specialized. For example,
instead of
loop x where loop arg = ...
write
loop SPEC x where loop !_ arg = ...
There is no semantic difference between SPEC
and SPEC2
,
we just need a type with two constructors lest it is optimised away
before SpecConstr
.
This type is reexported from GHC.Exts since GHC 9.0 and base-4.15
.
For compatibility with earlier releases import it from GHC.Types
in ghc-prim
package.
Since: ghc-prim-0.3.1.0
data TypeLitSort Source #
Instances
Show TypeLitSort Source # | Since: base-4.11.0.0 |
Defined in GHC.Internal.Show |
data CONSTRAINT (a :: RuntimeRep) Source #
data TYPE (a :: RuntimeRep) Source #
Instances
type family Any :: k where ... Source #
The type constructor Any :: forall k. k
is a type to which you can unsafely coerce any type, and back.
For unsafeCoerce
this means for all lifted types t
that
unsafeCoerce (unsafeCoerce x :: Any) :: t
is equivalent to x
and safe.
The same is true for *all* types when using
unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep)
(a :: TYPE r1) (b :: TYPE r2).
a -> b
but only if you instantiate r1
and r2
to the same runtime representation.
For example using (unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE IntRep). a -> b) x
is fine, but (unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE FloatRep). a -> b)
will likely cause seg-faults or worse.
For this resason, users should always prefer unsafeCoerce over unsafeCoerce# when possible.
Here are some more examples:
bad_a1 :: Any
(TYPE 'IntRep)
bad_a1 = unsafeCoerce# True
bad_a2 :: Any (TYPE ('BoxedRep 'UnliftedRep))
bad_a2 = unsafeCoerce# True
Here bad_a1
is bad because we started with True :: (Bool :: Type)
, represented by a boxed heap pointer,
and coerced it to a1 :: Any
(TYPE 'IntRep), whose representation is a non-pointer integer.
That's why we had to use
bad_a2unsafeCoerce#
; it is really unsafe because it can change representations.
Similarly is bad because although both
True and
bad_a2 are represented by a heap pointer,
True is lifted but
bad_a2@ is not; bugs here may be rather subtle.
If you must use unsafeCoerce# to cast to Any
, type annotations are recommended
to make sure that Any
has the correct kind. As casting between different runtimereps is
unsound. For example to cast a ByteArray#
to Any
you might use:
unsafeCoerce# b :: (Any :: TYPE ('BoxedRep 'Unlifted))
Instances
Bits Bool Source # | Interpret Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Bits (.&.) :: Bool -> Bool -> Bool Source # (.|.) :: Bool -> Bool -> Bool Source # xor :: Bool -> Bool -> Bool Source # complement :: Bool -> Bool Source # shift :: Bool -> Int -> Bool Source # rotate :: Bool -> Int -> Bool Source # setBit :: Bool -> Int -> Bool Source # clearBit :: Bool -> Int -> Bool Source # complementBit :: Bool -> Int -> Bool Source # testBit :: Bool -> Int -> Bool Source # bitSizeMaybe :: Bool -> Maybe Int Source # bitSize :: Bool -> Int Source # isSigned :: Bool -> Bool Source # shiftL :: Bool -> Int -> Bool Source # unsafeShiftL :: Bool -> Int -> Bool Source # shiftR :: Bool -> Int -> Bool Source # unsafeShiftR :: Bool -> Int -> Bool Source # rotateL :: Bool -> Int -> Bool Source # | |||||
FiniteBits Bool Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Bits finiteBitSize :: Bool -> Int Source # countLeadingZeros :: Bool -> Int Source # countTrailingZeros :: Bool -> Int Source # | |||||
Data Bool Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool Source # toConstr :: Bool -> Constr Source # dataTypeOf :: Bool -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) Source # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool Source # | |||||
Bounded Bool Source # | Since: base-2.1 | ||||
Enum Bool Source # | Since: base-2.1 | ||||
Storable Bool Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Bool -> Int Source # alignment :: Bool -> Int Source # peekElemOff :: Ptr Bool -> Int -> IO Bool Source # pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Bool Source # pokeByteOff :: Ptr b -> Int -> Bool -> IO () Source # | |||||
Generic Bool Source # | |||||
Defined in GHC.Internal.Generics | |||||
SingKind Bool | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics
| |||||
Ix Bool Source # | Since: base-2.1 | ||||
Read Bool Source # | Since: base-2.1 | ||||
Show Bool Source # | Since: base-2.1 | ||||
Eq Bool Source # | |||||
Ord Bool Source # | |||||
SingI 'False | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
SingI 'True | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Lift Bool Source # | |||||
type DemoteRep Bool Source # | |||||
Defined in GHC.Internal.Generics | |||||
type Rep Bool Source # | Since: base-4.6.0.0 | ||||
data Sing (a :: Bool) Source # | |||||
The character type Char
represents Unicode codespace
and its elements are code points as in definitions
D9 and D10 of the Unicode Standard.
Character literals in Haskell are single-quoted: 'Q'
, 'Я'
or 'Ω'
.
To represent a single quote itself use '\''
, and to represent a backslash
use '\\'
. The full grammar can be found in the section 2.6 of the
Haskell 2010 Language Report.
To specify a character by its code point one can use decimal, hexadecimal
or octal notation: '\65'
, '\x41'
and '\o101'
are all alternative forms
of 'A'
. The largest code point is '\x10ffff'
.
There is a special escape syntax for ASCII control characters:
Escape | Alternatives | Meaning |
---|---|---|
'\NUL' | '\0' | null character |
'\SOH' | '\1' | start of heading |
'\STX' | '\2' | start of text |
'\ETX' | '\3' | end of text |
'\EOT' | '\4' | end of transmission |
'\ENQ' | '\5' | enquiry |
'\ACK' | '\6' | acknowledge |
'\BEL' | '\7' , '\a' | bell (alert) |
'\BS' | '\8' , '\b' | backspace |
'\HT' | '\9' , '\t' | horizontal tab |
'\LF' | '\10' , '\n' | line feed (new line) |
'\VT' | '\11' , '\v' | vertical tab |
'\FF' | '\12' , '\f' | form feed |
'\CR' | '\13' , '\r' | carriage return |
'\SO' | '\14' | shift out |
'\SI' | '\15' | shift in |
'\DLE' | '\16' | data link escape |
'\DC1' | '\17' | device control 1 |
'\DC2' | '\18' | device control 2 |
'\DC3' | '\19' | device control 3 |
'\DC4' | '\20' | device control 4 |
'\NAK' | '\21' | negative acknowledge |
'\SYN' | '\22' | synchronous idle |
'\ETB' | '\23' | end of transmission block |
'\CAN' | '\24' | cancel |
'\EM' | '\25' | end of medium |
'\SUB' | '\26' | substitute |
'\ESC' | '\27' | escape |
'\FS' | '\28' | file separator |
'\GS' | '\29' | group separator |
'\RS' | '\30' | record separator |
'\US' | '\31' | unit separator |
'\SP' | '\32' , ' ' | space |
'\DEL' | '\127' | delete |
Instances
IsChar Char Source # | Since: base-2.1 | ||||
PrintfArg Char Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |||||
Data Char Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char Source # toConstr :: Char -> Constr Source # dataTypeOf :: Char -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) Source # gmapT :: (forall b. Data b => b -> b) -> Char -> Char Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source # | |||||
Bounded Char Source # | Since: base-2.1 | ||||
Enum Char Source # | Since: base-2.1 | ||||
Storable Char Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Char -> Int Source # alignment :: Char -> Int Source # peekElemOff :: Ptr Char -> Int -> IO Char Source # pokeElemOff :: Ptr Char -> Int -> Char -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Char Source # pokeByteOff :: Ptr b -> Int -> Char -> IO () Source # | |||||
Ix Char Source # | Since: base-2.1 | ||||
Read Char Source # | Since: base-2.1 | ||||
Show Char Source # | Since: base-2.1 | ||||
Eq Char Source # | |||||
Ord Char Source # | |||||
TestCoercion SChar Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
TestEquality SChar Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
Lift Char Source # | |||||
Generic1 (URec Char :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Ord1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Char p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Char p -> URec Char p -> Ordering Source # (<) :: URec Char p -> URec Char p -> Bool Source # (<=) :: URec Char p -> URec Char p -> Bool Source # (>) :: URec Char p -> URec Char p -> Bool Source # (>=) :: URec Char p -> URec Char p -> Bool Source # | |||||
data URec Char (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Compare (a :: Char) (b :: Char) Source # | |||||
Defined in GHC.Internal.Data.Type.Ord | |||||
type Rep1 (URec Char :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Char p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
class a ~R# b => Coercible (a :: k) (b :: k) Source #
Coercible
is a two-parameter class that has instances for types a
and b
if
the compiler can infer that they have the same representation. This class
does not have regular instances; instead they are created on-the-fly during
type-checking. Trying to manually declare an instance of Coercible
is an error.
Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:
instance Coercible a a
Furthermore, for every type constructor there is
an instance that allows to coerce under the type constructor. For
example, let D
be a prototypical type constructor (data
or
newtype
) with three type arguments, which have roles nominal
,
representational
resp. phantom
. Then there is an instance of
the form
instance Coercible b b' => Coercible (D a b c) (D a b' c')
Note that the nominal
type arguments are equal, the
representational
type arguments can differ, but need to have a
Coercible
instance themself, and the phantom
type arguments can be
changed arbitrarily.
The third kind of instance exists for every newtype NT = MkNT T
and
comes in two variants, namely
instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b
This instance is only usable if the constructor MkNT
is in scope.
If, as a library author of a type constructor like Set a
, you
want to prevent a user of your module to write
coerce :: Set T -> Set NT
,
you need to set the role of Set
's type parameter to nominal
,
by writing
type role Set nominal
For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.
Since: ghc-prim-0.4.0
type Constraint = CONSTRAINT LiftedRep Source #
The kind of lifted constraints
Data type Dict
provides a simple way to wrap up a (lifted)
constraint as a type
a => MkDictBox |
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
PrintfArg Double Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: Double -> FieldFormatter Source # parseFormat :: Double -> ModifierParser Source # | |||||
Data Double Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double Source # toConstr :: Double -> Constr Source # dataTypeOf :: Double -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) Source # gmapT :: (forall b. Data b => b -> b) -> Double -> Double Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double Source # | |||||
Floating Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float exp :: Double -> Double Source # log :: Double -> Double Source # sqrt :: Double -> Double Source # (**) :: Double -> Double -> Double Source # logBase :: Double -> Double -> Double Source # sin :: Double -> Double Source # cos :: Double -> Double Source # tan :: Double -> Double Source # asin :: Double -> Double Source # acos :: Double -> Double Source # atan :: Double -> Double Source # sinh :: Double -> Double Source # cosh :: Double -> Double Source # tanh :: Double -> Double Source # asinh :: Double -> Double Source # acosh :: Double -> Double Source # atanh :: Double -> Double Source # log1p :: Double -> Double Source # expm1 :: Double -> Double Source # | |||||
RealFloat Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float floatRadix :: Double -> Integer Source # floatDigits :: Double -> Int Source # floatRange :: Double -> (Int, Int) Source # decodeFloat :: Double -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Double Source # exponent :: Double -> Int Source # significand :: Double -> Double Source # scaleFloat :: Int -> Double -> Double Source # isNaN :: Double -> Bool Source # isInfinite :: Double -> Bool Source # isDenormalized :: Double -> Bool Source # isNegativeZero :: Double -> Bool Source # | |||||
Storable Double Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Double -> Int Source # alignment :: Double -> Int Source # peekElemOff :: Ptr Double -> Int -> IO Double Source # pokeElemOff :: Ptr Double -> Int -> Double -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Double Source # pokeByteOff :: Ptr b -> Int -> Double -> IO () Source # | |||||
Read Double Source # | Since: base-2.1 | ||||
Eq Double Source # | Note that due to the presence of
Also note that
| ||||
Ord Double Source # | IEEE 754 IEEE 754-2008, section 5.11 requires that if at least one of arguments of
IEEE 754-2008, section 5.10 defines Thus, users must be extremely cautious when using Moving further, the behaviour of IEEE 754-2008 compliant | ||||
Defined in GHC.Classes | |||||
Lift Double Source # | |||||
Generic1 (URec Double :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Ord1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Double p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |||||
data URec Double (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Double :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Double p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
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
PrintfArg Float Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: Float -> FieldFormatter Source # parseFormat :: Float -> ModifierParser Source # | |||||
Data Float Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Float -> c Float Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float Source # toConstr :: Float -> Constr Source # dataTypeOf :: Float -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) Source # gmapT :: (forall b. Data b => b -> b) -> Float -> Float Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float Source # | |||||
Floating Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float exp :: Float -> Float Source # log :: Float -> Float Source # sqrt :: Float -> Float Source # (**) :: Float -> Float -> Float Source # logBase :: Float -> Float -> Float Source # sin :: Float -> Float Source # cos :: Float -> Float Source # tan :: Float -> Float Source # asin :: Float -> Float Source # acos :: Float -> Float Source # atan :: Float -> Float Source # sinh :: Float -> Float Source # cosh :: Float -> Float Source # tanh :: Float -> Float Source # asinh :: Float -> Float Source # acosh :: Float -> Float Source # atanh :: Float -> Float Source # log1p :: Float -> Float Source # expm1 :: Float -> Float Source # | |||||
RealFloat Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Float floatRadix :: Float -> Integer Source # floatDigits :: Float -> Int Source # floatRange :: Float -> (Int, Int) Source # decodeFloat :: Float -> (Integer, Int) Source # encodeFloat :: Integer -> Int -> Float Source # exponent :: Float -> Int Source # significand :: Float -> Float Source # scaleFloat :: Int -> Float -> Float Source # isNaN :: Float -> Bool Source # isInfinite :: Float -> Bool Source # isDenormalized :: Float -> Bool Source # isNegativeZero :: Float -> Bool Source # | |||||
Storable Float Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable sizeOf :: Float -> Int Source # alignment :: Float -> Int Source # peekElemOff :: Ptr Float -> Int -> IO Float Source # pokeElemOff :: Ptr Float -> Int -> Float -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Float Source # pokeByteOff :: Ptr b -> Int -> Float -> IO () Source # | |||||
Read Float Source # | Since: base-2.1 | ||||
Eq Float Source # | Note that due to the presence of
Also note that
| ||||
Ord Float Source # | See | ||||
Defined in GHC.Classes | |||||
Lift Float Source # | |||||
Generic1 (URec Float :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Ord1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Float p) Source # | |||||
Eq (URec Float p) Source # | |||||
Ord (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |||||
data URec Float (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Float :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics |
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
PrintfArg Int Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: Int -> FieldFormatter Source # parseFormat :: Int -> ModifierParser Source # | |||||
Bits Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Bits (.&.) :: Int -> Int -> Int Source # (.|.) :: Int -> Int -> Int Source # xor :: Int -> Int -> Int Source # complement :: Int -> Int Source # shift :: Int -> Int -> Int Source # rotate :: Int -> Int -> Int Source # setBit :: Int -> Int -> Int Source # clearBit :: Int -> Int -> Int Source # complementBit :: Int -> Int -> Int Source # testBit :: Int -> Int -> Bool Source # bitSizeMaybe :: Int -> Maybe Int Source # bitSize :: Int -> Int Source # isSigned :: Int -> Bool Source # shiftL :: Int -> Int -> Int Source # unsafeShiftL :: Int -> Int -> Int Source # shiftR :: Int -> Int -> Int Source # unsafeShiftR :: Int -> Int -> Int Source # rotateL :: Int -> Int -> Int Source # | |||||
FiniteBits Int Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Bits finiteBitSize :: Int -> Int Source # countLeadingZeros :: Int -> Int Source # countTrailingZeros :: Int -> Int Source # | |||||
Data Int Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int Source # toConstr :: Int -> Constr Source # dataTypeOf :: Int -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) Source # gmapT :: (forall b. Data b => b -> b) -> Int -> Int Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source # | |||||
Bounded Int Source # | Since: base-2.1 | ||||
Enum Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Enum | |||||
Storable Int Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Foreign.Storable | |||||
Ix Int Source # | Since: base-2.1 | ||||
Num Int Source # | Since: base-2.1 | ||||
Read Int Source # | Since: base-2.1 | ||||
Integral Int Source # | Since: base-2.0.1 | ||||
Real Int Source # | Since: base-2.0.1 | ||||
Defined in GHC.Internal.Real toRational :: Int -> Rational Source # | |||||
Show Int Source # | Since: base-2.1 | ||||
Eq Int Source # | |||||
Ord Int Source # | |||||
Lift Int Source # | |||||
Generic1 (URec Int :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Ord1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Int p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics compare :: URec Int p -> URec Int p -> Ordering Source # (<) :: URec Int p -> URec Int p -> Bool Source # (<=) :: URec Int p -> URec Int p -> Bool Source # (>) :: URec Int p -> URec Int p -> Bool Source # (>=) :: URec Int p -> URec Int p -> Bool Source # | |||||
data URec Int (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Int :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Int p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
Whether a boxed type is lifted or unlifted.
Instances
Bounded Levity Source # | Since: base-4.16.0.0 |
Enum Levity Source # | Since: base-4.16.0.0 |
Defined in GHC.Internal.Enum succ :: Levity -> Levity Source # pred :: Levity -> Levity Source # toEnum :: Int -> Levity Source # fromEnum :: Levity -> Int Source # enumFrom :: Levity -> [Levity] Source # enumFromThen :: Levity -> Levity -> [Levity] Source # enumFromTo :: Levity -> Levity -> [Levity] Source # enumFromThenTo :: Levity -> Levity -> Levity -> [Levity] Source # | |
Show Levity Source # | Since: base-4.15.0.0 |
The builtin linked list type.
In Haskell, lists are one of the most important data types as they are often used analogous to loops in imperative programming languages. These lists are singly linked, which makes them unsuited for operations that require \(\mathcal{O}(1)\) access. Instead, they are intended to be traversed.
You can use List a
or [a]
in type signatures:
length :: [a] -> Int
or
length :: List a -> Int
They are fully equivalent, and List a
will be normalised to [a]
.
Usage
Lists are constructed recursively using the right-associative constructor operator (or cons)
(:) :: a -> [a] -> [a]
, which prepends an element to a list,
and the empty list []
.
(1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
Lists can also be constructed using list literals
of the form [x_1, x_2, ..., x_n]
which are syntactic sugar and, unless -XOverloadedLists
is enabled,
are translated into uses of (:)
and []
String
literals, like "I 💜 hs"
, are translated into
Lists of characters, ['I', ' ', '💜', ' ', 'h', 's']
.
Implementation
Internally and in memory, all the above are represented like this, with arrows being pointers to locations in memory.
╭───┬───┬──╮ ╭───┬───┬──╮ ╭───┬───┬──╮ ╭────╮ │(:)│ │ ─┼──>│(:)│ │ ─┼──>│(:)│ │ ─┼──>│ [] │ ╰───┴─┼─┴──╯ ╰───┴─┼─┴──╯ ╰───┴─┼─┴──╯ ╰────╯ v v v 1 2 3
Examples
>>> ['H', 'a', 's', 'k', 'e', 'l', 'l'] "Haskell"
>>> 1 : [4, 1, 5, 9] [1,4,1,5,9]
>>> [] : [] : [] [[],[]]
Since: ghc-prim-0.10.0
Instances
Eq1 [] Source # | Since: base-4.9.0.0 | ||||
Ord1 [] Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering Source # | |||||
Read1 [] Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 [] Source # | Since: base-4.9.0.0 | ||||
Alternative [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
Applicative [] Source # | Since: base-2.1 | ||||
Functor [] Source # | Since: base-2.1 | ||||
Monad [] Source # | Since: base-2.1 | ||||
MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
MonadFail [] Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Control.Monad.Fail | |||||
MonadFix [] Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
MonadZip [] Source # | Since: ghc-internal-4.3.1.0 | ||||
Foldable [] Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => [m] -> m Source # foldMap :: Monoid m => (a -> m) -> [a] -> m Source # foldMap' :: Monoid m => (a -> m) -> [a] -> m Source # foldr :: (a -> b -> b) -> b -> [a] -> b Source # foldr' :: (a -> b -> b) -> b -> [a] -> b Source # foldl :: (b -> a -> b) -> b -> [a] -> b Source # foldl' :: (b -> a -> b) -> b -> [a] -> b Source # foldr1 :: (a -> a -> a) -> [a] -> a Source # foldl1 :: (a -> a -> a) -> [a] -> a Source # elem :: Eq a => a -> [a] -> Bool Source # maximum :: Ord a => [a] -> a Source # minimum :: Ord a => [a] -> a Source # | |||||
Traversable [] Source # | Since: base-2.1 | ||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Lift a => Lift ([a] :: Type) Source # | |||||
IsChar c => PrintfArg [c] Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: [c] -> FieldFormatter Source # parseFormat :: [c] -> ModifierParser Source # | |||||
IsChar c => PrintfType [c] Source # | Since: base-2.1 | ||||
Defined in Text.Printf | |||||
Monoid [a] Source # | Since: base-2.1 | ||||
Semigroup [a] Source # | Since: base-4.9.0.0 | ||||
Data a => Data [a] Source # | For historical reasons, the constructor name used for Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> [a] -> c [a] Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c [a] Source # toConstr :: [a] -> Constr Source # dataTypeOf :: [a] -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c [a]) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c [a]) Source # gmapT :: (forall b. Data b => b -> b) -> [a] -> [a] Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQ :: (forall d. Data d => d -> u) -> [a] -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> [a] -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # | |||||
a ~ Char => IsString [a] Source # |
Since: base-2.1 | ||||
Defined in GHC.Internal.Data.String fromString :: String -> [a] Source # | |||||
Generic [a] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
IsList [a] Source # | Since: base-4.7.0.0 | ||||
Read a => Read [a] Source # | Since: base-2.1 | ||||
Show a => Show [a] Source # | Since: base-2.1 | ||||
Eq a => Eq [a] Source # | |||||
Ord a => Ord [a] Source # | |||||
type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep [a] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep [a] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
type Item [a] Source # | |||||
Defined in GHC.Internal.IsList type Item [a] = a |
data Multiplicity Source #
data RuntimeRep Source #
GHC maintains a property that the kind of all inhabited types
(as distinct from type constructors or type-level data) tells us
the runtime representation of values of that type. This datatype
encodes the choice of runtime value.
Note that TYPE
is parameterised by RuntimeRep
; this is precisely
what we mean by the fact that a type's kind encodes the runtime
representation.
For boxed values (that is, values that are represented by a pointer), a further distinction is made, between lifted types (that contain ⊥), and unlifted ones (that don't).
VecRep VecCount VecElem | a SIMD vector type |
TupleRep [RuntimeRep] | An unboxed tuple of the given reps |
SumRep [RuntimeRep] | An unboxed sum of the given reps |
BoxedRep Levity | boxed; represented by a pointer |
IntRep | signed, word-sized value |
Int8Rep | signed, 8-bit value |
Int16Rep | signed, 16-bit value |
Int32Rep | signed, 32-bit value |
Int64Rep | signed, 64-bit value |
WordRep | unsigned, word-sized value |
Word8Rep | unsigned, 8-bit value |
Word16Rep | unsigned, 16-bit value |
Word32Rep | unsigned, 32-bit value |
Word64Rep | unsigned, 64-bit value |
AddrRep | A pointer, but not to a Haskell value |
FloatRep | a 32-bit floating point number |
DoubleRep | a 64-bit floating point number |
Instances
Show RuntimeRep Source # | Since: base-4.11.0.0 |
Defined in GHC.Internal.Show | |
Lift (# #) Source # | Since: template-haskell-2.16.0.0 |
Lift a => Lift ((# a #) :: TYPE ('TupleRep '[LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '[LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d) => Lift ((# a | b | c | d #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d) => Lift ((# a, b, c, d #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a | b | c | d | e #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a, b, c, d, e #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a | b | c | d | e | f #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a, b, c, d, e, f #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a | b | c | d | e | f | g #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a, b, c, d, e, f, g #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source # | Since: template-haskell-2.16.0.0 |
(Kind) This is the kind of type-level symbols.
Instances
SingKind Symbol | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics
| |||||
TestCoercion SSymbol Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
TestEquality SSymbol Source # | Since: base-4.18.0.0 | ||||
Defined in GHC.Internal.TypeLits | |||||
KnownSymbol a => SingI (a :: Symbol) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics sing :: Sing a | |||||
type DemoteRep Symbol Source # | |||||
Defined in GHC.Internal.Generics | |||||
data Sing (s :: Symbol) Source # | |||||
Defined in GHC.Internal.Generics | |||||
type Compare (a :: Symbol) (b :: Symbol) Source # | |||||
Defined in GHC.Internal.Data.Type.Ord |
type UnliftedRep = 'BoxedRep 'Unlifted Source #
The runtime representation of unlifted types.
type UnliftedType = TYPE UnliftedRep Source #
The kind of boxed, unlifted values, for example Array#
or a user-defined
unlifted data type, using -XUnliftedDataTypes
.
Length of a SIMD vector type
Instances
Bounded VecCount Source # | Since: base-4.10.0.0 |
Enum VecCount Source # | Since: base-4.10.0.0 |
Defined in GHC.Internal.Enum succ :: VecCount -> VecCount Source # pred :: VecCount -> VecCount Source # toEnum :: Int -> VecCount Source # fromEnum :: VecCount -> Int Source # enumFrom :: VecCount -> [VecCount] Source # enumFromThen :: VecCount -> VecCount -> [VecCount] Source # enumFromTo :: VecCount -> VecCount -> [VecCount] Source # enumFromThenTo :: VecCount -> VecCount -> VecCount -> [VecCount] Source # | |
Show VecCount Source # | Since: base-4.11.0.0 |
Element of a SIMD vector type
Int8ElemRep | |
Int16ElemRep | |
Int32ElemRep | |
Int64ElemRep | |
Word8ElemRep | |
Word16ElemRep | |
Word32ElemRep | |
Word64ElemRep | |
FloatElemRep | |
DoubleElemRep |
Instances
Bounded VecElem Source # | Since: base-4.10.0.0 |
Enum VecElem Source # | Since: base-4.10.0.0 |
Defined in GHC.Internal.Enum succ :: VecElem -> VecElem Source # pred :: VecElem -> VecElem Source # toEnum :: Int -> VecElem Source # fromEnum :: VecElem -> Int Source # enumFrom :: VecElem -> [VecElem] Source # enumFromThen :: VecElem -> VecElem -> [VecElem] Source # enumFromTo :: VecElem -> VecElem -> [VecElem] Source # enumFromThenTo :: VecElem -> VecElem -> VecElem -> [VecElem] Source # | |
Show VecElem Source # | Since: base-4.11.0.0 |
Instances
PrintfArg Word Source # | Since: base-2.1 | ||||
Defined in Text.Printf formatArg :: Word -> FieldFormatter Source # parseFormat :: Word -> ModifierParser Source # | |||||
Bits Word Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.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 # | |||||
FiniteBits Word Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Bits finiteBitSize :: Word -> Int Source # countLeadingZeros :: Word -> Int Source # countTrailingZeros :: Word -> Int Source # | |||||
Data Word Source # | Since: base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # | |||||
Bounded Word Source # | Since: base-2.1 | ||||
Enum Word Source # | Since: base-2.1 | ||||
Storable Word Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.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 # | |||||
Ix Word Source # | Since: base-4.6.0.0 | ||||
Num Word Source # | Since: base-2.1 | ||||
Read Word Source # | Since: base-4.5.0.0 | ||||
Integral Word Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Real | |||||
Real Word Source # | Since: base-2.1 | ||||
Defined in GHC.Internal.Real toRational :: Word -> Rational Source # | |||||
Show Word Source # | Since: base-2.1 | ||||
Eq Word Source # | |||||
Ord Word Source # | |||||
Lift Word Source # | |||||
Generic1 (URec Word :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Eq1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Ord1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Show1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |||||
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec Word p) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Show (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Eq (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.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 # | |||||
data URec Word (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec Word :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep (URec Word p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics |
type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep]) Source #
The runtime representation of a zero-width tuple, represented by no bits at all
type ZeroBitType = TYPE ZeroBitRep Source #
The kind of the empty unboxed tuple type (# #)
class a ~# b => (a :: k) ~ (b :: k) infix 4 Source #
Lifted, homogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By homogeneous, the two
types a
and b
must have the same kinds.
class a ~# b => (a :: k0) ~~ (b :: k1) infix 4 Source #
Lifted, heterogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By heterogeneous, the two
types a
and b
might have different kinds. Because ~~
can
appear unexpectedly in error messages to users who do not care
about the difference between heterogeneous equality ~~
and
homogeneous equality ~
, this is printed as ~
unless
-fprint-equality-relations
is set.
In 0.7.0
, the fixity was set to infix 4
to match the fixity of :~~:
.
acosDouble# :: Double# -> Double# Source #
acosFloat# :: Float# -> Float# Source #
acoshDouble# :: Double# -> Double# Source #
acoshFloat# :: Float# -> Float# Source #
addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
attaches a C
function pointer addCFinalizerToWeak#
fptr ptr flag eptr wfptr
to a weak pointer w
as a finalizer. If
flag
is zero, fptr
will be called with one argument,
ptr
. Otherwise, it will be called with two arguments,
eptr
and ptr
. addCFinalizerToWeak#
returns
1 on success, or 0 if w
is already dead.
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#
.
addr2Int# :: Addr# -> Int# Source #
Coerce directly from address to int. Users are discouraged from using this operation as it makes little sense on platforms with tagged pointers.
addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). 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 unsafeCoerce#
, but if implemented as such
the core lint pass complains and fails to compile.
As a primop, it is opaque to core/stg, and only appears
in cmm (where the copy propagation pass will get rid of it).
Note that "a" must be a value, not a thunk! It's too late
for strictness analysis to enforce this, so you're on your
own to guarantee this. Also note that Addr#
is not a GC
pointer - up to you to guarantee that it does not become
a dangling pointer immediately after you get it.
asinDouble# :: Double# -> Double# Source #
asinFloat# :: Float# -> Float# Source #
asinhDouble# :: Double# -> Double# Source #
asinhFloat# :: Float# -> Float# Source #
atanDouble# :: Double# -> Double# Source #
atanFloat# :: Float# -> Float# Source #
atanhDouble# :: Double# -> Double# Source #
atanhFloat# :: Float# -> Float# Source #
atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
Compare and swap on a word-sized memory location.
Use as: s -> atomicCasAddrAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) Source #
Compare and swap on a 16 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr16# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) Source #
Compare and swap on a 32 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr32# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) Source #
Compare and swap on a 64 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr64# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) Source #
Compare and swap on a 8 bit-sized and aligned memory location.
Use as: s -> atomicCasWordAddr8# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) Source #
Compare and swap on a word-sized and aligned memory location.
Use as: s -> atomicCasWordAddr# location expected desired s
This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).
Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #
The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.
Warning: this can fail with an unchecked exception.
atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.
Warning: this can fail with an unchecked exception.
atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) Source #
Modify the contents of a MutVar#
, returning the previous
contents x :: a
and the result of applying the given function to the
previous contents f x :: c
.
The data
type c
(not a newtype
!) must be a record whose first field
is of lifted type a :: Type
and is not unpacked. For example, product
types c ~ Solo a
or c ~ (a, b)
work well. If the record type is both
monomorphic and strict in its first field, it's recommended to mark the
latter {-# NOUNPACK #-}
explicitly.
Under the hood atomicModifyMutVar2#
atomically replaces a pointer to an
old x :: a
with a pointer to a selector thunk fst r
, where
fst
is a selector for the first field of the record and r
is a
function application thunk r = f x
.
atomicModifyIORef2Native
from atomic-modify-general
package makes an
effort to reflect restrictions on c
faithfully, providing a
well-typed high-level wrapper.
atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) Source #
Modify the contents of a MutVar#
, returning the previous
contents and the result of applying the given function to the
previous contents.
atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array and an offset in machine words, read an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #) Source #
Given an address, read a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) Source #
Atomically exchange the value of a MutVar#
.
atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Given an array and an offset in machine words, write an element. The index is assumed to be in bounds. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d Source #
Given an address, write a machine word. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
bitReverse# :: Word# -> Word# Source #
Reverse the order of the bits in a word.
bitReverse16# :: Word# -> Word# Source #
Reverse the order of the bits in a 16-bit word.
bitReverse32# :: Word# -> Word# Source #
Reverse the order of the bits in a 32-bit word.
bitReverse64# :: Word64# -> Word64# Source #
Reverse the order of the bits in a 64-bit word.
bitReverse8# :: Word# -> Word# Source #
Reverse the order of the bits in a 8-bit word.
broadcastDoubleX2# :: Double# -> DoubleX2# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX4# :: Double# -> DoubleX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastDoubleX8# :: Double# -> DoubleX8# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX16# :: Float# -> FloatX16# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX4# :: Float# -> FloatX4# Source #
Broadcast a scalar to all elements of a vector.
broadcastFloatX8# :: Float# -> FloatX8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X16# :: Int16# -> Int16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X32# :: Int16# -> Int16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt16X8# :: Int16# -> Int16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X16# :: Int32# -> Int32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X4# :: Int32# -> Int32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt32X8# :: Int32# -> Int32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X2# :: Int64# -> Int64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X4# :: Int64# -> Int64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt64X8# :: Int64# -> Int64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X16# :: Int8# -> Int8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X32# :: Int8# -> Int8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastInt8X64# :: Int8# -> Int8X64# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X16# :: Word16# -> Word16X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X32# :: Word16# -> Word16X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord16X8# :: Word16# -> Word16X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X16# :: Word32# -> Word32X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X4# :: Word32# -> Word32X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord32X8# :: Word32# -> Word32X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X2# :: Word64# -> Word64X2# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X4# :: Word64# -> Word64X4# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord64X8# :: Word64# -> Word64X8# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X16# :: Word8# -> Word8X16# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X32# :: Word8# -> Word8X32# Source #
Broadcast a scalar to all elements of a vector.
broadcastWord8X64# :: Word8# -> Word8X64# Source #
Broadcast a scalar to all elements of a vector.
byteArrayContents# :: ByteArray# -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
byteSwap16# :: Word# -> Word# Source #
Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.
byteSwap32# :: Word# -> Word# Source #
Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.
byteSwap64# :: Word64# -> Word64# Source #
Swap bytes in a 64 bits of a word.
casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Given an array, an offset, the expected old value, and
the new value, perform an atomic compare and swap (i.e. write the new
value if the current value and the old value are the same pointer).
Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns
the element at the offset after the operation completes. This means that
on a success the new value is returned, and on a failure the actual old
value (not the expected one) is returned. Implies a full memory barrier.
The use of a pointer equality on a boxed value makes this function harder
to use correctly than casIntArray#
. All of the difficulties
of using reallyUnsafePtrEquality#
correctly apply to
casArray#
as well.
Warning: this can fail with an unchecked exception.
casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) Source #
Given an array, an offset in 16 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) Source #
Given an array, an offset in 32 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) Source #
Given an array, an offset in 64 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) Source #
Given an array, an offset in bytes, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, an offset in machine words, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Compare-and-swap: perform a pointer equality test between
the first value passed to this function and the value
stored inside the MutVar#
. If the pointers are equal,
replace the stored value with the second value passed to this
function, otherwise do nothing.
Returns the final value stored inside the MutVar#
.
The Int#
indicates whether a swap took place,
with 1#
meaning that we didn't swap, and 0#
that we did.
Implies a full memory barrier.
Because the comparison is done on the level of pointers,
all of the difficulties of using
reallyUnsafePtrEquality#
correctly apply to
casMutVar#
as well.
casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #
Unsafe, machine-level atomic compare and swap on an element within an array.
See the documentation of casArray#
.
Warning: this can fail with an unchecked exception.
catch# :: forall {k :: Levity} a (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates catch#
k handler sk s
, invoking handler
on any exceptions
thrown.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
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.
cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
closureSize# :: a -> Int# Source #
returns the size of the given closure in
machine words. closureSize#
closure
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.
When used in conversions involving a newtype wrapper, make sure the newtype constructor is in scope.
This function is representation-polymorphic, but the
RuntimeRep
type argument is marked as Inferred
, meaning
that it is not available for visible type application. This means
the typechecker will accept
.coerce
@Int
@Age 42
Examples
>>>
newtype TTL = TTL Int deriving (Eq, Ord, Show)
>>>
newtype Age = Age Int deriving (Eq, Ord, Show)
>>>
coerce (Age 42) :: TTL
TTL 42>>>
coerce (+ (1 :: Int)) (Age 42) :: TTL
TTL 43>>>
coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
[TTL 43,TTL 25]
compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #
Recursively add a closure and its transitive closure to a
Compact#
(a CNF), evaluating any unevaluated components
at the same time. Note: compactAdd#
is not thread-safe, so
only one thread may call compactAdd#
with a particular
Compact#
at any given time. The primop does not
enforce any mutual exclusion; the caller is expected to
arrange this.
compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #
Like compactAdd#
, but retains sharing and cycles
during compaction.
compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #
Attempt to allocate a compact block with the capacity (in
bytes) given by the first argument. The Addr#
is a pointer
to previous compact block of the CNF or nullAddr#
to create a
new CNF with a single compact block.
The resulting block is not known to the GC until
compactFixupPointers#
is called on it, and care must be taken
so that the address does not escape or memory will be leaked.
compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
Returns 1# if the object is contained in the CNF, 0# otherwise.
compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
Returns 1# if the object is in any CNF at all, 0# otherwise.
compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) Source #
Given the pointer to the first block of a CNF and the address of the root object in the old address space, fix up the internal pointers inside the CNF to account for a different position in memory than when it was serialized. This method must be called exactly once after importing a serialized CNF. It returns the new CNF and the new adjusted root address.
compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
Returns the address and the utilized size (in bytes) of the first compact block of a CNF.
compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
Given a CNF and the address of one its compact blocks, returns the
next compact block and its utilized size, or nullAddr#
if the
argument was the last compact block in the CNF.
compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #) Source #
Create a new CNF with a single compact block. The argument is the capacity of the compact block (in bytes, not words). The capacity is rounded up to a multiple of the allocator block size and is capped to one mega block.
compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld Source #
Set the new allocation size of the CNF. This value (in bytes) determines the capacity of each compact block in the CNF. It does not retroactively affect existing compact blocks in the CNF.
compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) Source #
Return the total capacity (in bytes) of all the compact blocks in the CNF.
compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #
compares
compareByteArrays#
src1 src1_ofs src2 src2_ofs nn
bytes starting at offset src1_ofs
in the first
ByteArray#
src1
to the range of n
bytes
(i.e. same length) starting at offset src2_ofs
of the second
ByteArray#
src2
. Both arrays must fully contain the
specified ranges, but this is not checked. Returns an Int#
less than, equal to, or greater than zero if the range is found,
respectively, to be byte-wise lexicographically less than, to
match, or be greater than the second range.
Since: ghc-prim-0.5.2.0
control0# :: PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #) Source #
See GHC.Prim.
Warning: this can fail with an unchecked exception.
copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddr#
src dest lenlen
bytes
from src
to dest
. These two memory ranges are allowed to overlap.
Analogous to the standard C function memmove
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #
copies copyAddrToAddrNonOverlapping#
src dest lenlen
bytes
from src
to dest
. As the name suggests, these two memory ranges
must not overlap, although this pre-condition is not checked.
Analogous to the standard C function memcpy
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Copy a memory range starting at the Addr# to the specified range in the MutableByteArray#. The memory region at Addr# and the ByteArray# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range
starting at offset copyByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
ByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain
the specified ranges, but this is not checked. The two arrays must
not be the same array in different states, but this is not checked
either.
Warning: this can fail with an unchecked exception.
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the ByteArray# to the memory range starting at the Addr#. The ByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the ByteArray# (e.g. if the ByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. In the case where the source and destination are the same array the source and destination regions may overlap.
Warning: this can fail with an unchecked exception.
copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the
range starting at offset copyMutableByteArray#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from the
MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are
allowed to overlap, although this is only possible when the same
array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
copies the range starting at offset copyMutableByteArrayNonOverlapping#
src src_ofs dst dst_ofs lensrc_ofs
of length len
from
the MutableByteArray#
src
to the MutableByteArray#
dst
starting at offset dst_ofs
. Both arrays must fully contain the
specified ranges, but this is not checked. The regions are not
allowed to overlap, but this is also not checked.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d Source #
Copy a range of the MutableByteArray# to the memory range starting at the Addr#. The MutableByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.
Warning: this can fail with an unchecked exception.
copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.
Warning: this can fail with an unchecked exception.
copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #
Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.
Warning: this can fail with an unchecked exception.
cosDouble# :: Double# -> Double# Source #
coshDouble# :: Double# -> Double# Source #
coshFloat# :: Float# -> Float# Source #
deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) Source #
deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) Source #
decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) Source #
Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.
decodeDouble_Int64# :: Double# -> (# Int64#, Int# #) Source #
Decode Double#
into mantissa and base-2 exponent.
decodeFloat_Int# :: Float# -> (# Int#, Int# #) Source #
Convert to integers.
First Int#
in result is the mantissa; second is the exponent.
double2Float# :: Double# -> Float# Source #
double2Int# :: Double# -> Int# Source #
eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int# Source #
expDouble# :: Double# -> Double# Source #
expm1Double# :: Double# -> Double# Source #
expm1Float# :: Float# -> Float# Source #
fabsDouble# :: Double# -> Double# Source #
fabsFloat# :: Float# -> Float# Source #
fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #
Given an array, and offset in machine words, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #
Given an address, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.
Warning: this can fail with an unchecked exception.
finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) Source #
Finalize a weak pointer. The return value is an unboxed tuple
containing the new state of the world and an "unboxed Maybe",
represented by an Int#
and a (possibly invalid) finalization
action. An Int#
of 1
indicates that the finalizer is valid. The
return value b
from the finalizer should be ignored.
float2Double# :: Float# -> Double# Source #
float2Int# :: Float# -> Int# Source #
fmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
fmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-add operation x*y+z
. See GHC.Prim.
fmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused multiply-subtract operation x*y-z
. See GHC.Prim.
fnmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fnmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-add operation -x*y+z
. See GHC.Prim.
fnmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
fnmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #
Fused negate-multiply-subtract operation -x*y-z
. See GHC.Prim.
fork# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #
forkOn# :: Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #
freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
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).
getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkMutableByteArray#
and resizeMutableByteArray#
.
Since: ghc-prim-0.5.0.0
getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) Source #
Return the number of elements in the array, correctly accounting for
the effect of shrinkSmallMutableArray#
and resizeSmallMutableArray#
.
Since: ghc-prim-0.6.1
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address from immutable array; offset in machine words.
indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source #
Read a machine address from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #) Source #
Read from the specified index of an immutable array. The result is packaged into an unboxed unary tuple; the result itself is not yet evaluated. Pattern matching on the tuple forces the indexing of the array to happen but does not evaluate the element itself. Evaluating the thunk prevents additional thunks from building up on the heap. Avoiding these thunks, in turn, reduces references to the argument array, allowing it to be garbage collected more promptly.
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character from immutable array; offset in bytes.
indexCharOffAddr# :: Addr# -> Int# -> Char# Source #
Read an 8-bit character from immutable address; offset in bytes.
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable array; offset in 8-byte words.
indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# 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.
indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in scalar elements.
indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in scalar elements.
indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array.
indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array.
indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array.
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable array; offset in 4-byte words.
indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# 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.
indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexFloatOffAddr# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in scalar elements.
indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in scalar elements.
indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array.
indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array.
indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array.
indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable array; offset in 2-byte words.
indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# 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.
indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt16OffAddr# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in scalar elements.
indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in scalar elements.
indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array.
indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array.
indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array.
indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable array; offset in 4-byte words.
indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# 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.
indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt32OffAddr# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in scalar elements.
indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in scalar elements.
indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array.
indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array.
indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array.
indexInt64Array# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable array; offset in 8-byte words.
indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# 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.
indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt64OffAddr# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in scalar elements.
indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in scalar elements.
indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array.
indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array.
indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array.
indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #
Read an 8-bit signed integer from immutable array; offset in bytes.
indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# 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.
indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexInt8OffAddr# :: Addr# -> Int# -> Int8# Source #
Read an 8-bit signed integer from immutable address; offset in bytes.
indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in scalar elements.
indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in scalar elements.
indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array.
indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array.
indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array.
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer from immutable array; offset in machine words.
indexIntOffAddr# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #) Source #
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable array; offset in machine words.
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character from immutable array; offset in 4-byte words.
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable array; offset in 2-byte words.
indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# 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.
indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord16OffAddr# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in scalar elements.
indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in scalar elements.
indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array.
indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in bytes.
indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array.
indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in bytes.
indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array.
indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable array; offset in 4-byte words.
indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# 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.
indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord32OffAddr# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in scalar elements.
indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in scalar elements.
indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array.
indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in bytes.
indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array.
indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array.
indexWord64Array# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable array; offset in 8-byte words.
indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# 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.
indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord64OffAddr# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in scalar elements.
indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in scalar elements.
indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array.
indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array.
indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array.
indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #
Read a machine address from immutable array; offset in bytes.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #
Read an 8-bit character from immutable array; offset in bytes.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable array; offset in bytes.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable array; offset in bytes.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #
Read a word-sized integer from immutable array; offset in bytes.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable array; offset in bytes.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable array; offset in bytes.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #
Read a 32-bit character from immutable array; offset in bytes.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable array; offset in bytes.
indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# 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.
indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
indexWord8OffAddr# :: Addr# -> Int# -> Word8# Source #
Read an 8-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# Source #
Read a machine address from immutable address; offset in bytes.
indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char# Source #
Read an 8-bit character from immutable address; offset in bytes.
indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# Source #
Read a double-precision floating-point value from immutable address; offset in bytes.
indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# Source #
Read a single-precision floating-point value from immutable address; offset in bytes.
indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int# Source #
Read a word-sized integer from immutable address; offset in bytes.
indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# Source #
Read a 16-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# Source #
Read a 32-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# Source #
Read a 64-bit signed integer from immutable address; offset in bytes.
indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a Source #
Read a StablePtr#
value from immutable address; offset in bytes.
indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# Source #
Read a 32-bit character from immutable address; offset in bytes.
indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# Source #
Read a 16-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# Source #
Read a 32-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# Source #
Read a 64-bit unsigned integer from immutable address; offset in bytes.
indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in scalar elements.
indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in scalar elements.
indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array.
indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array.
indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array.
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable array; offset in machine words.
indexWordOffAddr# :: Addr# -> Int# -> Word# Source #
Read a word-sized unsigned integer from immutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# 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.
insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# 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.
insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# 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.
insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# Source #
Insert a scalar at the given position in a vector.
insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# Source #
Insert a scalar at the given position in a vector.
insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# Source #
Insert a scalar at the given position in a vector.
insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# Source #
Insert a scalar at the given position in a vector.
insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# Source #
Insert a scalar at the given position in a vector.
insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# Source #
Insert a scalar at the given position in a vector.
insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# Source #
Insert a scalar at the given position in a vector.
insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# Source #
Insert a scalar at the given position in a vector.
insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# Source #
Insert a scalar at the given position in a vector.
insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# Source #
Insert a scalar at the given position in a vector.
insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# Source #
Insert a scalar at the given position in a vector.
insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# Source #
Insert a scalar at the given position in a vector.
insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16# Source #
Insert a scalar at the given position in a vector.
insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32# Source #
Insert a scalar at the given position in a vector.
insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8# Source #
Insert a scalar at the given position in a vector.
insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# Source #
Insert a scalar at the given position in a vector.
insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# Source #
Insert a scalar at the given position in a vector.
insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# Source #
Insert a scalar at the given position in a vector.
insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# Source #
Insert a scalar at the given position in a vector.
insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# Source #
Insert a scalar at the given position in a vector.
insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# Source #
Insert a scalar at the given position in a vector.
insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16# Source #
Insert a scalar at the given position in a vector.
insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32# Source #
Insert a scalar at the given position in a vector.
insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64# Source #
Insert a scalar at the given position in a vector.
int16ToInt# :: Int16# -> Int# Source #
int16ToWord16# :: Int16# -> Word16# Source #
int2Addr# :: Int# -> Addr# Source #
Coerce directly from int to address. Users are discouraged from using this operation as it makes little sense on platforms with tagged pointers.
int2Double# :: Int# -> Double# Source #
Convert an Int#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Double#
1# == 1.0##
int2Float# :: Int# -> Float# Source #
Convert an Int#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
int2Float#
1# == 1.0#
int32ToInt# :: Int32# -> Int# Source #
int32ToWord32# :: Int32# -> Word32# Source #
int64ToInt# :: Int64# -> Int# Source #
int64ToWord64# :: Int64# -> Word64# Source #
int8ToInt# :: Int8# -> Int# Source #
int8ToWord8# :: Int8# -> Word8# Source #
intToInt16# :: Int# -> Int16# Source #
intToInt32# :: Int# -> Int32# Source #
intToInt64# :: Int# -> Int64# Source #
intToInt8# :: Int# -> Int8# Source #
isByteArrayPinned# :: ByteArray# -> Int# Source #
Determine whether a ByteArray#
is guaranteed not to move.
isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #) Source #
Return 1 if MVar#
is empty; 0 otherwise.
isMutableByteArrayPinned# :: MutableByteArray# d -> Int# Source #
Determine whether a MutableByteArray#
is guaranteed not to move
during GC.
keepAlive# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d b. a -> State# d -> (State# d -> b) -> b Source #
keeps the value keepAlive#
x s kx
alive during the execution
of the computation k
.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld Source #
Set the label of the given thread. The ByteArray#
should contain
a UTF-8-encoded string.
leftSection :: forall {n :: Multiplicity} a b. (a %n -> b) -> a %n -> b Source #
listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #) Source #
Returns an array of the threads started by the program. Note that this threads which have finished execution may or may not be present in this list, depending upon whether they have been collected by the garbage collector.
Since: ghc-prim-0.10
log1pDouble# :: Double# -> Double# Source #
log1pFloat# :: Float# -> Float# Source #
logDouble# :: Double# -> Double# Source #
makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #) Source #
makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) Source #
maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates maskAsyncExceptions#
k sk s
such that asynchronous
exceptions are deferred until after evaluation has finished.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates maskUninterruptible#
k sk s
such that asynchronous
exceptions are deferred until after evaluation has finished.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
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.
mkApUpd0# :: BCO -> (# a #) Source #
Wrap a BCO in a AP_UPD
thunk which will be updated with the value of
the BCO when evaluated.
mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #
creates a weak reference to value mkWeak#
k v finalizer sk
,
with an associated reference to some value v
. If k
is still
alive then v
can be retrieved using deRefWeak#
. Note that
the type of k
must be represented by a pointer (i.e. of kind
TYPE
'LiftedRep
or TYPE
'UnliftedRep
@).
mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) 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.
mutableByteArrayContents# :: MutableByteArray# d -> Addr# Source #
Intended for use with pinned arrays; otherwise very unsafe!
narrow16Int# :: Int# -> Int# Source #
narrow16Word# :: Word# -> Word# Source #
narrow32Int# :: Int# -> Int# Source #
narrow32Word# :: Word# -> Word# Source #
narrow8Int# :: Int# -> Int# Source #
narrow8Word# :: Word# -> Word# Source #
negateDouble# :: Double# -> Double# Source #
negateDoubleX2# :: DoubleX2# -> DoubleX2# Source #
Negate element-wise.
negateDoubleX4# :: DoubleX4# -> DoubleX4# Source #
Negate element-wise.
negateDoubleX8# :: DoubleX8# -> DoubleX8# Source #
Negate element-wise.
negateFloat# :: Float# -> Float# Source #
negateFloatX16# :: FloatX16# -> FloatX16# Source #
Negate element-wise.
negateFloatX4# :: FloatX4# -> FloatX4# Source #
Negate element-wise.
negateFloatX8# :: FloatX8# -> FloatX8# Source #
Negate element-wise.
negateInt# :: Int# -> Int# Source #
Unary negation.
Since the negative Int#
range extends one further than the
positive range, negateInt#
of the most negative number is an
identity operation. This way, negateInt#
is always its own inverse.
negateInt16# :: Int16# -> Int16# Source #
negateInt16X16# :: Int16X16# -> Int16X16# Source #
Negate element-wise.
negateInt16X32# :: Int16X32# -> Int16X32# Source #
Negate element-wise.
negateInt16X8# :: Int16X8# -> Int16X8# Source #
Negate element-wise.
negateInt32# :: Int32# -> Int32# Source #
negateInt32X16# :: Int32X16# -> Int32X16# Source #
Negate element-wise.
negateInt32X4# :: Int32X4# -> Int32X4# Source #
Negate element-wise.
negateInt32X8# :: Int32X8# -> Int32X8# Source #
Negate element-wise.
negateInt64# :: Int64# -> Int64# Source #
negateInt64X2# :: Int64X2# -> Int64X2# Source #
Negate element-wise.
negateInt64X4# :: Int64X4# -> Int64X4# Source #
Negate element-wise.
negateInt64X8# :: Int64X8# -> Int64X8# Source #
Negate element-wise.
negateInt8# :: Int8# -> Int8# Source #
negateInt8X16# :: Int8X16# -> Int8X16# Source #
Negate element-wise.
negateInt8X32# :: Int8X32# -> Int8X32# Source #
Negate element-wise.
negateInt8X64# :: Int8X64# -> Int8X64# Source #
Negate element-wise.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newPinnedByteArray#
but allow specifying an arbitrary
alignment, which must be a power of two.
Warning: this can fail with an unchecked exception.
newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) Source #
creates a new bytecode object. The
resulting object encodes a function of the given arity with the instructions
encoded in newBCO#
instrs lits ptrs arity bitmapinstrs
, and a static reference table usage bitmap given by
bitmap
.
newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Create a new mutable byte array of specified size (in bytes), in the specified state thread. The size of the memory underlying the array will be rounded up to the platform's word size.
newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #) Source #
Create new IOPort#
; initially empty.
newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #) Source #
Create new MVar#
; initially empty.
newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) Source #
Create MutVar#
with specified initial value in specified state thread.
newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Like newByteArray#
but GC guarantees not to move it.
newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #) Source #
See GHC.Prim.
newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.
newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #) Source #
Create a new TVar#
holding a specified initial value.
noDuplicate# :: State# d -> State# d Source #
notWord16# :: Word16# -> Word16# Source #
notWord32# :: Word32# -> Word32# Source #
numSparks# :: State# d -> (# State# d, Int# #) Source #
Returns the number of sparks in the local spark pool.
packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# 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.
packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# 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.
packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4# 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.
packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32# Source #
Pack the elements of an unboxed tuple into a vector.
packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X2# :: (# Int64#, Int64# #) -> Int64X2# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4# Source #
Pack the elements of an unboxed tuple into a vector.
packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32# Source #
Pack the elements of an unboxed tuple into a vector.
packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32# Source #
Pack the elements of an unboxed tuple into a vector.
packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4# Source #
Pack the elements of an unboxed tuple into a vector.
packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X2# :: (# Word64#, Word64# #) -> Word64X2# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4# Source #
Pack the elements of an unboxed tuple into a vector.
packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32# Source #
Pack the elements of an unboxed tuple into a vector.
packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64# Source #
Pack the elements of an unboxed tuple into a vector.
Create a new spark evaluating the given argument. The return value should always be 1. Users are encouraged to use spark# instead.
pdep# :: Word# -> Word# -> Word# Source #
Deposit bits to a word at locations specified by a mask, aka parallel bit deposit.
Software emulation:
pdep :: Word -> Word -> Word pdep src mask = go 0 src mask where go :: Word -> Word -> Word -> Word go result _ 0 = result go result src mask = go newResult newSrc newMask where maskCtz = countTrailingZeros mask newResult = if testBit src 0 then setBit result maskCtz else result newSrc = src `shiftR` 1 newMask = clearBit mask maskCtz
Since: ghc-prim-0.5.2.0
pdep16# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep32# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep64# :: Word64# -> Word64# -> Word64# Source #
Deposit bits to a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pdep8# :: Word# -> Word# -> Word# Source #
Deposit bits to lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext# :: Word# -> Word# -> Word# Source #
Extract bits from a word at locations specified by a mask, aka parallel bit extract.
Software emulation:
pext :: Word -> Word -> Word pext src mask = loop 0 0 0 where loop i count result | i >= finiteBitSize (0 :: Word) = result | testBit mask i = loop (i + 1) (count + 1) (if testBit src i then setBit result count else result) | otherwise = loop (i + 1) count result
Since: ghc-prim-0.5.2.0
pext16# :: Word# -> Word# -> Word# Source #
Extract bits from lower 16 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext32# :: Word# -> Word# -> Word# Source #
Extract bits from lower 32 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext64# :: Word64# -> Word64# -> Word64# Source #
Extract bits from a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
pext8# :: Word# -> Word# -> Word# Source #
Extract bits from lower 8 bits of a word at locations specified by a mask.
Since: ghc-prim-0.5.2.0
plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #
Add two vectors element-wise.
plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #
Add two vectors element-wise.
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#
.
plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #
Add two vectors element-wise.
prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchValue0# :: a -> State# d -> State# d Source #
prefetchValue1# :: a -> State# d -> State# d Source #
prefetchValue2# :: a -> State# d -> State# d Source #
prefetchValue3# :: a -> State# d -> State# d Source #
prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
See GHC.Prim.
proxy# :: forall {k} (a :: k). Proxy# a Source #
Witness for an unboxed Proxy#
value, which has no runtime
representation.
putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d Source #
If MVar#
is full, block until it becomes empty.
Then store value arg as its new contents.
quotInt# :: Int# -> Int# -> Int# Source #
Rounds towards zero. The behavior is undefined if the second argument is zero.
quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) Source #
Takes high word of dividend, then low word of dividend, then divisor. Requires that high word < divisor.
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.
raiseDivZero# :: (# #) -> b Source #
raiseIO# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> State# RealWorld -> (# State# RealWorld, b #) Source #
raiseOverflow# :: (# #) -> b Source #
raiseUnderflow# :: (# #) -> b Source #
readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #) Source #
readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) Source #
Read an 8-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #
If MVar#
is empty, block until it becomes full.
Then read its contents without modifying the MVar, without possibility
of intervention from other threads.
readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of MutVar#
. Result is not yet evaluated.
readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #
Read from specified index of mutable array. Result is not yet evaluated.
Warning: this can fail with an unchecked exception.
readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of TVar#
inside an STM transaction,
i.e. within a call to atomically#
.
Does not force evaluation of the result.
readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #
Read contents of TVar#
outside an STM transaction.
Does not force evaluation of the result.
readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Read a vector from specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) Source #
Read an 8-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #
Read a machine address from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read an 8-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #
Read a double-precision floating-point value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #
Read a single-precision floating-point value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #
Read a word-sized integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #
Read a 16-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #
Read a 32-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #
Read a 64-bit signed integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #
Read a StablePtr#
value from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #
Read a 32-bit character from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #
Read a 16-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #
Read a 32-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #
Read a 64-bit unsigned integer from mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Read a vector from specified index of mutable array.
Warning: this can fail with an unchecked exception.
readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in bytes.
Warning: this can fail with an unchecked exception.
readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #
Read a word-sized unsigned integer from mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
realWorld# :: State# RealWorld Source #
The token used in the implementation of the IO monad as a state monad.
It does not pass any information at runtime.
See also runRW#
.
reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int# Source #
Returns 1#
if the given pointers are equal and 0#
otherwise.
remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# 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
remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# 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
remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# 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
remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# 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
remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# 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
remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# 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
remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# 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
remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# 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
remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# 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
remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# 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
remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# 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
remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #
Satisfies (
. quot#
x y) times#
y plus#
(rem#
x y) == x
resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Resize mutable byte array to new specified size (in bytes), shrinking or growing it.
The returned MutableByteArray#
is either the original
MutableByteArray#
resized in-place or, if not possible, a newly
allocated (unpinned) MutableByteArray#
(with the original content
copied over).
To avoid undefined behaviour, the original MutableByteArray#
shall
not be accessed anymore after a resizeMutableByteArray#
has been
performed. Moreover, no reference to the old one should be kept in order
to allow garbage collection of the original MutableByteArray#
in
case a new MutableByteArray#
had to be allocated.
Since: ghc-prim-0.4.0.0
retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #) Source #
rightSection :: forall {n :: Multiplicity} {o :: Multiplicity} a b c. (a %n -> b %o -> c) -> b %o -> a %n -> c Source #
seq :: a -> b -> b infixr 0 Source #
The value of
is bottom if seq
a ba
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression
does
not guarantee that seq
a ba
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld Source #
sets all of the bytes in
setAddrRange#
dest len c[dest, dest+len)
to the value c
.
Analogous to the standard C function memset
, but with a different
argument order.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.11.0
setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d Source #
sets the byte range setByteArray#
ba off len c[off, off+len)
of
the MutableByteArray#
to the byte c
.
Warning: this can fail with an unchecked exception.
setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld Source #
Sets the allocation counter for the current thread to the given value.
shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
Shrink mutable byte array to new specified size (in bytes), in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofMutableByteArray#
.
Assuming the non-profiling RTS, this primitive compiles to an O(1) operation in C--, modifying the array in-place. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.4.0.0
shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d Source #
Shrink mutable array to new specified size, in
the specified state thread. The new size argument must be less than or
equal to the current size as reported by getSizeofSmallMutableArray#
.
Assuming the non-profiling RTS, for the copying garbage collector (default) this primitive compiles to an O(1) operation in C--, modifying the array in-place. For the non-moving garbage collector, however, the time is proportional to the number of elements shrinked out. Backends bypassing C-- representation (such as JavaScript) might behave differently.
Warning: this can fail with an unchecked exception.
Since: ghc-prim-0.6.1
sinDouble# :: Double# -> Double# Source #
sinhDouble# :: Double# -> Double# Source #
sinhFloat# :: Float# -> Float# Source #
sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# Source #
Return the number of elements in the array.
sizeofByteArray# :: ByteArray# -> Int# Source #
Return the size of the array in bytes.
sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# Source #
Return the number of elements in the array.
sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #
Deprecated: Use getSizeofMutableByteArray#
instead
Return the size of the array in bytes. Deprecated, it is
unsafe in the presence of shrinkMutableByteArray#
and resizeMutableByteArray#
operations on the same mutable byte
array.
sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# Source #
Return the number of elements in the array.
sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# Source #
Deprecated: Use getSizeofSmallMutableArray#
instead
Return the number of elements in the array. Deprecated, it is
unsafe in the presence of shrinkSmallMutableArray#
and resizeSmallMutableArray#
operations on the same small mutable array.
sqrtDouble# :: Double# -> Double# Source #
sqrtFloat# :: Float# -> Float# Source #
stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int# Source #
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.
tagToEnum# :: Int# -> a Source #
takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #
If MVar#
is empty, block until it becomes full.
Then remove and return its contents, and set it empty.
tanDouble# :: Double# -> Double# Source #
tanhDouble# :: Double# -> Double# Source #
tanhFloat# :: Float# -> Float# Source #
thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.
Warning: this can fail with an unchecked exception.
threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #) Source #
Get the label of the given thread.
Morally of type ThreadId# -> IO (Maybe ByteArray#)
, with a 1#
tag
denoting Just
.
Since: ghc-prim-0.10
threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) Source #
Get the status of the given thread. Result is
(ThreadStatus, Capability, Locked)
where
ThreadStatus
is one of the status constants defined in
rts/Constants.h
, Capability
is the number of
the capability which currently owns the thread, and
Locked
is a boolean indicating whether the
thread is bound to that capability.
Since: ghc-prim-0.9
timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) Source #
Return a triple (isHighNeeded,high,low) where high and low are respectively the high and low bits of the double-word result. isHighNeeded is a cheap way to test if the high word is a sign-extension of the low word (isHighNeeded = 0#) or not (isHighNeeded = 1#).
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.
traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d Source #
Emits an event via the RTS tracing framework. The contents
of the event is the binary object passed as the first argument with
the given length passed as the second argument. The event will be
emitted to the .eventlog
file.
traceEvent# :: Addr# -> State# d -> State# d Source #
Emits an event via the RTS tracing framework. The contents
of the event is the zero-terminated byte string passed as the first
argument. The event will be emitted either to the .eventlog
file,
or to stderr, depending on the runtime RTS flags.
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.
tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #) Source #
If MVar#
is full, immediately return with integer 0.
Otherwise, store value arg as 'MVar#''s new contents, and return with integer 1.
tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) Source #
tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) 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.
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.
unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
evaluates unmaskAsyncUninterruptible#
k sk s
such that asynchronous
exceptions are unmasked.
Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.
unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #) Source #
copies the closure and pointers in the
payload of the given closure into two new arrays, and returns a pointer to
the first word of the closure's info table, a non-pointer array for the raw
bytes of the closure, and a pointer array for the pointers in the payload. unpackClosure#
closure
unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #) 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. #
unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, 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. #
unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #) 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. #
unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #
Unpack the elements of a vector into an unboxed tuple. #
unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) Source #
Make a mutable array immutable, without copying.
unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Source #
Make a mutable byte array immutable, without copying.
unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) Source #
Make a mutable array immutable, without copying.
unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) Source #
Make an immutable array mutable, without copying.
unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #) Source #
Make an immutable byte array mutable, without copying.
Since: ghc-prim-0.12.0.0
unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #
Make an immutable array mutable, without copying.
Deprecated: Use an unboxed unit tuple instead
This is an alias for the unboxed unit tuple constructor.
In earlier versions of GHC, void#
was a value
of the primitive type Void#
, which is now defined to be (# #)
.
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.
word16ToInt16# :: Word16# -> Int16# Source #
word16ToWord# :: Word16# -> Word# Source #
word2Double# :: Word# -> Double# Source #
Convert an Word#
to the corresponding Double#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Double#
1## == 1.0##
word2Float# :: Word# -> Float# Source #
Convert an Word#
to the corresponding Float#
with the same
integral value (up to truncation due to floating-point precision). e.g.
word2Float#
1## == 1.0#
word32ToInt32# :: Word32# -> Int32# Source #
word32ToWord# :: Word32# -> Word# Source #
word64ToInt64# :: Word64# -> Int64# Source #
word64ToWord# :: Word64# -> Word# Source #
word8ToInt8# :: Word8# -> Int8# Source #
word8ToWord# :: Word8# -> Word# Source #
wordToWord16# :: Word# -> Word16# Source #
wordToWord32# :: Word# -> Word32# Source #
wordToWord64# :: Word# -> Word64# Source #
wordToWord8# :: Word# -> Word8# Source #
writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #) Source #
If IOPort#
is full, immediately return with integer 0,
throwing an IOPortException
.
Otherwise, store value arg as 'IOPort#''s new contents,
and return with integer 1.
writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d Source #
Write an 8-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d Source #
Write contents of MutVar#
.
writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d Source #
Write to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d Source #
Write contents of TVar#
.
writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable array; offset in 2-byte words.
Warning: this can fail with an unchecked exception.
writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable address; offset in 2-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable array; offset in 4-byte words.
Warning: this can fail with an unchecked exception.
writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable address; offset in 4-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable array; offset in 8-byte words.
Warning: this can fail with an unchecked exception.
writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable address; offset in 8-byte words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable array; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array of scalars; offset is in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d Source #
Write an 8-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #
Write a machine address to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write an 8-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #
Write a double-precision floating-point value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #
Write a single-precision floating-point value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #
Write a word-sized integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #
Write a 16-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #
Write a 32-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #
Write a 64-bit signed integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #
Write a StablePtr#
value to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #
Write a 32-bit character to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #
Write a 16-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #
Write a 32-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #
Write a 64-bit unsigned integer to mutable address; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this can fail with an unchecked exception.
writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this can fail with an unchecked exception.
writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this can fail with an unchecked exception.
writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable array; offset in machine words.
Warning: this can fail with an unchecked exception.
writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #
Write a word-sized unsigned integer to mutable address; offset in machine words.
On some platforms, the access may fail
for an insufficiently aligned Addr#
.
Warning: this can fail with an unchecked exception.
data Addr# :: TYPE 'AddrRep Source #
An arbitrary machine address assumed to point outside the garbage-collected heap.
data ByteArray# :: UnliftedType Source #
A boxed, unlifted datatype representing a region of raw memory in the garbage-collected heap, which is not scanned for pointers during garbage collection.
It is created by freezing a MutableByteArray#
with unsafeFreezeByteArray#
.
Freezing is essentially a no-op, as MutableByteArray#
and ByteArray#
share the same heap structure under the hood.
The immutable and mutable variants are commonly used for scenarios requiring high-performance data structures,
like Text
, Primitive Vector
, Unboxed Array
, and ShortByteString
.
Another application of fundamental importance is Integer
, which is backed by ByteArray#
.
The representation on the heap of a Byte Array is:
+------------+-----------------+-----------------------+ | | | | | HEADER | SIZE (in bytes) | PAYLOAD | | | | | +------------+-----------------+-----------------------+
To obtain a pointer to actual payload (e.g., for FFI purposes) use byteArrayContents#
or mutableByteArrayContents#
.
Alternatively, enabling the UnliftedFFITypes
extension
allows to mention ByteArray#
and MutableByteArray#
in FFI type signatures directly.
data CONSTRAINT (a :: RuntimeRep) Source #
data Compact# :: UnliftedType Source #
The builtin function type, written in infix form as a % m -> b
.
Values of this type are functions taking inputs of type a
and
producing outputs of type b
. The multiplicity of the input is
m
.
Note that
permits representation polymorphism in both
FUN
m a ba
and b
, so that types like
can still be
well-kinded.Int#
-> Int#
Instances
Category (->) Source # | Since: base-3.0 |
(PrintfArg a, HPrintfType r) => HPrintfType (a -> r) Source # | Since: base-2.1 |
Defined in Text.Printf | |
(PrintfArg a, PrintfType r) => PrintfType (a -> r) Source # | Since: base-2.1 |
Defined in Text.Printf | |
Monoid b => Monoid (a -> b) Source # | Since: base-2.1 |
Semigroup b => Semigroup (a -> b) Source # | Since: base-4.9.0.0 |
Arrow (->) Source # | Since: base-2.1 |
ArrowApply (->) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Arrow | |
ArrowChoice (->) Source # | Since: base-2.1 |
ArrowLoop (->) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Arrow | |
Show (a -> b) Source # | Since: base-2.1 |
Applicative ((->) r) Source # | Since: base-2.1 |
Functor ((->) r) Source # | Since: base-2.1 |
Monad ((->) r) Source # | Since: base-2.1 |
MonadFix ((->) r) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Monad.Fix |
data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
A shared I/O port is almost the same as an MVar#
.
The main difference is that IOPort has no deadlock detection or
deadlock breaking code that forcibly releases the lock.
data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
A MutVar#
behaves like a single-element mutable array.
data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data MutableByteArray# a :: UnliftedType Source #
A mutable ByteAray#
. It can be created in three ways:
newByteArray#
: Create an unpinned array.newPinnedByteArray#
: This will create a pinned array,newAlignedPinnedByteArray#
: This will create a pinned array, with a custom alignment.
Unpinned arrays can be moved around during garbage collection, so you must not store or pass pointers to these values if there is a chance for the garbage collector to kick in. That said, even unpinned arrays can be passed to unsafe FFI calls, because no garbage collection happens during these unsafe calls (see Guaranteed Call Safety in the GHC Manual). For safe FFI calls, byte arrays must be not only pinned, but also kept alive by means of the keepAlive# function for the duration of a call (that's because garbage collection cannot move a pinned array, but is free to scrap it altogether).
data PromptTag# a :: UnliftedType Source #
See GHC.Prim.
data Proxy# (a :: k) :: ZeroBitType Source #
data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data StackSnapshot# :: UnliftedType Source #
Haskell representation of a StgStack*
that was created (cloned)
with a function in GHC.Stack.CloneStack. Please check the
documentation in that module for more detailed explanations.
data State# a :: ZeroBitType Source #
data TYPE (a :: RuntimeRep) Source #
Instances
HasResolution E0 Source # | Since: base-4.1.0.0 | ||||
Defined in Data.Fixed resolution :: p E0 -> Integer Source # | |||||
HasResolution E1 Source # | Since: base-4.1.0.0 | ||||
Defined in Data.Fixed resolution :: p E1 -> Integer Source # | |||||
HasResolution E12 Source # | Since: base-2.1 | ||||
Defined in Data.Fixed resolution :: p E12 -> Integer Source # | |||||
HasResolution E2 Source # | Since: base-4.1.0.0 | ||||
Defined in Data.Fixed resolution :: p E2 -> Integer Source # | |||||
HasResolution E3 Source # | Since: base-4.1.0.0 | ||||
Defined in Data.Fixed resolution :: p E3 -> Integer Source # | |||||
HasResolution E6 Source # | Since: base-2.1 | ||||
Defined in Data.Fixed resolution :: p E6 -> Integer Source # | |||||
HasResolution E9 Source # | Since: base-4.1.0.0 | ||||
Defined in Data.Fixed resolution :: p E9 -> Integer Source # | |||||
Category Op Source # | |||||
Generic1 Complex Source # | |||||
Defined in Data.Complex
| |||||
Generic1 First Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Last Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Max Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 Min Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 WrappedMonoid Source # | |||||
Defined in Data.Semigroup
from1 :: WrappedMonoid a -> Rep1 WrappedMonoid a Source # to1 :: Rep1 WrappedMonoid a -> WrappedMonoid a Source # | |||||
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Identity Source # | |||||
Defined in GHC.Internal.Data.Functor.Identity
| |||||
Generic1 First Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Last Source # | |||||
Defined in GHC.Internal.Data.Monoid
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal
| |||||
Generic1 ZipList Source # | |||||
Defined in GHC.Internal.Functor.ZipList
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 Solo Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source # | Since: base-3.0 | ||||
Generic1 (WrappedMonad m :: Type -> Type) Source # | |||||
Defined in Control.Applicative
from1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source # to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source # | |||||
Generic1 (Arg a :: Type -> Type) Source # | |||||
Defined in Data.Semigroup
| |||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Category (->) Source # | Since: base-3.0 | ||||
Generic1 (WrappedArrow a b :: Type -> Type) Source # | |||||
Defined in Control.Applicative
from1 :: WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source # to1 :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source # | |||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Control.Arrow
| |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Functor f => Generic1 (Compose f g :: k -> Type) Source # | |||||
Defined in Data.Functor.Compose
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source # to1 :: Rep1 ((,,,,,,,,) a b c d e f g h) a0 -> (a, b, c, d, e, f, g, h, a0) Source # | |||||
Generic1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source # to1 :: Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 -> (a, b, c, d, e, f, g, h, i, a0) Source # | |||||
Generic1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, a0) -> Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 Source # to1 :: Rep1 ((,,,,,,,,,,) a b c d e f g h i j) a0 -> (a, b, c, d, e, f, g, h, i, j, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, a0) -> Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) a0 -> (a, b, c, d, e, f, g, h, i, j, k, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, a0) -> Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) Source # | |||||
Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics
from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 Source # to1 :: Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) Source # | |||||
Bifoldable (Const :: Type -> Type -> Type) Source # | Since: base-4.10.0.0 | ||||
Bifoldable1 (Const :: Type -> Type -> Type) Source # | |||||
Bifunctor (Const :: Type -> Type -> Type) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Const :: Type -> Type -> Type) Source # | 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 # | |||||
Foldable1 (V1 :: Type -> Type) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => V1 m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> V1 a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> V1 a -> m Source # toNonEmpty :: V1 a -> NonEmpty a Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V1 a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V1 a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V1 a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V1 a -> b Source # | |||||
Eq1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Eq1 (U1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UAddr :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq1 (V1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Eq2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Ord1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (U1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UAddr :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 (V1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read1 (Proxy :: Type -> Type) Source # | 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 # | |||||
Read1 (U1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read1 (V1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read2 (Const :: Type -> Type -> Type) Source # | 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 # | |||||
Show1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Show1 (U1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UAddr :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UChar :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UDouble :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UFloat :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UInt :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (UWord :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show1 (V1 :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Show2 (Const :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Contravariant (Proxy :: Type -> Type) Source # | |||||
Contravariant (U1 :: Type -> Type) Source # | |||||
Contravariant (V1 :: Type -> Type) Source # | |||||
Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Alternative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Applicative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
MonadZip (Proxy :: Type -> Type) Source # | Since: ghc-internal-4.9.0.0 | ||||
MonadZip (U1 :: Type -> Type) Source # | Since: ghc-internal-4.9.0.0 | ||||
Foldable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Proxy m -> m Source # foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source # foldr :: (a -> b -> b) -> b -> Proxy a -> b Source # foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source # foldl :: (b -> a -> b) -> b -> Proxy a -> b Source # foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source # foldr1 :: (a -> a -> a) -> Proxy a -> a Source # foldl1 :: (a -> a -> a) -> Proxy a -> a Source # toList :: Proxy a -> [a] Source # null :: Proxy a -> Bool Source # length :: Proxy a -> Int Source # elem :: Eq a => a -> Proxy a -> Bool Source # maximum :: Ord a => Proxy a -> a Source # minimum :: Ord a => Proxy a -> a Source # | |||||
Foldable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => U1 m -> m Source # foldMap :: Monoid m => (a -> m) -> U1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> U1 a -> m Source # foldr :: (a -> b -> b) -> b -> U1 a -> b Source # foldr' :: (a -> b -> b) -> b -> U1 a -> b Source # foldl :: (b -> a -> b) -> b -> U1 a -> b Source # foldl' :: (b -> a -> b) -> b -> U1 a -> b Source # foldr1 :: (a -> a -> a) -> U1 a -> a Source # foldl1 :: (a -> a -> a) -> U1 a -> a Source # toList :: U1 a -> [a] Source # length :: U1 a -> Int Source # elem :: Eq a => a -> U1 a -> Bool Source # maximum :: Ord a => U1 a -> a Source # minimum :: Ord a => U1 a -> a Source # | |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UChar m -> m Source # foldMap :: Monoid m => (a -> m) -> UChar a -> m Source # foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source # foldr :: (a -> b -> b) -> b -> UChar a -> b Source # foldr' :: (a -> b -> b) -> b -> UChar a -> b Source # foldl :: (b -> a -> b) -> b -> UChar a -> b Source # foldl' :: (b -> a -> b) -> b -> UChar a -> b Source # foldr1 :: (a -> a -> a) -> UChar a -> a Source # foldl1 :: (a -> a -> a) -> UChar a -> a Source # toList :: UChar a -> [a] Source # null :: UChar a -> Bool Source # length :: UChar a -> Int Source # elem :: Eq a => a -> UChar a -> Bool Source # maximum :: Ord a => UChar a -> a Source # minimum :: Ord a => UChar a -> a Source # | |||||
Foldable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UDouble m -> m Source # foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source # foldr :: (a -> b -> b) -> b -> UDouble a -> b Source # foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source # foldl :: (b -> a -> b) -> b -> UDouble a -> b Source # foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source # foldr1 :: (a -> a -> a) -> UDouble a -> a Source # foldl1 :: (a -> a -> a) -> UDouble a -> a Source # toList :: UDouble a -> [a] Source # null :: UDouble a -> Bool Source # length :: UDouble a -> Int Source # elem :: Eq a => a -> UDouble a -> Bool Source # maximum :: Ord a => UDouble a -> a Source # minimum :: Ord a => UDouble a -> a Source # | |||||
Foldable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UFloat m -> m Source # foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source # foldr :: (a -> b -> b) -> b -> UFloat a -> b Source # foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source # foldl :: (b -> a -> b) -> b -> UFloat a -> b Source # foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source # foldr1 :: (a -> a -> a) -> UFloat a -> a Source # foldl1 :: (a -> a -> a) -> UFloat a -> a Source # toList :: UFloat a -> [a] Source # null :: UFloat a -> Bool Source # length :: UFloat a -> Int Source # elem :: Eq a => a -> UFloat a -> Bool Source # maximum :: Ord a => UFloat a -> a Source # minimum :: Ord a => UFloat a -> a Source # | |||||
Foldable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UInt m -> m Source # foldMap :: Monoid m => (a -> m) -> UInt a -> m Source # foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source # foldr :: (a -> b -> b) -> b -> UInt a -> b Source # foldr' :: (a -> b -> b) -> b -> UInt a -> b Source # foldl :: (b -> a -> b) -> b -> UInt a -> b Source # foldl' :: (b -> a -> b) -> b -> UInt a -> b Source # foldr1 :: (a -> a -> a) -> UInt a -> a Source # foldl1 :: (a -> a -> a) -> UInt a -> a Source # toList :: UInt a -> [a] Source # null :: UInt a -> Bool Source # length :: UInt a -> Int Source # elem :: Eq a => a -> UInt a -> Bool Source # maximum :: Ord a => UInt a -> a Source # minimum :: Ord a => UInt a -> a Source # | |||||
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |||||
Foldable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => V1 m -> m Source # foldMap :: Monoid m => (a -> m) -> V1 a -> m Source # foldMap' :: Monoid m => (a -> m) -> V1 a -> m Source # foldr :: (a -> b -> b) -> b -> V1 a -> b Source # foldr' :: (a -> b -> b) -> b -> V1 a -> b Source # foldl :: (b -> a -> b) -> b -> V1 a -> b Source # foldl' :: (b -> a -> b) -> b -> V1 a -> b Source # foldr1 :: (a -> a -> a) -> V1 a -> a Source # foldl1 :: (a -> a -> a) -> V1 a -> a Source # toList :: V1 a -> [a] Source # length :: V1 a -> Int Source # elem :: Eq a => a -> V1 a -> Bool Source # maximum :: Ord a => V1 a -> a Source # minimum :: Ord a => V1 a -> a Source # | |||||
Traversable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UDouble :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UFloat :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (UInt :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Bifoldable (K1 i :: Type -> Type -> Type) Source # | Since: base-4.10.0.0 | ||||
Bifunctor (K1 i :: Type -> Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Bitraversable (K1 i :: Type -> Type -> Type) Source # | 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 # | |||||
Foldable1 f => Foldable1 (Ap f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Ap f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Ap f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Ap f a -> m Source # toNonEmpty :: Ap f a -> NonEmpty a Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Ap f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Ap f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Ap f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Ap f a -> b Source # | |||||
Foldable1 f => Foldable1 (Alt f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Alt f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Alt f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Alt f a -> m Source # toNonEmpty :: Alt f a -> NonEmpty a Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Alt f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Alt f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Alt f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Alt f a -> b Source # | |||||
Foldable1 f => Foldable1 (Rec1 f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Rec1 f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Rec1 f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Rec1 f a -> m Source # toNonEmpty :: Rec1 f a -> NonEmpty a Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # head :: Rec1 f a -> a Source # last :: Rec1 f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Rec1 f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Rec1 f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Rec1 f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Rec1 f a -> b Source # | |||||
Eq a => Eq1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in Data.Functor.Classes liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source # | |||||
Eq1 f => Eq1 (Rec1 f) Source # | Since: base-4.21.0.0 | ||||
Ord a => Ord1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source # | |||||
Ord1 f => Ord1 (Rec1 f) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read a => Read1 (Const a :: Type -> Type) Source # | 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 # | |||||
Read1 f => Read1 (Rec1 f) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Rec1 f a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Rec1 f a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Rec1 f a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Rec1 f a] Source # | |||||
Show a => Show1 (Const a :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Show1 f => Show1 (Rec1 f) Source # | Since: base-4.21.0.0 | ||||
Contravariant (Const a :: Type -> Type) Source # | |||||
Contravariant f => Contravariant (Alt f) Source # | |||||
Contravariant f => Contravariant (Rec1 f) Source # | |||||
Alternative f => Alternative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Alternative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics empty :: Generically1 f a Source # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # some :: Generically1 f a -> Generically1 f [a] Source # many :: Generically1 f a -> Generically1 f [a] Source # | |||||
Alternative f => Alternative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Monoid m => Applicative (Const m :: Type -> Type) Source # | Since: base-2.0.1 | ||||
Defined in GHC.Internal.Data.Functor.Const | |||||
Applicative f => Applicative (Ap f) Source # | Since: base-4.12.0.0 | ||||
Applicative f => Applicative (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics pure :: a -> Generically1 f a Source # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source # | |||||
Applicative f => Applicative (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (Const m :: Type -> Type) Source # | Since: base-2.1 | ||||
Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 | ||||
Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 | ||||
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 | ||||
Defined in GHC.Internal.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |||||
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 | ||||
Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 | ||||
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadPlus f => MonadPlus (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadFail f => MonadFail (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Ap f) Source # | Since: base-4.12.0.0 | ||||
MonadFix f => MonadFix (Alt f) Source # | Since: base-4.8.0.0 | ||||
MonadFix f => MonadFix (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
MonadZip f => MonadZip (Alt f) Source # | Since: ghc-internal-4.8.0.0 | ||||
MonadZip f => MonadZip (Rec1 f) Source # | Since: ghc-internal-4.9.0.0 | ||||
Data t => Data (Proxy t) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) Source # toConstr :: Proxy t -> Constr Source # dataTypeOf :: Proxy t -> DataType Source # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) Source # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # | |||||
Data p => Data (U1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> U1 p -> c (U1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (U1 p) Source # toConstr :: U1 p -> Constr Source # dataTypeOf :: U1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (U1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (U1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> U1 p -> U1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> U1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 p -> m (U1 p) Source # | |||||
Data p => Data (V1 p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 p -> c (V1 p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 p) Source # toConstr :: V1 p -> Constr Source # dataTypeOf :: V1 p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 p)) Source # gmapT :: (forall b. Data b => b -> b) -> V1 p -> V1 p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> V1 p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 p -> m (V1 p) Source # | |||||
Foldable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 Source # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source # foldr :: (a -> b -> b) -> b -> Const m a -> b Source # foldr' :: (a -> b -> b) -> b -> Const m a -> b Source # foldl :: (b -> a -> b) -> b -> Const m a -> b Source # foldl' :: (b -> a -> b) -> b -> Const m a -> b Source # foldr1 :: (a -> a -> a) -> Const m a -> a Source # foldl1 :: (a -> a -> a) -> Const m a -> a Source # toList :: Const m a -> [a] Source # null :: Const m a -> Bool Source # length :: Const m a -> Int Source # elem :: Eq a => a -> Const m a -> Bool Source # maximum :: Ord a => Const m a -> a Source # minimum :: Ord a => Const m a -> a Source # | |||||
Foldable f => Foldable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Ap f m -> m Source # foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m Source # foldr :: (a -> b -> b) -> b -> Ap f a -> b Source # foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source # foldl :: (b -> a -> b) -> b -> Ap f a -> b Source # foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source # foldr1 :: (a -> a -> a) -> Ap f a -> a Source # foldl1 :: (a -> a -> a) -> Ap f a -> a Source # toList :: Ap f a -> [a] Source # null :: Ap f a -> Bool Source # length :: Ap f a -> Int Source # elem :: Eq a => a -> Ap f a -> Bool Source # maximum :: Ord a => Ap f a -> a Source # minimum :: Ord a => Ap f a -> a Source # | |||||
Foldable f => Foldable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Alt f m -> m Source # foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source # foldr :: (a -> b -> b) -> b -> Alt f a -> b Source # foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source # foldl :: (b -> a -> b) -> b -> Alt f a -> b Source # foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source # foldr1 :: (a -> a -> a) -> Alt f a -> a Source # foldl1 :: (a -> a -> a) -> Alt f a -> a Source # toList :: Alt f a -> [a] Source # null :: Alt f a -> Bool Source # length :: Alt f a -> Int Source # elem :: Eq a => a -> Alt f a -> Bool Source # maximum :: Ord a => Alt f a -> a Source # minimum :: Ord a => Alt f a -> a Source # | |||||
Foldable f => Foldable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => Rec1 f m -> m Source # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m Source # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source # foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source # foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source # toList :: Rec1 f a -> [a] Source # null :: Rec1 f a -> Bool Source # length :: Rec1 f a -> Int Source # elem :: Eq a => a -> Rec1 f a -> Bool Source # maximum :: Ord a => Rec1 f a -> a Source # minimum :: Ord a => Rec1 f a -> a Source # | |||||
Traversable (Const m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Ap f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Alt f) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (Rec1 f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (Product f g) Source # | It would be enough for either half of a product to be | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Product f g m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Product f g a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Product f g a -> m Source # toNonEmpty :: Product f g a -> NonEmpty a Source # maximum :: Ord a => Product f g a -> a Source # minimum :: Ord a => Product f g a -> a Source # head :: Product f g a -> a Source # last :: Product f g a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Product f g a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Product f g a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Product f g a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Product f g a -> b Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (Sum f g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Sum f g m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Sum f g a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Sum f g a -> m Source # toNonEmpty :: Sum f g a -> NonEmpty a Source # maximum :: Ord a => Sum f g a -> a Source # minimum :: Ord a => Sum f g a -> a Source # head :: Sum f g a -> a Source # last :: Sum f g a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Sum f g a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Sum f g a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Sum f g a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Sum f g a -> b Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :*: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :*: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :*: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :*: g) a -> m Source # toNonEmpty :: (f :*: g) a -> NonEmpty a Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # head :: (f :*: g) a -> a Source # last :: (f :*: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :+: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :+: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :+: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :+: g) a -> m Source # toNonEmpty :: (f :+: g) a -> NonEmpty a Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # head :: (f :+: g) a -> a Source # last :: (f :+: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :+: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :+: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :+: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :+: g) a -> b Source # | |||||
(Eq1 f, Eq1 g) => Eq1 (Product f g) Source # | Since: base-4.9.0.0 | ||||
(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source # | Since: base-4.9.0.0 | ||||
(Eq1 f, Eq1 g) => Eq1 (f :*: g) Source # | Since: base-4.21.0.0 | ||||
(Eq1 f, Eq1 g) => Eq1 (f :+: g) Source # | Since: base-4.21.0.0 | ||||
Eq c => Eq1 (K1 i c :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
(Ord1 f, Ord1 g) => Ord1 (Product f g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Product | |||||
(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Sum | |||||
(Ord1 f, Ord1 g) => Ord1 (f :*: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Ord1 f, Ord1 g) => Ord1 (f :+: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord c => Ord1 (K1 i c :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Read1 f, Read1 g) => Read1 (Product f g) Source # | 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 # | |||||
(Read1 f, Read1 g) => Read1 (Sum f g) Source # | 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 (f :*: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :*: g) a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :*: g) a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :*: g) a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :*: g) a] Source # | |||||
(Read1 f, Read1 g) => Read1 (f :+: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :+: g) a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :+: g) a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :+: g) a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :+: g) a] Source # | |||||
Read c => Read1 (K1 i c :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (K1 i c a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [K1 i c a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (K1 i c a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [K1 i c a] Source # | |||||
(Show1 f, Show1 g) => Show1 (Product f g) Source # | Since: base-4.9.0.0 | ||||
(Show1 f, Show1 g) => Show1 (Sum f g) Source # | Since: base-4.9.0.0 | ||||
(Show1 f, Show1 g) => Show1 (f :*: g) Source # | Since: base-4.21.0.0 | ||||
(Show1 f, Show1 g) => Show1 (f :+: g) Source # | Since: base-4.21.0.0 | ||||
Show c => Show1 (K1 i c :: Type -> Type) Source # | Since: base-4.21.0.0 | ||||
(Contravariant f, Contravariant g) => Contravariant (Product f g) Source # | |||||
(Contravariant f, Contravariant g) => Contravariant (Sum f g) Source # | |||||
(Contravariant f, Contravariant g) => Contravariant (f :*: g) Source # | |||||
(Contravariant f, Contravariant g) => Contravariant (f :+: g) Source # | |||||
Contravariant (K1 i c :: Type -> Type) Source # | |||||
(Alternative f, Alternative g) => Alternative (Product f g) Source # | Since: base-4.9.0.0 | ||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (Product f g) Source # | 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 # | |||||
(Applicative f, Applicative g) => Applicative (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Monoid c => Applicative (K1 i c :: Type -> Type) Source # | Since: base-4.12.0.0 | ||||
(Functor f, Functor g) => Functor (Product f g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (Sum f g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (Product f g) Source # | Since: base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) Source # | Since: base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Monoid a) => Monoid (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Monoid (Alt f a) Source # | Since: base-4.8.0.0 | ||||
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Alternative f => Semigroup (Alt f a) Source # | Since: base-4.9.0.0 | ||||
(MonadFix f, MonadFix g) => MonadFix (Product f g) Source # | Since: base-4.9.0.0 | ||||
(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source # | Since: base-4.9.0.0 | ||||
(MonadZip f, MonadZip g) => MonadZip (Product f g) Source # | Since: base-4.9.0.0 | ||||
(MonadZip f, MonadZip g) => MonadZip (f :*: g) Source # | Since: ghc-internal-4.9.0.0 | ||||
(Data (f a), Data a, Typeable f) => Data (Ap f a) Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ap f a -> c (Ap f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ap f a) Source # toConstr :: Ap f a -> Constr Source # dataTypeOf :: Ap f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ap f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source # | |||||
(Data (f a), Data a, Typeable f) => Data (Alt f a) Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alt f a -> c (Alt f a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Alt f a) Source # toConstr :: Alt f a -> Constr Source # dataTypeOf :: Alt f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Alt f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source # | |||||
(Coercible a b, Data a, Data b) => Data (Coercion a b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Coercion a b -> c (Coercion a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion a b) Source # toConstr :: Coercion a b -> Constr Source # dataTypeOf :: Coercion a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Coercion a b -> Coercion a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Coercion a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion a b -> m (Coercion a b) Source # | |||||
(a ~ b, Data a) => Data (a :~: b) Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) Source # toConstr :: (a :~: b) -> Constr Source # dataTypeOf :: (a :~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # | |||||
(Data (f p), Typeable f, Data p) => Data (Rec1 f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rec1 f p -> c (Rec1 f p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Rec1 f p) Source # toConstr :: Rec1 f p -> Constr Source # dataTypeOf :: Rec1 f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Rec1 f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Rec1 f p)) Source # gmapT :: (forall b. Data b => b -> b) -> Rec1 f p -> Rec1 f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Rec1 f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 f p -> m (Rec1 f p) Source # | |||||
(Foldable f, Foldable g) => Foldable (Product f g) Source # | 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 # 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 # | |||||
(Foldable f, Foldable g) => Foldable (Sum f g) Source # | 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 # 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 (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :*: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source # toList :: (f :*: g) a -> [a] Source # null :: (f :*: g) a -> Bool Source # length :: (f :*: g) a -> Int Source # elem :: Eq a => a -> (f :*: g) a -> Bool Source # maximum :: Ord a => (f :*: g) a -> a Source # minimum :: Ord a => (f :*: g) a -> a Source # | |||||
(Foldable f, Foldable g) => Foldable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :+: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source # toList :: (f :+: g) a -> [a] Source # null :: (f :+: g) a -> Bool Source # length :: (f :+: g) a -> Int Source # elem :: Eq a => a -> (f :+: g) a -> Bool Source # maximum :: Ord a => (f :+: g) a -> a Source # minimum :: Ord a => (f :+: g) a -> a Source # | |||||
Foldable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => K1 i c m -> m Source # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m Source # foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source # foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source # foldr1 :: (a -> a -> a) -> K1 i c a -> a Source # foldl1 :: (a -> a -> a) -> K1 i c a -> a Source # toList :: K1 i c a -> [a] Source # null :: K1 i c a -> Bool Source # length :: K1 i c a -> Int Source # elem :: Eq a => a -> K1 i c a -> Bool Source # maximum :: Ord a => K1 i c a -> a Source # minimum :: Ord a => K1 i c a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (Product f g) Source # | 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 # | |||||
(Traversable f, Traversable g) => Traversable (Sum f g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Sum | |||||
(Traversable f, Traversable g) => Traversable (f :*: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Applicative f, Bounded a) => Bounded (Ap f a) Source # | Since: base-4.12.0.0 | ||||
(Applicative f, Num a) => Num (Ap f a) Source # | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (Compose f g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => Compose f g m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> Compose f g a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> Compose f g a -> m Source # toNonEmpty :: Compose f g a -> NonEmpty a Source # maximum :: Ord a => Compose f g a -> a Source # minimum :: Ord a => Compose f g a -> a Source # head :: Compose f g a -> a Source # last :: Compose f g a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Compose f g a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Compose f g a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Compose f g a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Compose f g a -> b Source # | |||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :.: g) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :.: g) m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (f :.: g) a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (f :.: g) a -> m Source # toNonEmpty :: (f :.: g) a -> NonEmpty a Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # head :: (f :.: g) a -> a Source # last :: (f :.: g) a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :.: g) a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :.: g) a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :.: g) a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :.: g) a -> b Source # | |||||
Foldable1 f => Foldable1 (M1 i c f) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => M1 i c f m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> M1 i c f a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> M1 i c f a -> m Source # toNonEmpty :: M1 i c f a -> NonEmpty a Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # head :: M1 i c f a -> a Source # last :: M1 i c f a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> M1 i c f a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> M1 i c f a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> M1 i c f a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> M1 i c f a -> b Source # | |||||
(Eq1 f, Eq1 g) => Eq1 (Compose f g) Source # | Since: base-4.9.0.0 | ||||
(Eq1 f, Eq1 g) => Eq1 (f :.: g) Source # | Since: base-4.21.0.0 | ||||
Eq1 f => Eq1 (M1 i c f) Source # | Since: base-4.21.0.0 | ||||
(Ord1 f, Ord1 g) => Ord1 (Compose f g) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Compose | |||||
(Ord1 f, Ord1 g) => Ord1 (f :.: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Ord1 f => Ord1 (M1 i c f) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Read1 f, Read1 g) => Read1 (Compose f g) Source # | 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 # | |||||
(Read1 f, Read1 g) => Read1 (f :.: g) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] Source # | |||||
Read1 f => Read1 (M1 i c f) Source # | Since: base-4.21.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (M1 i c f a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [M1 i c f a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (M1 i c f a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [M1 i c f a] Source # | |||||
(Show1 f, Show1 g) => Show1 (Compose f g) Source # | Since: base-4.9.0.0 | ||||
(Show1 f, Show1 g) => Show1 (f :.: g) Source # | Since: base-4.21.0.0 | ||||
Show1 f => Show1 (M1 i c f) Source # | Since: base-4.21.0.0 | ||||
(Functor f, Contravariant g) => Contravariant (Compose f g) Source # | |||||
(Functor f, Contravariant g) => Contravariant (f :.: g) Source # | |||||
Contravariant f => Contravariant (M1 i c f) Source # | |||||
(Alternative f, Applicative g) => Alternative (Compose f g) Source # | Since: base-4.9.0.0 | ||||
(Alternative f, Applicative g) => Alternative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Alternative f => Alternative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (Compose f g) Source # | 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 # | |||||
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
Applicative f => Applicative (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
(Functor f, Functor g) => Functor (Compose f g) Source # | Since: base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadFix f => MonadFix (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
MonadZip f => MonadZip (M1 i c f) Source # | Since: ghc-internal-4.9.0.0 | ||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :*: g) p -> c ((f :*: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :*: g) p) Source # toConstr :: (f :*: g) p -> Constr Source # dataTypeOf :: (f :*: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :*: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :*: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :*: g) p -> (f :*: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :*: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :*: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :*: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :*: g) p -> m ((f :*: g) p) Source # | |||||
(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :+: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :+: g) p -> c ((f :+: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :+: g) p) Source # toConstr :: (f :+: g) p -> Constr Source # dataTypeOf :: (f :+: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :+: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :+: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :+: g) p -> (f :+: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :+: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :+: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :+: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :+: g) p -> m ((f :+: g) p) Source # | |||||
(Typeable i, Data p, Data c) => Data (K1 i c p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> K1 i c p -> c0 (K1 i c p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (K1 i c p) Source # toConstr :: K1 i c p -> Constr Source # dataTypeOf :: K1 i c p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (K1 i c p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (K1 i c p)) Source # gmapT :: (forall b. Data b => b -> b) -> K1 i c p -> K1 i c p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 i c p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> K1 i c p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 i c p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 i c p -> m (K1 i c p) Source # | |||||
(Foldable f, Foldable g) => Foldable (Compose f g) Source # | 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 # 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 # | |||||
(Foldable f, Foldable g) => Foldable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => (f :.: g) m -> m Source # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source # toList :: (f :.: g) a -> [a] Source # null :: (f :.: g) a -> Bool Source # length :: (f :.: g) a -> Int Source # elem :: Eq a => a -> (f :.: g) a -> Bool Source # maximum :: Ord a => (f :.: g) a -> a Source # minimum :: Ord a => (f :.: g) a -> a Source # | |||||
Foldable f => Foldable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => M1 i c f m -> m Source # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m Source # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source # foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source # foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source # toList :: M1 i c f a -> [a] Source # null :: M1 i c f a -> Bool Source # length :: M1 i c f a -> Int Source # elem :: Eq a => a -> M1 i c f a -> Bool Source # maximum :: Ord a => M1 i c f a -> a Source # minimum :: Ord a => M1 i c f a -> a Source # | |||||
(Traversable f, Traversable g) => Traversable (Compose f g) Source # | 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 # | |||||
(Traversable f, Traversable g) => Traversable (f :.: g) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Traversable f => Traversable (M1 i c f) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> (f :.: g) p -> c ((f :.: g) p) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((f :.: g) p) Source # toConstr :: (f :.: g) p -> Constr Source # dataTypeOf :: (f :.: g) p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ((f :.: g) p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((f :.: g) p)) Source # gmapT :: (forall b. Data b => b -> b) -> (f :.: g) p -> (f :.: g) p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (f :.: g) p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (f :.: g) p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (f :.: g) p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (f :.: g) p -> m ((f :.: g) p) Source # | |||||
(Data p, Data (f p), Typeable c, Typeable i, Typeable f) => Data (M1 i c f p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> M1 i c f p -> c0 (M1 i c f p) Source # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (M1 i c f p) Source # toConstr :: M1 i c f p -> Constr Source # dataTypeOf :: M1 i c f p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (M1 i c f p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (M1 i c f p)) Source # gmapT :: (forall b. Data b => b -> b) -> M1 i c f p -> M1 i c f p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 i c f p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> M1 i c f p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 i c f p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 i c f p -> m (M1 i c f p) Source # | |||||
type Rep1 Complex Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Complex type Rep1 Complex = D1 ('MetaData "Complex" "Data.Complex" "base-4.20.0.0-inplace" '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 First Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 Last Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 Max Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 Min Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup | |||||
type Rep1 WrappedMonoid Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup type Rep1 WrappedMonoid = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base-4.20.0.0-inplace" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 NonEmpty Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 Identity Source # | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
type Rep1 First Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Last Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Monoid | |||||
type Rep1 Down Source # | Since: base-4.12.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Dual Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Product Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 Sum Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Semigroup.Internal | |||||
type Rep1 ZipList Source # | Since: base-4.7.0.0 | ||||
Defined in GHC.Internal.Functor.ZipList | |||||
type Rep1 Par1 Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Maybe Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 Solo Source # | Since: base-4.15 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep1 (WrappedMonad m :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in Control.Applicative type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base-4.20.0.0-inplace" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m))) | |||||
type Rep1 (Arg a :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Semigroup type Rep1 (Arg a :: Type -> Type) = D1 ('MetaData "Arg" "Data.Semigroup" "base-4.20.0.0-inplace" '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 (Either a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 ((,) a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,) a :: Type -> Type) = D1 ('MetaData "Tuple2" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep1 (WrappedArrow a b :: Type -> Type) Source # | Since: base-4.7.0.0 | ||||
Defined in Control.Applicative type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b)))) | |||||
type Rep1 (Kleisli m a :: Type -> Type) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Internal.Control.Arrow | |||||
type Rep1 ((,,) a b :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,) a b :: Type -> Type) = D1 ('MetaData "Tuple3" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,) a b c :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,) a b c :: Type -> Type) = D1 ('MetaData "Tuple4" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep1 ((,,,,) a b c d :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,) a b c d :: Type -> Type) = D1 ('MetaData "Tuple5" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 (Compose f g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Compose | |||||
type Rep1 (f :.: g :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 ((,,,,,) a b c d e :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,) a b c d e :: Type -> Type) = D1 ('MetaData "Tuple6" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) = D1 ('MetaData "Tuple7" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) = D1 ('MetaData "Tuple8" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) = D1 ('MetaData "Tuple9" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) = D1 ('MetaData "Tuple10" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) = D1 ('MetaData "Tuple11" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) = D1 ('MetaData "Tuple12" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "Tuple13" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "Tuple14" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "Tuple15" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) |
data ThreadId# :: UnliftedType Source #
(In a non-concurrent implementation, this can be a singleton
type, whose (unique) value is returned by myThreadId#
. The
other operations can be omitted.)
data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep) Source #
data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep) Source #
data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep) Source #
module GHC.Prim.Ext
module GHC.Prim.PtrEq
module GHC.Internal.Err
module GHC.Internal.Maybe
Equality and ordering
class IP (x :: Symbol) a | x -> a where Source #
The syntax ?x :: a
is desugared into IP "x" a
IP is declared very early, so that libraries can take
advantage of the implicit-call-stack feature
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
The Haskell Report defines no laws for Eq
. However, instances are
encouraged to follow these properties:
Instances
Eq ByteArray Source # | Since: base-4.17.0.0 |
Eq Timeout Source # | |
Eq BigNat # | |
Eq Void Source # | Since: base-4.8.0.0 |
Eq ByteOrder Source # | Since: base-4.11.0.0 |
Eq ClosureType Source # | |
Defined in GHC.Internal.ClosureTypes (==) :: ClosureType -> ClosureType -> Bool Source # (/=) :: ClosureType -> ClosureType -> Bool Source # | |
Eq BlockReason Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync (==) :: BlockReason -> BlockReason -> Bool Source # (/=) :: BlockReason -> BlockReason -> Bool Source # | |
Eq ThreadId Source # | Since: base-4.2.0.0 |
Eq ThreadStatus Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync (==) :: ThreadStatus -> ThreadStatus -> Bool Source # (/=) :: ThreadStatus -> ThreadStatus -> Bool Source # | |
Eq Constr Source # | Equality of constructors Since: base-4.0.0.0 |
Eq ConstrRep Source # | Since: base-4.0.0.0 |
Eq DataRep Source # | Since: base-4.0.0.0 |
Eq Fixity Source # | Since: base-4.0.0.0 |
Eq All Source # | Since: base-2.1 |
Eq Any Source # | Since: base-2.1 |
Eq SomeTypeRep Source # | |
Defined in GHC.Internal.Data.Typeable.Internal (==) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (/=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # | |
Eq Unique Source # | |
Eq Version Source # | Since: base-2.1 |
Eq ControlMessage Source # | Since: base-4.4.0.0 |
Eq Event Source # | Since: base-4.4.0.0 |
Eq EventLifetime Source # | Since: base-4.8.0.0 |
Eq Lifetime Source # | Since: base-4.8.1.0 |
Eq FdKey Source # | Since: base-4.4.0.0 |
Eq State Source # | Since: base-4.4.0.0 |
Eq TimeoutKey Source # | |
Defined in GHC.Internal.Event.TimeOut (==) :: TimeoutKey -> TimeoutKey -> Bool Source # (/=) :: TimeoutKey -> TimeoutKey -> Bool Source # | |
Eq State Source # | Since: base-4.7.0.0 |
Eq Unique Source # | Since: base-4.4.0.0 |
Eq ErrorCall Source # | Since: base-4.7.0.0 |
Eq ArithException Source # | Since: base-3.0 |
Defined in GHC.Internal.Exception.Type (==) :: ArithException -> ArithException -> Bool Source # (/=) :: ArithException -> ArithException -> Bool Source # | |
Eq SpecConstrAnnotation Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Exts (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # | |
Eq Fingerprint Source # | Since: base-4.4.0.0 |
Defined in GHC.Internal.Fingerprint.Type (==) :: Fingerprint -> Fingerprint -> Bool Source # (/=) :: Fingerprint -> Fingerprint -> Bool Source # | |
Eq Errno Source # | Since: base-2.1 |
Eq CBool Source # | |
Eq CChar Source # | |
Eq CClock Source # | |
Eq CDouble Source # | |
Eq CFloat Source # | |
Eq CInt Source # | |
Eq CIntMax Source # | |
Eq CIntPtr Source # | |
Eq CLLong Source # | |
Eq CLong Source # | |
Eq CPtrdiff Source # | |
Eq CSChar Source # | |
Eq CSUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types (==) :: CSUSeconds -> CSUSeconds -> Bool Source # (/=) :: CSUSeconds -> CSUSeconds -> Bool Source # | |
Eq CShort Source # | |
Eq CSigAtomic Source # | |
Defined in GHC.Internal.Foreign.C.Types (==) :: CSigAtomic -> CSigAtomic -> Bool Source # (/=) :: CSigAtomic -> CSigAtomic -> Bool Source # | |
Eq CSize Source # | |
Eq CTime Source # | |
Eq CUChar Source # | |
Eq CUInt Source # | |
Eq CUIntMax Source # | |
Eq CUIntPtr Source # | |
Eq CULLong Source # | |
Eq CULong Source # | |
Eq CUSeconds Source # | |
Eq CUShort Source # | |
Eq CWchar Source # | |
Eq IntPtr Source # | |
Eq WordPtr Source # | |
Eq ForeignSrcLang Source # | |
Defined in GHC.Internal.ForeignSrcLang (==) :: ForeignSrcLang -> ForeignSrcLang -> Bool Source # (/=) :: ForeignSrcLang -> ForeignSrcLang -> Bool Source # | |
Eq Associativity Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Generics (==) :: Associativity -> Associativity -> Bool Source # (/=) :: Associativity -> Associativity -> Bool Source # | |
Eq DecidedStrictness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics (==) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # | |
Eq Fixity Source # | Since: base-4.6.0.0 |
Eq SourceStrictness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics (==) :: SourceStrictness -> SourceStrictness -> Bool Source # (/=) :: SourceStrictness -> SourceStrictness -> Bool Source # | |
Eq SourceUnpackedness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # | |
Eq MaskingState Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO (==) :: MaskingState -> MaskingState -> Bool Source # (/=) :: MaskingState -> MaskingState -> Bool Source # | |
Eq BufferState Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Buffer (==) :: BufferState -> BufferState -> Bool Source # (/=) :: BufferState -> BufferState -> Bool Source # | |
Eq IODeviceType Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Device (==) :: IODeviceType -> IODeviceType -> Bool Source # (/=) :: IODeviceType -> IODeviceType -> Bool Source # | |
Eq SeekMode Source # | Since: base-4.2.0.0 |
Eq CodingProgress Source # | Since: base-4.4.0.0 |
Defined in GHC.Internal.IO.Encoding.Types (==) :: CodingProgress -> CodingProgress -> Bool Source # (/=) :: CodingProgress -> CodingProgress -> Bool Source # | |
Eq ArrayException Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception (==) :: ArrayException -> ArrayException -> Bool Source # (/=) :: ArrayException -> ArrayException -> Bool Source # | |
Eq AsyncException Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception (==) :: AsyncException -> AsyncException -> Bool Source # (/=) :: AsyncException -> AsyncException -> Bool Source # | |
Eq ExitCode Source # | |
Eq IOErrorType Source # | Since: base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception (==) :: IOErrorType -> IOErrorType -> Bool Source # (/=) :: IOErrorType -> IOErrorType -> Bool Source # | |
Eq IOException Source # | Since: base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception (==) :: IOException -> IOException -> Bool Source # (/=) :: IOException -> IOException -> Bool Source # | |
Eq HandlePosn Source # | Since: base-4.1.0.0 |
Defined in GHC.Internal.IO.Handle (==) :: HandlePosn -> HandlePosn -> Bool Source # (/=) :: HandlePosn -> HandlePosn -> Bool Source # | |
Eq BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types (==) :: BufferMode -> BufferMode -> Bool Source # (/=) :: BufferMode -> BufferMode -> Bool Source # | |
Eq Handle Source # | Since: base-4.1.0.0 |
Eq Newline Source # | Since: base-4.2.0.0 |
Eq NewlineMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types (==) :: NewlineMode -> NewlineMode -> Bool Source # (/=) :: NewlineMode -> NewlineMode -> Bool Source # | |
Eq IOMode Source # | Since: base-4.2.0.0 |
Eq IoSubSystem Source # | |
Defined in GHC.Internal.IO.SubSystem (==) :: IoSubSystem -> IoSubSystem -> Bool Source # (/=) :: IoSubSystem -> IoSubSystem -> Bool Source # | |
Eq InfoProv Source # | |
Eq Int16 Source # | Since: base-2.1 |
Eq Int32 Source # | Since: base-2.1 |
Eq Int64 Source # | Since: base-2.1 |
Eq Int8 Source # | Since: base-2.1 |
Eq Extension Source # | |
Eq IoManagerFlag Source # | |
Defined in GHC.Internal.RTS.Flags (==) :: IoManagerFlag -> IoManagerFlag -> Bool Source # (/=) :: IoManagerFlag -> IoManagerFlag -> Bool Source # | |
Eq StackEntry Source # | |
Defined in GHC.Internal.Stack.CloneStack (==) :: StackEntry -> StackEntry -> Bool Source # (/=) :: StackEntry -> StackEntry -> Bool Source # | |
Eq SrcLoc Source # | Since: base-4.9.0.0 |
Eq CBlkCnt Source # | |
Eq CBlkSize Source # | |
Eq CCc Source # | |
Eq CClockId Source # | |
Eq CDev Source # | |
Eq CFsBlkCnt Source # | |
Eq CFsFilCnt Source # | |
Eq CGid Source # | |
Eq CId Source # | |
Eq CIno Source # | |
Eq CKey Source # | |
Eq CMode Source # | |
Eq CNfds Source # | |
Eq CNlink Source # | |
Eq COff Source # | |
Eq CPid Source # | |
Eq CRLim Source # | |
Eq CSocklen Source # | |
Eq CSpeed Source # | |
Eq CSsize Source # | |
Eq CTcflag Source # | |
Eq CTimer Source # | |
Eq CUid Source # | |
Eq Fd Source # | |
Eq AnnLookup Source # | |
Eq AnnTarget Source # | |
Eq Bang Source # | |
Eq BndrVis Source # | |
Eq Body Source # | |
Eq Bytes Source # | |
Eq Callconv Source # | |
Eq Clause Source # | |
Eq Con Source # | |
Eq Dec Source # | |
Eq DecidedStrictness Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # | |
Eq DerivClause Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: DerivClause -> DerivClause -> Bool Source # (/=) :: DerivClause -> DerivClause -> Bool Source # | |
Eq DerivStrategy Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: DerivStrategy -> DerivStrategy -> Bool Source # (/=) :: DerivStrategy -> DerivStrategy -> Bool Source # | |
Eq DocLoc Source # | |
Eq Exp Source # | |
Eq FamilyResultSig Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: FamilyResultSig -> FamilyResultSig -> Bool Source # (/=) :: FamilyResultSig -> FamilyResultSig -> Bool Source # | |
Eq Fixity Source # | |
Eq FixityDirection Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: FixityDirection -> FixityDirection -> Bool Source # (/=) :: FixityDirection -> FixityDirection -> Bool Source # | |
Eq Foreign Source # | |
Eq FunDep Source # | |
Eq Guard Source # | |
Eq Info Source # | |
Eq InjectivityAnn Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: InjectivityAnn -> InjectivityAnn -> Bool Source # (/=) :: InjectivityAnn -> InjectivityAnn -> Bool Source # | |
Eq Inline Source # | |
Eq Lit Source # | |
Eq Loc Source # | |
Eq Match Source # | |
Eq ModName Source # | |
Eq Module Source # | |
Eq ModuleInfo Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: ModuleInfo -> ModuleInfo -> Bool Source # (/=) :: ModuleInfo -> ModuleInfo -> Bool Source # | |
Eq Name Source # | |
Eq NameFlavour Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: NameFlavour -> NameFlavour -> Bool Source # (/=) :: NameFlavour -> NameFlavour -> Bool Source # | |
Eq NameSpace Source # | |
Eq NamespaceSpecifier Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # (/=) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # | |
Eq OccName Source # | |
Eq Overlap Source # | |
Eq Pat Source # | |
Eq PatSynArgs Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: PatSynArgs -> PatSynArgs -> Bool Source # (/=) :: PatSynArgs -> PatSynArgs -> Bool Source # | |
Eq PatSynDir Source # | |
Eq Phases Source # | |
Eq PkgName Source # | |
Eq Pragma Source # | |
Eq Range Source # | |
Eq Role Source # | |
Eq RuleBndr Source # | |
Eq RuleMatch Source # | |
Eq Safety Source # | |
Eq SourceStrictness Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: SourceStrictness -> SourceStrictness -> Bool Source # (/=) :: SourceStrictness -> SourceStrictness -> Bool Source # | |
Eq SourceUnpackedness Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # | |
Eq Specificity Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: Specificity -> Specificity -> Bool Source # (/=) :: Specificity -> Specificity -> Bool Source # | |
Eq Stmt Source # | |
Eq TyLit Source # | |
Eq TySynEqn Source # | |
Eq Type Source # | |
Eq TypeFamilyHead Source # | |
Defined in GHC.Internal.TH.Syntax (==) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # (/=) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # | |
Eq Lexeme Source # | Since: base-2.1 |
Eq Number Source # | Since: base-4.6.0.0 |
Eq SomeChar Source # | |
Eq SomeSymbol Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.TypeLits (==) :: SomeSymbol -> SomeSymbol -> Bool Source # (/=) :: SomeSymbol -> SomeSymbol -> Bool Source # | |
Eq SomeNat Source # | Since: base-4.7.0.0 |
Eq GeneralCategory Source # | Since: base-2.1 |
Defined in GHC.Internal.Unicode (==) :: GeneralCategory -> GeneralCategory -> Bool Source # (/=) :: GeneralCategory -> GeneralCategory -> Bool Source # | |
Eq Word16 Source # | Since: base-2.1 |
Eq Word32 Source # | Since: base-2.1 |
Eq Word64 Source # | Since: base-2.1 |
Eq Word8 Source # | Since: base-2.1 |
Eq Module Source # | |
Eq Ordering Source # | |
Eq TrName Source # | |
Eq TyCon Source # | |
Eq Integer # | |
Eq Natural # | |
Eq () Source # | |
Eq Bool Source # | |
Eq Char Source # | |
Eq Double Source # | Note that due to the presence of
Also note that
|
Eq Float Source # | Note that due to the presence of
Also note that
|
Eq Int Source # | |
Eq Word Source # | |
Eq (Chan a) Source # | Since: base-4.4.0.0 |
Eq (MutableByteArray s) Source # | Since: base-4.17.0.0 |
Defined in Data.Array.Byte (==) :: MutableByteArray s -> MutableByteArray s -> Bool Source # (/=) :: MutableByteArray s -> MutableByteArray s -> Bool Source # | |
Eq a => Eq (Complex a) Source # | Since: base-2.1 |
Eq a => Eq (First a) Source # | Since: base-4.9.0.0 |
Eq a => Eq (Last a) Source # | Since: base-4.9.0.0 |
Eq a => Eq (Max a) Source # | Since: base-4.9.0.0 |
Eq a => Eq (Min a) Source # | Since: base-4.9.0.0 |
Eq m => Eq (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup (==) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (/=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # | |
Eq a => Eq (NonEmpty a) Source # | Since: base-4.9.0.0 |
Eq (TVar a) Source # | Since: base-4.8.0.0 |
Eq a => Eq (And a) Source # | Since: base-4.16 |
Eq a => Eq (Iff a) Source # | Since: base-4.16 |
Eq a => Eq (Ior a) Source # | Since: base-4.16 |
Eq a => Eq (Xor a) Source # | Since: base-4.16 |
Eq a => Eq (Identity a) Source # | Since: base-4.8.0.0 |
Eq a => Eq (First a) Source # | Since: base-2.1 |
Eq a => Eq (Last a) Source # | Since: base-2.1 |
Eq a => Eq (Down a) Source # | Since: base-4.6.0.0 |
Eq a => Eq (Dual a) Source # | Since: base-2.1 |
Eq a => Eq (Product a) Source # | Since: base-2.1 |
Eq a => Eq (Sum a) Source # | Since: base-2.1 |
Eq (ConstPtr a) Source # | |
Eq (ForeignPtr a) Source # | Since: base-2.1 |
Defined in GHC.Internal.ForeignPtr (==) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (/=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # | |
Eq a => Eq (ZipList a) Source # | Since: base-4.7.0.0 |
Eq p => Eq (Par1 p) Source # | Since: base-4.7.0.0 |
Eq (IOPort a) Source # | Since: base-4.1.0.0 |
Eq (IORef a) Source # | Pointer equality. Since: base-4.0.0.0 |
Eq (MVar a) Source # | Compares the underlying pointers. Since: base-4.1.0.0 |
Eq (FunPtr a) Source # | |
Eq (Ptr a) Source # | Since: base-2.1 |
Eq a => Eq (Ratio a) Source # | Since: base-2.1 |
Eq (StablePtr a) Source # | Since: base-2.1 |
Eq (StableName a) Source # | Since: base-2.1 |
Defined in GHC.Internal.StableName (==) :: StableName a -> StableName a -> Bool Source # (/=) :: StableName a -> StableName a -> Bool Source # | |
Eq flag => Eq (TyVarBndr flag) Source # | |
Eq (SChar c) Source # | Since: base-4.19.0.0 |
Eq (SSymbol s) Source # | Since: base-4.19.0.0 |
Eq (SNat n) Source # | Since: base-4.19.0.0 |
Eq a => Eq (Maybe a) Source # | Since: base-2.1 |
Eq a => Eq (Solo a) Source # | |
Eq a => Eq [a] Source # | |
Eq (Fixed a) Source # | Since: base-2.1 |
Eq a => Eq (Arg a b) Source # | Note that
Since: base-4.9.0.0 |
(Ix i, Eq e) => Eq (Array i e) Source # | Since: base-2.1 |
(Eq a, Eq b) => Eq (Either a b) Source # | Since: base-2.1 |
Eq (Proxy s) Source # | Since: base-4.7.0.0 |
Eq (TypeRep a) Source # | Since: base-2.1 |
Eq (U1 p) Source # | Since: base-4.9.0.0 |
Eq (V1 p) Source # | Since: base-4.9.0.0 |
Eq (IOArray i e) Source # | Since: base-4.1.0.0 |
Eq (STRef s a) Source # | Pointer equality. Since: base-2.1 |
(Eq a, Eq b) => Eq (a, b) Source # | |
Eq (STArray s i e) Source # | Since: base-2.1 |
Eq a => Eq (Const a b) Source # | Since: base-4.9.0.0 |
Eq (f a) => Eq (Ap f a) Source # | Since: base-4.12.0.0 |
Eq (f a) => Eq (Alt f a) Source # | Since: base-4.8.0.0 |
Eq (Coercion a b) Source # | Since: base-4.7.0.0 |
Eq (a :~: b) Source # | Since: base-4.7.0.0 |
Eq (OrderingI a b) Source # | |
(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) Source # | Since: base-4.18.0.0 |
Defined in GHC.Internal.Generics (==) :: Generically1 f a -> Generically1 f a -> Bool Source # (/=) :: Generically1 f a -> Generically1 f a -> Bool Source # | |
Eq (f p) => Eq (Rec1 f p) Source # | Since: base-4.7.0.0 |
Eq (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 |
Eq (URec Char p) Source # | Since: base-4.9.0.0 |
Eq (URec Double p) Source # | Since: base-4.9.0.0 |
Eq (URec Float p) Source # | |
Eq (URec Int p) Source # | Since: base-4.9.0.0 |
Eq (URec Word p) Source # | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c) => Eq (a, b, c) Source # | |
(Eq (f a), Eq (g a)) => Eq (Product f g a) Source # | Since: base-4.18.0.0 |
(Eq (f a), Eq (g a)) => Eq (Sum f g a) Source # | Since: base-4.18.0.0 |
Eq (a :~~: b) Source # | Since: base-4.10.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) Source # | Since: base-4.7.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) Source # | Since: base-4.7.0.0 |
Eq c => Eq (K1 i c p) Source # | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) Source # | |
Eq (f (g a)) => Eq (Compose f g a) Source # | Since: base-4.18.0.0 |
Eq (f (g p)) => Eq ((f :.: g) p) Source # | Since: base-4.7.0.0 |
Eq (f p) => Eq (M1 i c f p) Source # | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
class Eq a => Ord a where Source #
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined datatype whose
constituent types are in Ord
. The declared order of the constructors in
the data declaration determines the ordering in derived Ord
instances. The
Ordering
datatype allows a single comparison to determine the precise
ordering of two objects.
Ord
, as defined by the Haskell report, implements a total order and has the
following properties:
- Comparability
x <= y || y <= x
=True
- Transitivity
- if
x <= y && y <= z
=True
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
The following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
max x y == if x >= y then x else y
=True
Note that (7.) and (8.) do not require min
and max
to return either of
their arguments. The result is merely required to equal one of the
arguments in terms of (==)
. Users who expect a stronger guarantee are advised
to write their own min and/or max functions.
The nuance of the above distinction is not always fully internalized by
developers, and in the past (tracing back to the Haskell 1.4 Report) the
specification for Ord
asserted the stronger property that (min x y, max x
y) = (x, y)
or (y, x)
, or in other words, that min
and max
will
return one of their arguments, using argument order as the tie-breaker if
the arguments are equal by comparison. A few list and
Foldable
functions have behavior that is best understood
with this assumption in mind: all variations of minimumBy
and maximumBy
(which can't use min
and max
in their implementations) are written such
that minimumBy
and compare
maximumBy
are respectively
equivalent to compare
minimum
and maximum
(which do use min
and max
) only if
min
and max
adhere to this tie-breaking convention. Otherwise, if there
are multiple least or largest elements in a container, minimum
and
maximum
may not return the same one that minimumBy
and
compare
maximumBy
do (though they should return something that is
equal). (This is relevant for types with non-extensional equality, like
compare
Arg
, but also in cases where the precise reference held
matters for memory-management reasons.) Unless there is a reason to deviate,
it is less confusing for implementors of Ord
to respect this same
convention (as the default definitions of min
and max
do).
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
compare :: a -> a -> Ordering Source #
(<) :: a -> a -> Bool infix 4 Source #
(<=) :: a -> a -> Bool infix 4 Source #
(>) :: a -> a -> Bool infix 4 Source #
Instances
Ord ByteArray Source # | Non-lexicographic ordering. This compares the lengths of the byte arrays first and uses a lexicographic ordering if the lengths are equal. Subject to change between major versions. Since: base-4.17.0.0 |
Defined in Data.Array.Byte | |
Ord BigNat # | |
Defined in GHC.Num.BigNat | |
Ord Void Source # | Since: base-4.8.0.0 |
Ord ByteOrder Source # | Since: base-4.11.0.0 |
Defined in GHC.Internal.ByteOrder | |
Ord ClosureType Source # | |
Defined in GHC.Internal.ClosureTypes compare :: ClosureType -> ClosureType -> Ordering Source # (<) :: ClosureType -> ClosureType -> Bool Source # (<=) :: ClosureType -> ClosureType -> Bool Source # (>) :: ClosureType -> ClosureType -> Bool Source # (>=) :: ClosureType -> ClosureType -> Bool Source # max :: ClosureType -> ClosureType -> ClosureType Source # min :: ClosureType -> ClosureType -> ClosureType Source # | |
Ord BlockReason Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync compare :: BlockReason -> BlockReason -> Ordering Source # (<) :: BlockReason -> BlockReason -> Bool Source # (<=) :: BlockReason -> BlockReason -> Bool Source # (>) :: BlockReason -> BlockReason -> Bool Source # (>=) :: BlockReason -> BlockReason -> Bool Source # max :: BlockReason -> BlockReason -> BlockReason Source # min :: BlockReason -> BlockReason -> BlockReason Source # | |
Ord ThreadId Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.Conc.Sync | |
Ord ThreadStatus Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync compare :: ThreadStatus -> ThreadStatus -> Ordering Source # (<) :: ThreadStatus -> ThreadStatus -> Bool Source # (<=) :: ThreadStatus -> ThreadStatus -> Bool Source # (>) :: ThreadStatus -> ThreadStatus -> Bool Source # (>=) :: ThreadStatus -> ThreadStatus -> Bool Source # max :: ThreadStatus -> ThreadStatus -> ThreadStatus Source # min :: ThreadStatus -> ThreadStatus -> ThreadStatus Source # | |
Ord All Source # | Since: base-2.1 |
Ord Any Source # | Since: base-2.1 |
Ord SomeTypeRep Source # | |
Defined in GHC.Internal.Data.Typeable.Internal compare :: SomeTypeRep -> SomeTypeRep -> Ordering Source # (<) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (<=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (>) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (>=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # max :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep Source # min :: SomeTypeRep -> SomeTypeRep -> SomeTypeRep Source # | |
Ord Unique Source # | |
Defined in GHC.Internal.Data.Unique | |
Ord Version Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Version | |
Ord TimeoutKey Source # | |
Defined in GHC.Internal.Event.TimeOut compare :: TimeoutKey -> TimeoutKey -> Ordering Source # (<) :: TimeoutKey -> TimeoutKey -> Bool Source # (<=) :: TimeoutKey -> TimeoutKey -> Bool Source # (>) :: TimeoutKey -> TimeoutKey -> Bool Source # (>=) :: TimeoutKey -> TimeoutKey -> Bool Source # max :: TimeoutKey -> TimeoutKey -> TimeoutKey Source # min :: TimeoutKey -> TimeoutKey -> TimeoutKey Source # | |
Ord Unique Source # | Since: base-4.4.0.0 |
Defined in GHC.Internal.Event.Unique | |
Ord ErrorCall Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Exception | |
Ord ArithException Source # | Since: base-3.0 |
Defined in GHC.Internal.Exception.Type compare :: ArithException -> ArithException -> Ordering Source # (<) :: ArithException -> ArithException -> Bool Source # (<=) :: ArithException -> ArithException -> Bool Source # (>) :: ArithException -> ArithException -> Bool Source # (>=) :: ArithException -> ArithException -> Bool Source # max :: ArithException -> ArithException -> ArithException Source # min :: ArithException -> ArithException -> ArithException Source # | |
Ord Fingerprint Source # | Since: base-4.4.0.0 |
Defined in GHC.Internal.Fingerprint.Type compare :: Fingerprint -> Fingerprint -> Ordering Source # (<) :: Fingerprint -> Fingerprint -> Bool Source # (<=) :: Fingerprint -> Fingerprint -> Bool Source # (>) :: Fingerprint -> Fingerprint -> Bool Source # (>=) :: Fingerprint -> Fingerprint -> Bool Source # max :: Fingerprint -> Fingerprint -> Fingerprint Source # min :: Fingerprint -> Fingerprint -> Fingerprint Source # | |
Ord CBool Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CClock Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CDouble Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CFloat Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CInt Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CIntMax Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CIntPtr Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CLLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CPtrdiff Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types compare :: CSUSeconds -> CSUSeconds -> Ordering Source # (<) :: CSUSeconds -> CSUSeconds -> Bool Source # (<=) :: CSUSeconds -> CSUSeconds -> Bool Source # (>) :: CSUSeconds -> CSUSeconds -> Bool Source # (>=) :: CSUSeconds -> CSUSeconds -> Bool Source # max :: CSUSeconds -> CSUSeconds -> CSUSeconds Source # min :: CSUSeconds -> CSUSeconds -> CSUSeconds Source # | |
Ord CShort Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSigAtomic Source # | |
Defined in GHC.Internal.Foreign.C.Types compare :: CSigAtomic -> CSigAtomic -> Ordering Source # (<) :: CSigAtomic -> CSigAtomic -> Bool Source # (<=) :: CSigAtomic -> CSigAtomic -> Bool Source # (>) :: CSigAtomic -> CSigAtomic -> Bool Source # (>=) :: CSigAtomic -> CSigAtomic -> Bool Source # max :: CSigAtomic -> CSigAtomic -> CSigAtomic Source # min :: CSigAtomic -> CSigAtomic -> CSigAtomic Source # | |
Ord CSize Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CTime Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUChar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUInt Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUIntMax Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUIntPtr Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CULLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CULong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUShort Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CWchar Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord IntPtr Source # | |
Defined in GHC.Internal.Foreign.Ptr | |
Ord WordPtr Source # | |
Defined in GHC.Internal.Foreign.Ptr | |
Ord Associativity Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Generics compare :: Associativity -> Associativity -> Ordering Source # (<) :: Associativity -> Associativity -> Bool Source # (<=) :: Associativity -> Associativity -> Bool Source # (>) :: Associativity -> Associativity -> Bool Source # (>=) :: Associativity -> Associativity -> Bool Source # max :: Associativity -> Associativity -> Associativity Source # min :: Associativity -> Associativity -> Associativity Source # | |
Ord DecidedStrictness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: DecidedStrictness -> DecidedStrictness -> Ordering Source # (<) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # | |
Ord Fixity Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Generics | |
Ord SourceStrictness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: SourceStrictness -> SourceStrictness -> Ordering Source # (<) :: SourceStrictness -> SourceStrictness -> Bool Source # (<=) :: SourceStrictness -> SourceStrictness -> Bool Source # (>) :: SourceStrictness -> SourceStrictness -> Bool Source # (>=) :: SourceStrictness -> SourceStrictness -> Bool Source # max :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # min :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # | |
Ord SourceUnpackedness Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering Source # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # | |
Ord SeekMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Device | |
Ord ArrayException Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception compare :: ArrayException -> ArrayException -> Ordering Source # (<) :: ArrayException -> ArrayException -> Bool Source # (<=) :: ArrayException -> ArrayException -> Bool Source # (>) :: ArrayException -> ArrayException -> Bool Source # (>=) :: ArrayException -> ArrayException -> Bool Source # max :: ArrayException -> ArrayException -> ArrayException Source # min :: ArrayException -> ArrayException -> ArrayException Source # | |
Ord AsyncException Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception compare :: AsyncException -> AsyncException -> Ordering Source # (<) :: AsyncException -> AsyncException -> Bool Source # (<=) :: AsyncException -> AsyncException -> Bool Source # (>) :: AsyncException -> AsyncException -> Bool Source # (>=) :: AsyncException -> AsyncException -> Bool Source # max :: AsyncException -> AsyncException -> AsyncException Source # min :: AsyncException -> AsyncException -> AsyncException Source # | |
Ord ExitCode Source # | |
Defined in GHC.Internal.IO.Exception | |
Ord BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: BufferMode -> BufferMode -> Ordering Source # (<) :: BufferMode -> BufferMode -> Bool Source # (<=) :: BufferMode -> BufferMode -> Bool Source # (>) :: BufferMode -> BufferMode -> Bool Source # (>=) :: BufferMode -> BufferMode -> Bool Source # max :: BufferMode -> BufferMode -> BufferMode Source # min :: BufferMode -> BufferMode -> BufferMode Source # | |
Ord Newline Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Ord NewlineMode Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: NewlineMode -> NewlineMode -> Ordering Source # (<) :: NewlineMode -> NewlineMode -> Bool Source # (<=) :: NewlineMode -> NewlineMode -> Bool Source # (>) :: NewlineMode -> NewlineMode -> Bool Source # (>=) :: NewlineMode -> NewlineMode -> Bool Source # max :: NewlineMode -> NewlineMode -> NewlineMode Source # min :: NewlineMode -> NewlineMode -> NewlineMode Source # | |
Ord IOMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.IOMode | |
Ord Int16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Int | |
Ord Int32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Int | |
Ord Int64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Int | |
Ord Int8 Source # | Since: base-2.1 |
Ord Extension Source # | |
Defined in GHC.Internal.LanguageExtensions | |
Ord CBlkCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CBlkSize Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CCc Source # | |
Ord CClockId Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CDev Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CFsBlkCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CFsFilCnt Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CGid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CId Source # | |
Ord CIno Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CKey Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CMode Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CNfds Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CNlink Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord COff Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CPid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CRLim Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSocklen Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSpeed Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CSsize Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CTcflag Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CTimer Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord CUid Source # | |
Defined in GHC.Internal.System.Posix.Types | |
Ord Fd Source # | |
Ord AnnLookup Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord AnnTarget Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Bang Source # | |
Ord BndrVis Source # | |
Ord Body Source # | |
Ord Bytes Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Callconv Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Clause Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Con Source # | |
Ord Dec Source # | |
Ord DecidedStrictness Source # | |
Defined in GHC.Internal.TH.Syntax compare :: DecidedStrictness -> DecidedStrictness -> Ordering Source # (<) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness Source # | |
Ord DerivClause Source # | |
Defined in GHC.Internal.TH.Syntax compare :: DerivClause -> DerivClause -> Ordering Source # (<) :: DerivClause -> DerivClause -> Bool Source # (<=) :: DerivClause -> DerivClause -> Bool Source # (>) :: DerivClause -> DerivClause -> Bool Source # (>=) :: DerivClause -> DerivClause -> Bool Source # max :: DerivClause -> DerivClause -> DerivClause Source # min :: DerivClause -> DerivClause -> DerivClause Source # | |
Ord DerivStrategy Source # | |
Defined in GHC.Internal.TH.Syntax compare :: DerivStrategy -> DerivStrategy -> Ordering Source # (<) :: DerivStrategy -> DerivStrategy -> Bool Source # (<=) :: DerivStrategy -> DerivStrategy -> Bool Source # (>) :: DerivStrategy -> DerivStrategy -> Bool Source # (>=) :: DerivStrategy -> DerivStrategy -> Bool Source # max :: DerivStrategy -> DerivStrategy -> DerivStrategy Source # min :: DerivStrategy -> DerivStrategy -> DerivStrategy Source # | |
Ord DocLoc Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Exp Source # | |
Ord FamilyResultSig Source # | |
Defined in GHC.Internal.TH.Syntax compare :: FamilyResultSig -> FamilyResultSig -> Ordering Source # (<) :: FamilyResultSig -> FamilyResultSig -> Bool Source # (<=) :: FamilyResultSig -> FamilyResultSig -> Bool Source # (>) :: FamilyResultSig -> FamilyResultSig -> Bool Source # (>=) :: FamilyResultSig -> FamilyResultSig -> Bool Source # max :: FamilyResultSig -> FamilyResultSig -> FamilyResultSig Source # min :: FamilyResultSig -> FamilyResultSig -> FamilyResultSig Source # | |
Ord Fixity Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord FixityDirection Source # | |
Defined in GHC.Internal.TH.Syntax compare :: FixityDirection -> FixityDirection -> Ordering Source # (<) :: FixityDirection -> FixityDirection -> Bool Source # (<=) :: FixityDirection -> FixityDirection -> Bool Source # (>) :: FixityDirection -> FixityDirection -> Bool Source # (>=) :: FixityDirection -> FixityDirection -> Bool Source # max :: FixityDirection -> FixityDirection -> FixityDirection Source # min :: FixityDirection -> FixityDirection -> FixityDirection Source # | |
Ord Foreign Source # | |
Ord FunDep Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Guard Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Info Source # | |
Ord InjectivityAnn Source # | |
Defined in GHC.Internal.TH.Syntax compare :: InjectivityAnn -> InjectivityAnn -> Ordering Source # (<) :: InjectivityAnn -> InjectivityAnn -> Bool Source # (<=) :: InjectivityAnn -> InjectivityAnn -> Bool Source # (>) :: InjectivityAnn -> InjectivityAnn -> Bool Source # (>=) :: InjectivityAnn -> InjectivityAnn -> Bool Source # max :: InjectivityAnn -> InjectivityAnn -> InjectivityAnn Source # min :: InjectivityAnn -> InjectivityAnn -> InjectivityAnn Source # | |
Ord Inline Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Lit Source # | |
Ord Loc Source # | |
Ord Match Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord ModName Source # | |
Ord Module Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord ModuleInfo Source # | |
Defined in GHC.Internal.TH.Syntax compare :: ModuleInfo -> ModuleInfo -> Ordering Source # (<) :: ModuleInfo -> ModuleInfo -> Bool Source # (<=) :: ModuleInfo -> ModuleInfo -> Bool Source # (>) :: ModuleInfo -> ModuleInfo -> Bool Source # (>=) :: ModuleInfo -> ModuleInfo -> Bool Source # max :: ModuleInfo -> ModuleInfo -> ModuleInfo Source # min :: ModuleInfo -> ModuleInfo -> ModuleInfo Source # | |
Ord Name Source # | |
Ord NameFlavour Source # | |
Defined in GHC.Internal.TH.Syntax compare :: NameFlavour -> NameFlavour -> Ordering Source # (<) :: NameFlavour -> NameFlavour -> Bool Source # (<=) :: NameFlavour -> NameFlavour -> Bool Source # (>) :: NameFlavour -> NameFlavour -> Bool Source # (>=) :: NameFlavour -> NameFlavour -> Bool Source # max :: NameFlavour -> NameFlavour -> NameFlavour Source # min :: NameFlavour -> NameFlavour -> NameFlavour Source # | |
Ord NameSpace Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord NamespaceSpecifier Source # | |
Defined in GHC.Internal.TH.Syntax compare :: NamespaceSpecifier -> NamespaceSpecifier -> Ordering Source # (<) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # (<=) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # (>) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # (>=) :: NamespaceSpecifier -> NamespaceSpecifier -> Bool Source # max :: NamespaceSpecifier -> NamespaceSpecifier -> NamespaceSpecifier Source # min :: NamespaceSpecifier -> NamespaceSpecifier -> NamespaceSpecifier Source # | |
Ord OccName Source # | |
Ord Overlap Source # | |
Ord Pat Source # | |
Ord PatSynArgs Source # | |
Defined in GHC.Internal.TH.Syntax compare :: PatSynArgs -> PatSynArgs -> Ordering Source # (<) :: PatSynArgs -> PatSynArgs -> Bool Source # (<=) :: PatSynArgs -> PatSynArgs -> Bool Source # (>) :: PatSynArgs -> PatSynArgs -> Bool Source # (>=) :: PatSynArgs -> PatSynArgs -> Bool Source # max :: PatSynArgs -> PatSynArgs -> PatSynArgs Source # min :: PatSynArgs -> PatSynArgs -> PatSynArgs Source # | |
Ord PatSynDir Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Phases Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord PkgName Source # | |
Ord Pragma Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Range Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Role Source # | |
Ord RuleBndr Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord RuleMatch Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Safety Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord SourceStrictness Source # | |
Defined in GHC.Internal.TH.Syntax compare :: SourceStrictness -> SourceStrictness -> Ordering Source # (<) :: SourceStrictness -> SourceStrictness -> Bool Source # (<=) :: SourceStrictness -> SourceStrictness -> Bool Source # (>) :: SourceStrictness -> SourceStrictness -> Bool Source # (>=) :: SourceStrictness -> SourceStrictness -> Bool Source # max :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # min :: SourceStrictness -> SourceStrictness -> SourceStrictness Source # | |
Ord SourceUnpackedness Source # | |
Defined in GHC.Internal.TH.Syntax compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering Source # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness Source # | |
Ord Specificity Source # | |
Defined in GHC.Internal.TH.Syntax compare :: Specificity -> Specificity -> Ordering Source # (<) :: Specificity -> Specificity -> Bool Source # (<=) :: Specificity -> Specificity -> Bool Source # (>) :: Specificity -> Specificity -> Bool Source # (>=) :: Specificity -> Specificity -> Bool Source # max :: Specificity -> Specificity -> Specificity Source # min :: Specificity -> Specificity -> Specificity Source # | |
Ord Stmt Source # | |
Ord TyLit Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord TySynEqn Source # | |
Defined in GHC.Internal.TH.Syntax | |
Ord Type Source # | |
Ord TypeFamilyHead Source # | |
Defined in GHC.Internal.TH.Syntax compare :: TypeFamilyHead -> TypeFamilyHead -> Ordering Source # (<) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # (<=) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # (>) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # (>=) :: TypeFamilyHead -> TypeFamilyHead -> Bool Source # max :: TypeFamilyHead -> TypeFamilyHead -> TypeFamilyHead Source # min :: TypeFamilyHead -> TypeFamilyHead -> TypeFamilyHead Source # | |
Ord SomeChar Source # | |
Defined in GHC.Internal.TypeLits | |
Ord SomeSymbol Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.TypeLits compare :: SomeSymbol -> SomeSymbol -> Ordering Source # (<) :: SomeSymbol -> SomeSymbol -> Bool Source # (<=) :: SomeSymbol -> SomeSymbol -> Bool Source # (>) :: SomeSymbol -> SomeSymbol -> Bool Source # (>=) :: SomeSymbol -> SomeSymbol -> Bool Source # max :: SomeSymbol -> SomeSymbol -> SomeSymbol Source # min :: SomeSymbol -> SomeSymbol -> SomeSymbol Source # | |
Ord SomeNat Source # | Since: base-4.7.0.0 |
Ord GeneralCategory Source # | Since: base-2.1 |
Defined in GHC.Internal.Unicode compare :: GeneralCategory -> GeneralCategory -> Ordering Source # (<) :: GeneralCategory -> GeneralCategory -> Bool Source # (<=) :: GeneralCategory -> GeneralCategory -> Bool Source # (>) :: GeneralCategory -> GeneralCategory -> Bool Source # (>=) :: GeneralCategory -> GeneralCategory -> Bool Source # max :: GeneralCategory -> GeneralCategory -> GeneralCategory Source # min :: GeneralCategory -> GeneralCategory -> GeneralCategory Source # | |
Ord Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Ord Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Ord Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Ord Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Ord Ordering Source # | |
Defined in GHC.Classes | |
Ord TyCon Source # | |
Defined in GHC.Classes | |
Ord Integer # | |
Ord Natural # | |
Ord () Source # | |
Ord Bool Source # | |
Ord Char Source # | |
Ord Double Source # | IEEE 754 IEEE 754-2008, section 5.11 requires that if at least one of arguments of
IEEE 754-2008, section 5.10 defines Thus, users must be extremely cautious when using Moving further, the behaviour of IEEE 754-2008 compliant |
Defined in GHC.Classes | |
Ord Float Source # | See |
Defined in GHC.Classes | |
Ord Int Source # | |
Ord Word Source # | |
Ord a => Ord (First a) Source # | Since: base-4.9.0.0 |
Ord a => Ord (Last a) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Ord a => Ord (Max a) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Ord a => Ord (Min a) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Ord m => Ord (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup compare :: WrappedMonoid m -> WrappedMonoid m -> Ordering Source # (<) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (<=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (>) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (>=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # max :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # min :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # | |
Ord a => Ord (NonEmpty a) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Base compare :: NonEmpty a -> NonEmpty a -> Ordering Source # (<) :: NonEmpty a -> NonEmpty a -> Bool Source # (<=) :: NonEmpty a -> NonEmpty a -> Bool Source # (>) :: NonEmpty a -> NonEmpty a -> Bool Source # (>=) :: NonEmpty a -> NonEmpty a -> Bool Source # | |
Ord a => Ord (Identity a) Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Functor.Identity compare :: Identity a -> Identity a -> Ordering Source # (<) :: Identity a -> Identity a -> Bool Source # (<=) :: Identity a -> Identity a -> Bool Source # (>) :: Identity a -> Identity a -> Bool Source # (>=) :: Identity a -> Identity a -> Bool Source # | |
Ord a => Ord (First a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Monoid | |
Ord a => Ord (Last a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Monoid | |
Ord a => Ord (Down a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Data.Ord | |
Ord a => Ord (Dual a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Product a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Sum a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord (ConstPtr a) Source # | |
Defined in GHC.Internal.Foreign.C.ConstPtr compare :: ConstPtr a -> ConstPtr a -> Ordering Source # (<) :: ConstPtr a -> ConstPtr a -> Bool Source # (<=) :: ConstPtr a -> ConstPtr a -> Bool Source # (>) :: ConstPtr a -> ConstPtr a -> Bool Source # (>=) :: ConstPtr a -> ConstPtr a -> Bool Source # | |
Ord (ForeignPtr a) Source # | Since: base-2.1 |
Defined in GHC.Internal.ForeignPtr compare :: ForeignPtr a -> ForeignPtr a -> Ordering Source # (<) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (<=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # max :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # min :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # | |
Ord a => Ord (ZipList a) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Functor.ZipList | |
Ord p => Ord (Par1 p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
Ord (FunPtr a) Source # | |
Defined in GHC.Internal.Ptr | |
Ord (Ptr a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Ptr | |
Integral a => Ord (Ratio a) Source # | Since: base-2.0.1 |
Ord flag => Ord (TyVarBndr flag) Source # | |
Defined in GHC.Internal.TH.Syntax compare :: TyVarBndr flag -> TyVarBndr flag -> Ordering Source # (<) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source # (<=) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source # (>) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source # (>=) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source # max :: TyVarBndr flag -> TyVarBndr flag -> TyVarBndr flag Source # min :: TyVarBndr flag -> TyVarBndr flag -> TyVarBndr flag Source # | |
Ord (SChar c) Source # | Since: base-4.19.0.0 |
Ord (SSymbol s) Source # | Since: base-4.19.0.0 |
Defined in GHC.Internal.TypeLits | |
Ord (SNat n) Source # | Since: base-4.19.0.0 |
Defined in GHC.Internal.TypeNats | |
Ord a => Ord (Maybe a) Source # | Since: base-2.1 |
Ord a => Ord (Solo a) Source # | |
Defined in GHC.Classes | |
Ord a => Ord [a] Source # | |
Ord (Fixed a) Source # | Since: base-2.1 |
Ord a => Ord (Arg a b) Source # | Note that Since: base-4.9.0.0 |
(Ix i, Ord e) => Ord (Array i e) Source # | Since: base-2.1 |
Defined in GHC.Internal.Arr | |
(Ord a, Ord b) => Ord (Either a b) Source # | Since: base-2.1 |
Defined in GHC.Internal.Data.Either compare :: Either a b -> Either a b -> Ordering Source # (<) :: Either a b -> Either a b -> Bool Source # (<=) :: Either a b -> Either a b -> Bool Source # (>) :: Either a b -> Either a b -> Bool Source # (>=) :: Either a b -> Either a b -> Bool Source # | |
Ord (Proxy s) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Data.Proxy | |
Ord (TypeRep a) Source # | Since: base-4.4.0.0 |
Defined in GHC.Internal.Data.Typeable.Internal | |
Ord (U1 p) Source # | Since: base-4.7.0.0 |
Ord (V1 p) Source # | Since: base-4.9.0.0 |
(Ord a, Ord b) => Ord (a, b) Source # | |
Defined in GHC.Classes | |
Ord a => Ord (Const a b) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Data.Functor.Const | |
Ord (f a) => Ord (Ap f a) Source # | Since: base-4.12.0.0 |
Defined in GHC.Internal.Data.Monoid | |
Ord (f a) => Ord (Alt f a) Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord (Coercion a b) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Coercion compare :: Coercion a b -> Coercion a b -> Ordering Source # (<) :: Coercion a b -> Coercion a b -> Bool Source # (<=) :: Coercion a b -> Coercion a b -> Bool Source # (>) :: Coercion a b -> Coercion a b -> Bool Source # (>=) :: Coercion a b -> Coercion a b -> Bool Source # max :: Coercion a b -> Coercion a b -> Coercion a b Source # min :: Coercion a b -> Coercion a b -> Coercion a b Source # | |
Ord (a :~: b) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Data.Type.Equality | |
(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) Source # | Since: base-4.18.0.0 |
Defined in GHC.Internal.Generics compare :: Generically1 f a -> Generically1 f a -> Ordering Source # (<) :: Generically1 f a -> Generically1 f a -> Bool Source # (<=) :: Generically1 f a -> Generically1 f a -> Bool Source # (>) :: Generically1 f a -> Generically1 f a -> Bool Source # (>=) :: Generically1 f a -> Generically1 f a -> Bool Source # max :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # min :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # | |
Ord (f p) => Ord (Rec1 f p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
Ord (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |
Ord (URec Char p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: URec Char p -> URec Char p -> Ordering Source # (<) :: URec Char p -> URec Char p -> Bool Source # (<=) :: URec Char p -> URec Char p -> Bool Source # (>) :: URec Char p -> URec Char p -> Bool Source # (>=) :: URec Char p -> URec Char p -> Bool Source # | |
Ord (URec Double p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: URec Double p -> URec Double p -> Ordering Source # (<) :: URec Double p -> URec Double p -> Bool Source # (<=) :: URec Double p -> URec Double p -> Bool Source # (>) :: URec Double p -> URec Double p -> Bool Source # (>=) :: URec Double p -> URec Double p -> Bool Source # max :: URec Double p -> URec Double p -> URec Double p Source # min :: URec Double p -> URec Double p -> URec Double p Source # | |
Ord (URec Float p) Source # | |
Defined in GHC.Internal.Generics compare :: URec Float p -> URec Float p -> Ordering Source # (<) :: URec Float p -> URec Float p -> Bool Source # (<=) :: URec Float p -> URec Float p -> Bool Source # (>) :: URec Float p -> URec Float p -> Bool Source # (>=) :: URec Float p -> URec Float p -> Bool Source # max :: URec Float p -> URec Float p -> URec Float p Source # min :: URec Float p -> URec Float p -> URec Float p Source # | |
Ord (URec Int p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics compare :: URec Int p -> URec Int p -> Ordering Source # (<) :: URec Int p -> URec Int p -> Bool Source # (<=) :: URec Int p -> URec Int p -> Bool Source # (>) :: URec Int p -> URec Int p -> Bool Source # (>=) :: URec Int p -> URec Int p -> Bool Source # | |
Ord (URec Word p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.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 # | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) Source # | |
Defined in GHC.Classes | |
(Ord (f a), Ord (g a)) => Ord (Product f g a) Source # | Since: base-4.18.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 # | |
(Ord (f a), Ord (g a)) => Ord (Sum f g a) Source # | Since: base-4.18.0.0 |
Defined in Data.Functor.Sum | |
Ord (a :~~: b) Source # | Since: base-4.10.0.0 |
Defined in GHC.Internal.Data.Type.Equality compare :: (a :~~: b) -> (a :~~: b) -> Ordering Source # (<) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (<=) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (>) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (>=) :: (a :~~: b) -> (a :~~: b) -> Bool Source # | |
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics compare :: (f :*: g) p -> (f :*: g) p -> Ordering Source # (<) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (<=) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (>) :: (f :*: g) p -> (f :*: g) p -> Bool Source # (>=) :: (f :*: g) p -> (f :*: g) p -> Bool Source # | |
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics compare :: (f :+: g) p -> (f :+: g) p -> Ordering Source # (<) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (<=) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (>) :: (f :+: g) p -> (f :+: g) p -> Bool Source # (>=) :: (f :+: g) p -> (f :+: g) p -> Bool Source # | |
Ord c => Ord (K1 i c p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering Source # (<) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (>) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source # min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source # | |
Ord (f (g a)) => Ord (Compose f g a) Source # | Since: base-4.18.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 # | |
Ord (f (g p)) => Ord ((f :.: g) p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics compare :: (f :.: g) p -> (f :.: g) p -> Ordering Source # (<) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (<=) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (>) :: (f :.: g) p -> (f :.: g) p -> Bool Source # (>=) :: (f :.: g) p -> (f :.: g) p -> Bool Source # | |
Ord (f p) => Ord (M1 i c f p) Source # | Since: base-4.7.0.0 |
Defined in GHC.Internal.Generics compare :: M1 i c f p -> M1 i c f p -> Ordering Source # (<) :: M1 i c f p -> M1 i c f p -> Bool Source # (<=) :: M1 i c f p -> M1 i c f p -> Bool Source # (>) :: M1 i c f p -> M1 i c f p -> Bool Source # (>=) :: M1 i c f p -> M1 i c f p -> Bool Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering Source # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering Source # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering Source # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source # max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source # min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source # min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source # min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source # min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # |
Monomorphic equality operators
C Strings
unpackCString# :: Addr# -> [Char] Source #
unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a Source #
cstringLength# :: Addr# -> Int# Source #
Compute the length of a NUL-terminated string. This address
must refer to immutable memory. GHC includes a built-in rule for
constant folding when the argument is a statically-known literal.
That is, a core-to-core pass reduces the expression
cstringLength# "hello"#
to the constant 5#
.
unpackCStringUtf8# :: Addr# -> [Char] Source #
unpackFoldrCStringUtf8# :: Addr# -> (Char -> a -> a) -> a -> a Source #
Magic combinators
The call inline f
arranges that f
is inlined, regardless of
its size. More precisely, the call inline f
rewrites to the
right-hand side of f
's definition. This allows the programmer to
control inlining from a particular call site rather than the
definition site of the function (c.f. INLINE
pragmas).
This inlining occurs regardless of the argument to the call or the
size of f
's definition; it is unconditional. The main caveat is
that f
's definition must be visible to the compiler; it is
therefore recommended to mark the function with an INLINABLE
pragma at its definition so that GHC guarantees to record its
unfolding regardless of size.
If no inlining takes place, the inline
function expands to the
identity function in Phase zero, so its use imposes no overhead.
The call noinline f
arranges that f
will not be inlined.
It is removed during CorePrep so that its use imposes no overhead
(besides the fact that it blocks inlining.)
The lazy
function restrains strictness analysis a little. The
call lazy e
means the same as e
, but lazy
has a magical
property so far as strictness analysis is concerned: it is lazy in
its first argument, even though its semantics is strict. After
strictness analysis has run, calls to lazy
are inlined to be the
identity function.
This behaviour is occasionally useful when controlling evaluation
order. Notably, lazy
is used in the library definition of
par
:
par :: a -> b -> b par x y = case (par# x) of _ -> lazy y
If lazy
were not lazy, par
would look strict in
y
which would defeat the whole purpose of par
.
oneShot :: (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.
runRW# :: (State# RealWorld -> o) -> o Source #
Apply a function to a
token. When manually applying
a function to State#
RealWorld
realWorld#
, it is necessary to use NOINLINE
to prevent
semantically undesirable floating. runRW#
is inlined, but only very late
in compilation after all floating is complete.
class DataToTag (a :: TYPE ('BoxedRep lev)) where Source #
evaluates its argument and returns the index
(starting at zero) of the constructor used to produce that
argument. Any algebraic data type with all of its constructors
in scope may be used with dataToTag#
dataToTag#
.
>>>
dataToTag# (Left ())
0#>>>
dataToTag# (Right undefined)
1#
dataToTag# :: a -> Int# Source #
class WithDict cls meth where Source #
The constraint
can be solved when evidence for
the constraint WithDict
cls methcls
can be provided in the form of a dictionary of
type meth
. This requires cls
to be a class constraint whose single
method has type meth
.
For more (important) details on how this works, see
Note [withDict]
in GHC.Tc.Instance.Class in GHC.
Since: ghc-prim-0.9.0
withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r Source #
Functions over Bool
Uninhabited data type
Since: base-4.8.0.0
Instances
Semigroup Void Source # | Since: base-4.9.0.0 |
Data Void Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void Source # toConstr :: Void -> Constr Source # dataTypeOf :: Void -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) Source # gmapT :: (forall b. Data b => b -> b) -> Void -> Void Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void Source # | |
Exception Void Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Exception.Type toException :: Void -> SomeException Source # fromException :: SomeException -> Maybe Void Source # displayException :: Void -> String Source # backtraceDesired :: Void -> Bool Source # | |
Generic Void Source # | |
Ix Void Source # | Since: base-4.8.0.0 |
Read Void Source # | Reading a Since: base-4.8.0.0 |
Show Void Source # | Since: base-4.8.0.0 |
Eq Void Source # | Since: base-4.8.0.0 |
Ord Void Source # | Since: base-4.8.0.0 |
Lift Void Source # | Since: template-haskell-2.15.0.0 |
type Rep Void Source # | Since: base-4.8.0.0 |
Since Void
values logically don't exist, this witnesses the
logical reasoning tool of "ex falso quodlibet".
>>>
let x :: Either Void Int; x = Right 5
>>>
:{
case x of Right r -> r Left l -> absurd l :} 5
Since: base-4.8.0.0
Semigroup/Monoid
class Semigroup a where Source #
The class of semigroups (types with an associative binary operation).
Instances should satisfy the following:
You can alternatively define sconcat
instead of (<>
), in which case the
laws are:
Since: base-4.9.0.0
(<>) :: a -> a -> a infixr 6 Source #
An associative operation.
Examples
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
>>>
Just [1, 2, 3] <> Just [4, 5, 6]
Just [1,2,3,4,5,6]
>>>
putStr "Hello, " <> putStrLn "World!"
Hello, World!
sconcat :: NonEmpty a -> a Source #
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
Examples
For the following examples, we will assume that we have:
>>>
import Data.List.NonEmpty (NonEmpty (..))
>>>
sconcat $ "Hello" :| [" ", "Haskell", "!"]
"Hello Haskell!"
>>>
sconcat $ Just [1, 2, 3] :| [Nothing, Just [4, 5, 6]]
Just [1,2,3,4,5,6]
>>>
sconcat $ Left 1 :| [Right 2, Left 3, Right 4]
Right 2
stimes :: Integral b => b -> a -> a Source #
Repeat a value n
times.
The default definition will raise an exception for a multiplier that is <= 0
.
This may be overridden with an implementation that is total. For monoids
it is preferred to use stimesMonoid
.
By making this a member of the class, idempotent semigroups
and monoids can upgrade this to execute in \(\mathcal{O}(1)\) by
picking stimes =
or stimesIdempotent
stimes =
respectively.stimesIdempotentMonoid
Examples
>>>
stimes 4 [1]
[1,1,1,1]
>>>
stimes 5 (putStr "hi!")
hi!hi!hi!hi!hi!
>>>
stimes 3 (Right ":)")
Right ":)"
Instances
Semigroup ByteArray Source # | Since: base-4.17.0.0 |
Semigroup Void Source # | Since: base-4.9.0.0 |
Semigroup All Source # | Since: base-4.9.0.0 |
Semigroup Any Source # | Since: base-4.9.0.0 |
Semigroup Event Source # | Since: base-4.10.0.0 |
Semigroup EventLifetime Source # | Since: base-4.11.0.0 |
Semigroup Lifetime Source # | Since: base-4.10.0.0 |
Semigroup ExceptionContext Source # | |
Defined in GHC.Internal.Exception.Context (<>) :: ExceptionContext -> ExceptionContext -> ExceptionContext Source # sconcat :: NonEmpty ExceptionContext -> ExceptionContext Source # stimes :: Integral b => b -> ExceptionContext -> ExceptionContext Source # | |
Semigroup Ordering Source # | Since: base-4.9.0.0 |
Semigroup () Source # | Since: base-4.9.0.0 |
Semigroup (Comparison a) Source # |
(<>) :: Comparison a -> Comparison a -> Comparison a Comparison cmp <> Comparison cmp' = Comparison a a' -> cmp a a' <> cmp a a' |
Defined in Data.Functor.Contravariant (<>) :: Comparison a -> Comparison a -> Comparison a Source # sconcat :: NonEmpty (Comparison a) -> Comparison a Source # stimes :: Integral b => b -> Comparison a -> Comparison a Source # | |
Semigroup (Equivalence a) Source # |
(<>) :: Equivalence a -> Equivalence a -> Equivalence a Equivalence equiv <> Equivalence equiv' = Equivalence a b -> equiv a b && equiv' a b |
Defined in Data.Functor.Contravariant (<>) :: Equivalence a -> Equivalence a -> Equivalence a Source # sconcat :: NonEmpty (Equivalence a) -> Equivalence a Source # stimes :: Integral b => b -> Equivalence a -> Equivalence a Source # | |
Semigroup (Predicate a) Source # |
(<>) :: Predicate a -> Predicate a -> Predicate a Predicate pred <> Predicate pred' = Predicate a -> pred a && pred' a |
Semigroup (First a) Source # | Since: base-4.9.0.0 |
Semigroup (Last a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Min a) Source # | Since: base-4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m Source # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m Source # | |
Semigroup (NonEmpty a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (STM a) Source # | Since: base-4.17.0.0 |
Bits a => Semigroup (And a) Source # | Since: base-4.16 |
FiniteBits a => Semigroup (Iff a) Source # | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
Bits a => Semigroup (Ior a) Source # | Since: base-4.16 |
Bits a => Semigroup (Xor a) Source # | Since: base-4.16 |
Semigroup a => Semigroup (Identity a) Source # | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) Source # | Since: base-4.11.0.0 |
Ord a => Semigroup (Min a) Source # | Since: base-4.11.0.0 |
Semigroup (First a) Source # | Since: base-4.9.0.0 |
Semigroup (Last a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Down a) Source # | Since: base-4.11.0.0 |
Semigroup a => Semigroup (Dual a) Source # | Since: base-4.9.0.0 |
Semigroup (Endo a) Source # | Since: base-4.9.0.0 |
Num a => Semigroup (Product a) Source # | Since: base-4.9.0.0 |
Num a => Semigroup (Sum a) Source # | Since: base-4.9.0.0 |
(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics (<>) :: Generically a -> Generically a -> Generically a Source # sconcat :: NonEmpty (Generically a) -> Generically a Source # stimes :: Integral b => b -> Generically a -> Generically a Source # | |
Semigroup p => Semigroup (Par1 p) Source # | Since: base-4.12.0.0 |
Semigroup a => Semigroup (Q a) Source # | Since: ghc-internal-2.17.0.0 |
Semigroup a => Semigroup (IO a) Source # | Since: base-4.10.0.0 |
Semigroup a => Semigroup (Maybe a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Solo a) Source # | Since: base-4.15 |
Semigroup [a] Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Op a b) Source # |
(<>) :: Op a b -> Op a b -> Op a b Op f <> Op g = Op a -> f a <> g a |
Semigroup (Either a b) Source # | Since: base-4.9.0.0 |
Semigroup (Proxy s) Source # | Since: base-4.9.0.0 |
Semigroup (U1 p) Source # | Since: base-4.12.0.0 |
Semigroup (V1 p) Source # | Since: base-4.12.0.0 |
Semigroup a => Semigroup (ST s a) Source # | Since: base-4.11.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) Source # | Since: base-4.9.0.0 |
Semigroup b => Semigroup (a -> b) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) Source # | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | Since: base-4.12.0.0 |
Alternative f => Semigroup (Alt f a) Source # | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (Rec1 f p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source # | Since: base-4.9.0.0 |
(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) Source # | Since: base-4.16.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) Source # | Since: base-4.12.0.0 |
Semigroup c => Semigroup (K1 i c p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source # | Since: base-4.9.0.0 |
Semigroup (f (g a)) => Semigroup (Compose f g a) Source # | Since: base-4.16.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) Source # | Since: base-4.12.0.0 |
Semigroup (f p) => Semigroup (M1 i c f p) Source # | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source # | Since: base-4.9.0.0 |
class Semigroup a => Monoid a where Source #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
You can alternatively define mconcat
instead of mempty
, in which case the
laws are:
- Unit
mconcat
(pure
x) = x- Multiplication
mconcat
(join
xss) =mconcat
(fmap
mconcat
xss)- Subclass
mconcat
(toList
xs) =sconcat
xs
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
Examples
>>>
"Hello world" <> mempty
"Hello world"
>>>
mempty <> [1, 2, 3]
[1,2,3]
mappend :: a -> a -> a Source #
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid ByteArray Source # | Since: base-4.17.0.0 |
Monoid All Source # | Since: base-2.1 |
Monoid Any Source # | Since: base-2.1 |
Monoid Event Source # | Since: base-4.4.0.0 |
Monoid EventLifetime Source # | Since: base-4.8.0.0 |
Monoid Lifetime Source # |
Since: base-4.8.0.0 |
Monoid ExceptionContext Source # | |
Defined in GHC.Internal.Exception.Context | |
Monoid Ordering Source # | Since: base-2.1 |
Monoid () Source # | Since: base-2.1 |
Monoid (Comparison a) Source # |
mempty :: Comparison a mempty = Comparison _ _ -> EQ |
Defined in Data.Functor.Contravariant mempty :: Comparison a Source # mappend :: Comparison a -> Comparison a -> Comparison a Source # mconcat :: [Comparison a] -> Comparison a Source # | |
Monoid (Equivalence a) Source # |
mempty :: Equivalence a mempty = Equivalence _ _ -> True |
Defined in Data.Functor.Contravariant mempty :: Equivalence a Source # mappend :: Equivalence a -> Equivalence a -> Equivalence a Source # mconcat :: [Equivalence a] -> Equivalence a Source # | |
Monoid (Predicate a) Source # |
mempty :: Predicate a mempty = _ -> True |
(Ord a, Bounded a) => Monoid (Max a) Source # | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) Source # | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) Source # | Since: base-4.9.0.0 |
Defined in Data.Semigroup mempty :: WrappedMonoid m Source # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source # mconcat :: [WrappedMonoid m] -> WrappedMonoid m Source # | |
Monoid a => Monoid (STM a) Source # | Since: base-4.17.0.0 |
FiniteBits a => Monoid (And a) Source # | This constraint is arguably too strong. However,
as some types (such as Since: base-4.16 |
FiniteBits a => Monoid (Iff a) Source # | This constraint is arguably
too strong. However, as some types (such as Since: base-4.16 |
Bits a => Monoid (Ior a) Source # | Since: base-4.16 |
Bits a => Monoid (Xor a) Source # | Since: base-4.16 |
Monoid a => Monoid (Identity a) Source # | Since: base-4.9.0.0 |
Ord a => Monoid (Max a) Source # | Since: base-4.8.0.0 |
Ord a => Monoid (Min a) Source # | Since: base-4.8.0.0 |
Monoid (First a) Source # | Since: base-2.1 |
Monoid (Last a) Source # | Since: base-2.1 |
Monoid a => Monoid (Down a) Source # | Since: base-4.11.0.0 |
Monoid a => Monoid (Dual a) Source # | Since: base-2.1 |
Monoid (Endo a) Source # | Since: base-2.1 |
Num a => Monoid (Product a) Source # | Since: base-2.1 |
Num a => Monoid (Sum a) Source # | Since: base-2.1 |
(Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics mempty :: Generically a Source # mappend :: Generically a -> Generically a -> Generically a Source # mconcat :: [Generically a] -> Generically a Source # | |
Monoid p => Monoid (Par1 p) Source # | Since: base-4.12.0.0 |
Monoid a => Monoid (Q a) Source # | Since: ghc-internal-2.17.0.0 |
Monoid a => Monoid (IO a) Source # | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) Source # | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (Solo a) Source # | Since: base-4.15 |
Monoid [a] Source # | Since: base-2.1 |
Monoid a => Monoid (Op a b) Source # |
mempty :: Op a b mempty = Op _ -> mempty |
Monoid (Proxy s) Source # | Since: base-4.7.0.0 |
Monoid (U1 p) Source # | Since: base-4.12.0.0 |
Monoid a => Monoid (ST s a) Source # | Since: base-4.11.0.0 |
(Monoid a, Monoid b) => Monoid (a, b) Source # | Since: base-2.1 |
Monoid b => Monoid (a -> b) Source # | Since: base-2.1 |
Monoid a => Monoid (Const a b) Source # | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) Source # | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) Source # | Since: base-4.8.0.0 |
Monoid (f p) => Monoid (Rec1 f p) Source # | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) Source # | Since: base-2.1 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a) Source # | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) Source # | Since: base-4.12.0.0 |
Monoid c => Monoid (K1 i c p) Source # | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) Source # | Since: base-2.1 |
Monoid (f (g a)) => Monoid (Compose f g a) Source # | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) Source # | Since: base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f p) Source # | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) Source # | Since: base-2.1 |
Functors
class Functor (f :: Type -> Type) where Source #
A type f
is a Functor if it provides a function fmap
which, given any types a
and b
lets you apply any function from (a -> b)
to turn an f a
into an f b
, preserving the
structure of f
. Furthermore f
needs to adhere to the following:
Note, that the second law follows from the free theorem of the type fmap
and
the first law, so you need only check that the former condition holds.
See these articles by School of Haskell or
David Luposchainsky
for an explanation.
fmap :: (a -> b) -> f a -> f b Source #
fmap
is used to apply a function of type (a -> b)
to a value of type f a
,
where f is a functor, to produce a value of type f b
.
Note that for any type constructor with more than one parameter (e.g., Either
),
only the last type parameter can be modified with fmap
(e.g., b
in Either a b
).
Some type constructors with two parameters or more have a
instance that allows
both the last and the penultimate parameters to be mapped over.Bifunctor
Examples
Convert from a
to a Maybe
IntMaybe String
using show
:
>>>
fmap show Nothing
Nothing>>>
fmap show (Just 3)
Just "3"
Convert from an
to an
Either
Int IntEither Int String
using show
:
>>>
fmap show (Left 17)
Left 17>>>
fmap show (Right 17)
Right "17"
Double each element of a list:
>>>
fmap (*2) [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
fmap even (2,2)
(2,True)
It may seem surprising that the function is only applied to the last element of the tuple
compared to the list example above which applies it to every element in the list.
To understand, remember that tuples are type constructors with multiple type parameters:
a tuple of 3 elements (a,b,c)
can also be written (,,) a b c
and its Functor
instance
is defined for Functor ((,,) a b)
(i.e., only the third parameter is free to be mapped over
with fmap
).
It explains why fmap
can be used with tuples containing values of different types as in the
following example:
>>>
fmap even ("hello", 1.0, 4)
("hello",1.0,True)
Instances
Functor Complex Source # | Since: base-4.9.0.0 |
Functor First Source # | Since: base-4.9.0.0 |
Functor Last Source # | Since: base-4.9.0.0 |
Functor Max Source # | Since: base-4.9.0.0 |
Functor Min Source # | Since: base-4.9.0.0 |
Functor ArgDescr Source # | Since: base-4.7.0.0 |
Functor ArgOrder Source # | Since: base-4.7.0.0 |
Functor OptDescr Source # | Since: base-4.7.0.0 |
Functor NonEmpty Source # | Since: base-4.9.0.0 |
Functor STM Source # | Since: base-4.3.0.0 |
Functor Handler Source # | Since: base-4.6.0.0 |
Functor Identity Source # | Since: base-4.8.0.0 |
Functor First Source # | Since: base-4.8.0.0 |
Functor Last Source # | Since: base-4.8.0.0 |
Functor Down Source # | Since: base-4.11.0.0 |
Functor Dual Source # | Since: base-4.8.0.0 |
Functor Product Source # | Since: base-4.8.0.0 |
Functor Sum Source # | Since: base-4.8.0.0 |
Functor ZipList Source # | Since: base-2.1 |
Functor NoIO Source # | Since: base-4.8.0.0 |
Functor Par1 Source # | Since: base-4.9.0.0 |
Functor Q Source # | |
Functor TyVarBndr Source # | |
Functor P Source # | Since: base-4.8.0.0 |
Functor ReadP Source # | Since: base-2.1 |
Functor ReadPrec Source # | Since: base-2.1 |
Functor IO Source # | Since: base-2.1 |
Functor Maybe Source # | Since: base-2.1 |
Functor Solo Source # | Since: base-4.15 |
Functor [] Source # | Since: base-2.1 |
Monad m => Functor (WrappedMonad m) Source # | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source # | |
Functor (Arg a) Source # | Since: base-4.9.0.0 |
Functor (Array i) Source # | Since: base-2.1 |
Arrow a => Functor (ArrowMonad a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source # | |
Functor (ST s) Source # | Since: base-2.1 |
Functor (Either a) Source # | Since: base-3.0 |
Functor (StateL s) Source # | Since: base-4.0 |
Functor (StateR s) Source # | Since: base-4.0 |
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (V1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (ST s) Source # | Since: base-2.1 |
Functor ((,) a) Source # | Since: base-2.1 |
Arrow a => Functor (WrappedArrow a b) Source # | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source # | |
Functor m => Functor (Kleisli m a) Source # | Since: base-4.14.0.0 |
Functor (Const m :: Type -> Type) Source # | Since: base-2.1 |
Monad m => Functor (StateT s m) Source # | Since: base-4.18.0.0 |
Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 |
Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 |
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Double :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Float :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Int :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor ((,,) a b) Source # | Since: base-4.14.0.0 |
(Functor f, Functor g) => Functor (Product f g) Source # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Sum f g) Source # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :*: g) Source # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) Source # | Since: base-4.9.0.0 |
Functor (K1 i c :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor ((,,,) a b c) Source # | Since: base-4.14.0.0 |
Functor ((->) r) Source # | Since: base-2.1 |
(Functor f, Functor g) => Functor (Compose f g) Source # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :.: g) Source # | Since: base-4.9.0.0 |
Functor f => Functor (M1 i c f) Source # | Since: base-4.9.0.0 |
Functor ((,,,,) a b c d) Source # | Since: base-4.18.0.0 |
Functor ((,,,,,) a b c d e) Source # | Since: base-4.18.0.0 |
Functor ((,,,,,,) a b c d e f) Source # | Since: base-4.18.0.0 |
class Functor f => Applicative (f :: Type -> Type) where Source #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- Identity
pure
id
<*>
v = v- Composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- Homomorphism
pure
f<*>
pure
x =pure
(f x)- Interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value into the Structure.
Examples
>>>
pure 1 :: Maybe Int
Just 1
>>>
pure 'z' :: [Char]
"z"
>>>
pure (pure ":D") :: Maybe [String]
Just [":D"]
(<*>) :: f (a -> b) -> f a -> f b infixl 4 Source #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
Example
Used in combination with
, (<$>)
can be used to build a record.(<*>)
>>>
data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>
produceFoo :: Applicative f => f Foo
>>>
produceBar :: Applicative f => f Bar
>>>
produceBaz :: Applicative f => f Baz
>>>
mkState :: Applicative f => f MyState
>>>
mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
liftA2 :: (a -> b -> c) -> f a -> f b -> f c Source #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Example
>>>
liftA2 (,) (Just 3) (Just 5)
Just (3,5)
>>>
liftA2 (+) [1, 2, 3] [4, 5, 6]
[5,6,7,6,7,8,7,8,9]
(*>) :: f a -> f b -> f b infixl 4 Source #
Sequence actions, discarding the value of the first argument.
Examples
If used in conjunction with the Applicative instance for Maybe
,
you can chain Maybe computations, with a possible "early return"
in case of Nothing
.
>>>
Just 2 *> Just 3
Just 3
>>>
Nothing *> Just 3
Nothing
Of course a more interesting use case would be to have effectful computations instead of just returning pure values.
>>>
import Data.Char
>>>
import GHC.Internal.Text.ParserCombinators.ReadP
>>>
let p = string "my name is " *> munch1 isAlpha <* eof
>>>
readP_to_S p "my name is Simon"
[("Simon","")]
(<*) :: f a -> f b -> f a infixl 4 Source #
Sequence actions, discarding the value of the second argument.
Instances
Applicative Complex Source # | Since: base-4.9.0.0 |
Applicative First Source # | Since: base-4.9.0.0 |
Applicative Last Source # | Since: base-4.9.0.0 |
Applicative Max Source # | Since: base-4.9.0.0 |
Applicative Min Source # | Since: base-4.9.0.0 |
Applicative NonEmpty Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Base | |
Applicative STM Source # | Since: base-4.8.0.0 |
Applicative Identity Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Functor.Identity | |
Applicative First Source # | Since: base-4.8.0.0 |
Applicative Last Source # | Since: base-4.8.0.0 |
Applicative Down Source # | Since: base-4.11.0.0 |
Applicative Dual Source # | Since: base-4.8.0.0 |
Applicative Product Source # | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Applicative Sum Source # | Since: base-4.8.0.0 |
Applicative ZipList Source # | f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Defined in GHC.Internal.Functor.ZipList | |
Applicative NoIO Source # | Since: base-4.8.0.0 |
Applicative Par1 Source # | Since: base-4.9.0.0 |
Applicative Q Source # | |
Applicative P Source # | Since: base-4.5.0.0 |
Applicative ReadP Source # | Since: base-4.6.0.0 |
Applicative ReadPrec Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Text.ParserCombinators.ReadPrec | |
Applicative IO Source # | Since: base-2.1 |
Applicative Maybe Source # | Since: base-2.1 |
Applicative Solo Source # | Since: base-4.15 |
Applicative [] Source # | Since: base-2.1 |
Monad m => Applicative (WrappedMonad m) Source # | Since: base-2.1 |
Defined in Control.Applicative pure :: a -> WrappedMonad m a Source # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c Source # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b Source # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a Source # | |
Arrow a => Applicative (ArrowMonad a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow pure :: a0 -> ArrowMonad a a0 Source # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c Source # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b Source # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 Source # | |
Applicative (ST s) Source # | Since: base-2.1 |
Applicative (Either e) Source # | Since: base-3.0 |
Defined in GHC.Internal.Data.Either | |
Applicative (StateL s) Source # | Since: base-4.0 |
Defined in GHC.Internal.Data.Functor.Utils | |
Applicative (StateR s) Source # | Since: base-4.0 |
Defined in GHC.Internal.Data.Functor.Utils | |
Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Applicative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Applicative (ST s) Source # | Since: base-4.4.0.0 |
Monoid a => Applicative ((,) a) Source # | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 |
Arrow a => Applicative (WrappedArrow a b) Source # | Since: base-2.1 |
Defined in Control.Applicative pure :: a0 -> WrappedArrow a b a0 Source # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c Source # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 Source # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source # | |
Applicative m => Applicative (Kleisli m a) Source # | Since: base-4.14.0.0 |
Defined in GHC.Internal.Control.Arrow pure :: a0 -> Kleisli m a a0 Source # (<*>) :: Kleisli m a (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b Source # liftA2 :: (a0 -> b -> c) -> Kleisli m a a0 -> Kleisli m a b -> Kleisli m a c Source # (*>) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a b Source # (<*) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a a0 Source # | |
Monoid m => Applicative (Const m :: Type -> Type) Source # | Since: base-2.0.1 |
Defined in GHC.Internal.Data.Functor.Const | |
Monad m => Applicative (StateT s m) Source # | Since: base-4.18.0.0 |
Defined in GHC.Internal.Data.Functor.Utils pure :: a -> StateT s m a Source # (<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b Source # liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c Source # (*>) :: StateT s m a -> StateT s m b -> StateT s m b Source # (<*) :: StateT s m a -> StateT s m b -> StateT s m a Source # | |
Applicative f => Applicative (Ap f) Source # | Since: base-4.12.0.0 |
Applicative f => Applicative (Alt f) Source # | Since: base-4.8.0.0 |
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics pure :: a -> Generically1 f a Source # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source # | |
Applicative f => Applicative (Rec1 f) Source # | Since: base-4.9.0.0 |
(Monoid a, Monoid b) => Applicative ((,,) a b) Source # | Since: base-4.14.0.0 |
Defined in GHC.Internal.Base | |
(Applicative f, Applicative g) => Applicative (Product f g) Source # | 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 # | |
(Applicative f, Applicative g) => Applicative (f :*: g) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Monoid c => Applicative (K1 i c :: Type -> Type) Source # | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) Source # | Since: base-4.14.0.0 |
Defined in GHC.Internal.Base pure :: a0 -> (a, b, c, a0) Source # (<*>) :: (a, b, c, a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source # liftA2 :: (a0 -> b0 -> c0) -> (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, c0) Source # (*>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source # (<*) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, a0) Source # | |
Applicative ((->) r) Source # | Since: base-2.1 |
(Applicative f, Applicative g) => Applicative (Compose f g) Source # | 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 # | |
(Applicative f, Applicative g) => Applicative (f :.: g) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Applicative f => Applicative (M1 i c f) Source # | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics |
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 Source #
A variant of <*>
with the types of the arguments reversed. It differs from
in that the effects are resolved in the order the arguments are
presented.flip
(<*>)
Examples
>>>
(<**>) (print 1) (id <$ print 2)
1 2
>>>
flip (<*>) (print 1) (id <$ print 2)
2 1
>>>
ZipList [4, 5, 6] <**> ZipList [(+1), (*2), (/3)]
ZipList {getZipList = [5.0,10.0,2.0]}
liftA :: Applicative f => (a -> b) -> f a -> f b Source #
Lift a function to actions.
Equivalent to Functor's fmap
but implemented using only Applicative
's methods:
liftA
f a = pure
f <*>
a
As such this function may be used to implement a Functor
instance from an Applicative
one.
Examples
Using the Applicative instance for Lists:
>>>
liftA (+1) [1, 2]
[2,3]
Or the Applicative instance for Maybe
>>>
liftA (+1) (Just 3)
Just 4
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #
Lift a ternary function to actions.
join :: Monad m => m (m a) -> m a Source #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the join
bssdo
expression
do bs <- bss bs
Examples
>>>
join [[1, 2, 3], [4, 5, 6], [7, 8, 9]]
[1,2,3,4,5,6,7,8,9]
>>>
join (Just (Just 3))
Just 3
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
class Applicative m => Monad (m :: Type -> Type) where Source #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following:
- Left identity
return
a>>=
k = k a- Right identity
m
>>=
return
= m- Associativity
m
>>=
(\x -> k x>>=
h) = (m>>=
k)>>=
h
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for List
, Maybe
and IO
defined in the Prelude satisfy these laws.
(>>=) :: m a -> (a -> m b) -> m b infixl 1 Source #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
'as
' can be understood as the >>=
bsdo
expression
do a <- as bs a
An alternative name for this function is 'bind', but some people may refer to it as 'flatMap', which results from it being equivalent to
\x f ->join
(fmap
f x) :: Monad m => m a -> (a -> m b) -> m b
which can be seen as mapping a value with
Monad m => m a -> m (m b)
and then 'flattening' m (m b)
to m b
using join
.
(>>) :: m a -> m b -> m b infixl 1 Source #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
'as
' can be understood as the >>
bsdo
expression
do as bs
or in terms of
as(>>=)
as >>= const bs
Inject a value into the monadic type.
This function should not be different from its default implementation
as pure
. The justification for the existence of this function is
merely historic.
Instances
Monad Complex Source # | Since: base-4.9.0.0 |
Monad First Source # | Since: base-4.9.0.0 |
Monad Last Source # | Since: base-4.9.0.0 |
Monad Max Source # | Since: base-4.9.0.0 |
Monad Min Source # | Since: base-4.9.0.0 |
Monad NonEmpty Source # | Since: base-4.9.0.0 |
Monad STM Source # | Since: base-4.3.0.0 |
Monad Identity Source # | Since: base-4.8.0.0 |
Monad First Source # | Since: base-4.8.0.0 |
Monad Last Source # | Since: base-4.8.0.0 |
Monad Down Source # | Since: base-4.11.0.0 |
Monad Dual Source # | Since: base-4.8.0.0 |
Monad Product Source # | Since: base-4.8.0.0 |
Monad Sum Source # | Since: base-4.8.0.0 |
Monad NoIO Source # | Since: base-4.4.0.0 |
Monad Par1 Source # | Since: base-4.9.0.0 |
Monad Q Source # | |
Monad P Source # | Since: base-2.1 |
Monad ReadP Source # | Since: base-2.1 |
Monad ReadPrec Source # | Since: base-2.1 |
Monad IO Source # | Since: base-2.1 |
Monad Maybe Source # | Since: base-2.1 |
Monad Solo Source # | Since: base-4.15 |
Monad [] Source # | Since: base-2.1 |
Monad m => Monad (WrappedMonad m) Source # | Since: base-4.7.0.0 |
Defined in Control.Applicative (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b Source # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b Source # return :: a -> WrappedMonad m a Source # | |
ArrowApply a => Monad (ArrowMonad a) Source # | Since: base-2.1 |
Defined in GHC.Internal.Control.Arrow (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b Source # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b Source # return :: a0 -> ArrowMonad a a0 Source # | |
Monad (ST s) Source # | Since: base-2.1 |
Monad (Either e) Source # | Since: base-4.4.0.0 |
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Monad (ST s) Source # | Since: base-2.1 |
Monoid a => Monad ((,) a) Source # | Since: base-4.9.0.0 |
Monad m => Monad (Kleisli m a) Source # | Since: base-4.14.0.0 |
Monad m => Monad (StateT s m) Source # | Since: base-4.18.0.0 |
Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 |
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 |
(Monoid a, Monoid b) => Monad ((,,) a b) Source # | Since: base-4.14.0.0 |
(Monad f, Monad g) => Monad (Product f g) Source # | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 |
(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) Source # | Since: base-4.14.0.0 |
Monad ((->) r) Source # | Since: base-2.1 |
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 |
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 Source #
Same as >>=
, but with the arguments interchanged.
as >>= f == f =<< as
when :: Applicative f => Bool -> f () -> f () Source #
Conditional execution of Applicative
expressions. For example,
Examples
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
>>>
putStr "pi:" >> when False (print 3.14159)
pi:
sequence :: Monad m => [m a] -> m [a] Source #
Evaluate each action in the sequence from left to right, and collect the results.
liftM :: Monad m => (a1 -> r) -> m a1 -> m r Source #
Promote a function to a monad.
This is equivalent to fmap
but specialised to Monads.
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r Source #
Promote a function to a monad, scanning the monadic arguments from left to right.
Examples
>>>
liftM2 (+) [0,1] [0,2]
[0,2,1,3]
>>>
liftM2 (+) (Just 1) Nothing
Nothing
>>>
liftM2 (+) (+ 3) (* 2) 5
18
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r Source #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r Source #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r Source #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
class Applicative f => Alternative (f :: Type -> Type) where Source #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
Examples
>>>
Nothing <|> Just 42
Just 42
>>>
[1, 2] <|> [3, 4]
[1,2,3,4]
>>>
empty <|> print (2^15)
32768
The identity of <|>
empty <|> a == a a <|> empty == a
(<|>) :: f a -> f a -> f a infixl 3 Source #
An associative binary operation
One or more.
Examples
>>>
some (putStr "la")
lalalalalalalalala... * goes on forever *
>>>
some Nothing
nothing
>>>
take 5 <$> some (Just 1)
* hangs forever *
Note that this function can be used with Parsers based on
Applicatives. In that case some parser
will attempt to
parse parser
one or more times until it fails.
Zero or more.
Examples
>>>
many (putStr "la")
lalalalalalalalala... * goes on forever *
>>>
many Nothing
Just []
>>>
take 5 <$> many (Just 1)
* hangs forever *
Note that this function can be used with Parsers based on
Applicatives. In that case many parser
will attempt to
parse parser
zero or more times until it fails.
Instances
Alternative STM Source # | Takes the first non- Since: base-4.8.0.0 |
Alternative ZipList Source # | Since: base-4.11.0.0 |
Alternative P Source # | Since: base-4.5.0.0 |
Alternative ReadP Source # | Since: base-4.6.0.0 |
Alternative ReadPrec Source # | Since: base-4.6.0.0 |
Alternative IO Source # | Takes the first non-throwing Since: base-4.9.0.0 |
Alternative Maybe Source # | Picks the leftmost Since: base-2.1 |
Alternative [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 |
MonadPlus m => Alternative (WrappedMonad m) Source # | Since: base-2.1 |
Defined in Control.Applicative empty :: WrappedMonad m a Source # (<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a Source # some :: WrappedMonad m a -> WrappedMonad m [a] Source # many :: WrappedMonad m a -> WrappedMonad m [a] Source # | |
ArrowPlus a => Alternative (ArrowMonad a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow empty :: ArrowMonad a a0 Source # (<|>) :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 Source # some :: ArrowMonad a a0 -> ArrowMonad a [a0] Source # many :: ArrowMonad a a0 -> ArrowMonad a [a0] Source # | |
Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Alternative (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) Source # | Since: base-2.1 |
Defined in Control.Applicative empty :: WrappedArrow a b a0 Source # (<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 Source # some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] Source # many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] Source # | |
Alternative m => Alternative (Kleisli m a) Source # | Since: base-4.14.0.0 |
Alternative f => Alternative (Ap f) Source # | Since: base-4.12.0.0 |
Alternative f => Alternative (Alt f) Source # | Since: base-4.8.0.0 |
(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics empty :: Generically1 f a Source # (<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a Source # some :: Generically1 f a -> Generically1 f [a] Source # many :: Generically1 f a -> Generically1 f [a] Source # | |
Alternative f => Alternative (Rec1 f) Source # | Since: base-4.9.0.0 |
(Alternative f, Alternative g) => Alternative (Product f g) Source # | Since: base-4.9.0.0 |
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | Since: base-4.9.0.0 |
(Alternative f, Applicative g) => Alternative (Compose f g) Source # | Since: base-4.9.0.0 |
(Alternative f, Applicative g) => Alternative (f :.: g) Source # | Since: base-4.9.0.0 |
Alternative f => Alternative (M1 i c f) Source # | Since: base-4.9.0.0 |
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where Source #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
mplus :: m a -> m a -> m a Source #
An associative operation. The default definition is
mplus = (<|>
)
Instances
MonadPlus STM Source # | Takes the first non- Since: base-4.3.0.0 |
MonadPlus P Source # | Since: base-2.1 |
MonadPlus ReadP Source # | Since: base-2.1 |
MonadPlus ReadPrec Source # | Since: base-2.1 |
MonadPlus IO Source # | Takes the first non-throwing Since: base-4.9.0.0 |
MonadPlus Maybe Source # | Picks the leftmost Since: base-2.1 |
MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 |
(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow mzero :: ArrowMonad a a0 Source # mplus :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 Source # | |
MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
MonadPlus (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
MonadPlus m => MonadPlus (Kleisli m a) Source # | Since: base-4.14.0.0 |
MonadPlus f => MonadPlus (Ap f) Source # | Since: base-4.12.0.0 |
MonadPlus f => MonadPlus (Alt f) Source # | Since: base-4.8.0.0 |
MonadPlus f => MonadPlus (Rec1 f) Source # | Since: base-4.9.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (Product f g) Source # | Since: base-4.9.0.0 |
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source # | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (M1 i c f) Source # | Since: base-4.9.0.0 |
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
a :| [a] infixr 5 |
Instances
Foldable1 NonEmpty Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => NonEmpty m -> m Source # foldMap1 :: Semigroup m => (a -> m) -> NonEmpty a -> m Source # foldMap1' :: Semigroup m => (a -> m) -> NonEmpty a -> m Source # toNonEmpty :: NonEmpty a -> NonEmpty a Source # maximum :: Ord a => NonEmpty a -> a Source # minimum :: Ord a => NonEmpty a -> a Source # head :: NonEmpty a -> a Source # last :: NonEmpty a -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b Source # | |||||
Eq1 NonEmpty Source # | Since: base-4.10.0.0 | ||||
Ord1 NonEmpty Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read1 NonEmpty Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] Source # | |||||
Show1 NonEmpty Source # | Since: base-4.10.0.0 | ||||
Applicative NonEmpty Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Base | |||||
Functor NonEmpty Source # | Since: base-4.9.0.0 | ||||
Monad NonEmpty Source # | Since: base-4.9.0.0 | ||||
MonadFix NonEmpty Source # | Since: base-4.9.0.0 | ||||
MonadZip NonEmpty Source # | Since: ghc-internal-4.9.0.0 | ||||
Foldable NonEmpty Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable fold :: Monoid m => NonEmpty m -> m Source # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m Source # foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m Source # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b Source # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b Source # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b Source # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b Source # foldr1 :: (a -> a -> a) -> NonEmpty a -> a Source # foldl1 :: (a -> a -> a) -> NonEmpty a -> a Source # toList :: NonEmpty a -> [a] Source # null :: NonEmpty a -> Bool Source # length :: NonEmpty a -> Int Source # elem :: Eq a => a -> NonEmpty a -> Bool Source # maximum :: Ord a => NonEmpty a -> a Source # minimum :: Ord a => NonEmpty a -> a Source # | |||||
Traversable NonEmpty Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics
| |||||
Lift a => Lift (NonEmpty a :: Type) Source # | Since: template-haskell-2.15.0.0 | ||||
Semigroup (NonEmpty a) Source # | Since: base-4.9.0.0 | ||||
Data a => Data (NonEmpty a) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) Source # toConstr :: NonEmpty a -> Constr Source # dataTypeOf :: NonEmpty a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) Source # gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source # | |||||
Generic (NonEmpty a) Source # | |||||
Defined in GHC.Internal.Generics
| |||||
IsList (NonEmpty a) Source # | Since: base-4.9.0.0 | ||||
Read a => Read (NonEmpty a) Source # | Since: base-4.11.0.0 | ||||
Show a => Show (NonEmpty a) Source # | Since: base-4.11.0.0 | ||||
Eq a => Eq (NonEmpty a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord (NonEmpty a) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Base compare :: NonEmpty a -> NonEmpty a -> Ordering Source # (<) :: NonEmpty a -> NonEmpty a -> Bool Source # (<=) :: NonEmpty a -> NonEmpty a -> Bool Source # (>) :: NonEmpty a -> NonEmpty a -> Bool Source # (>=) :: NonEmpty a -> NonEmpty a -> Bool Source # | |||||
type Rep1 NonEmpty Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep (NonEmpty a) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Internal.Generics type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
type Item (NonEmpty a) Source # | |||||
Defined in GHC.Internal.IsList |
foldr :: (a -> b -> b) -> b -> [a] -> b Source #
foldr
, applied to a binary operator, a starting value (typically
the right-identity of the operator), and a list, reduces the list
using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
map :: (a -> b) -> [a] -> [b] Source #
\(\mathcal{O}(n)\). map
f xs
is the list obtained by applying f
to
each element of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
this means that map id == id
Examples
>>>
map (+1) [1, 2, 3]
[2,3,4]
>>>
map id [1, 2, 3]
[1,2,3]
>>>
map (\n -> 3 * n + 1) [1, 2, 3]
[4,7,10]
(++) :: [a] -> [a] -> [a] infixr 5 Source #
(++)
appends two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
Performance considerations
This function takes linear time in the number of elements of the
first list. Thus it is better to associate repeated
applications of (++)
to the right (which is the default behaviour):
xs ++ (ys ++ zs)
or simply xs ++ ys ++ zs
, but not (xs ++ ys) ++ zs
.
For the same reason concat
=
foldr
(++)
[]
has linear performance, while foldl
(++)
[]
is prone
to quadratic slowdown
Examples
>>>
[1, 2, 3] ++ [4, 5, 6]
[1,2,3,4,5,6]
>>>
[] ++ [1, 2, 3]
[1,2,3]
>>>
[3, 2, 1] ++ []
[3,2,1]
String
is an alias for a list of characters.
String constants in Haskell are values of type String
.
That means if you write a string literal like "hello world"
,
it will have the type [Char]
, which is the same as String
.
Note: You can ask the compiler to automatically infer different types
with the -XOverloadedStrings
language extension, for example
"hello world" :: Text
. See IsString
for more information.
Because String
is just a list of characters, you can use normal list functions
to do basic string manipulation. See Data.List for operations on lists.
Performance considerations
[Char]
is a relatively memory-inefficient type.
It is a linked list of boxed word-size characters, internally it looks something like:
╭─────┬───┬──╮ ╭─────┬───┬──╮ ╭─────┬───┬──╮ ╭────╮ │ (:) │ │ ─┼─>│ (:) │ │ ─┼─>│ (:) │ │ ─┼─>│ [] │ ╰─────┴─┼─┴──╯ ╰─────┴─┼─┴──╯ ╰─────┴─┼─┴──╯ ╰────╯ v v v 'a' 'b' 'c'
The String
"abc" will use 5*3+1 = 16
(in general 5n+1
)
words of space in memory.
Furthermore, operations like (++)
(string concatenation) are O(n)
(in the left argument).
For historical reasons, the base
library uses String
in a lot of places
for the conceptual simplicity, but library code dealing with user-data
should use the text
package for Unicode text, or the the
bytestring package
for binary data.
eqString :: String -> String -> Bool Source #
This String
equality predicate is used when desugaring
pattern-matches against strings.
Miscellanea
Identity function.
id x = x
This function might seem useless at first glance, but it can be very useful in a higher order context.
Examples
>>>
length $ filter id [True, True, False, True]
3
>>>
Just (Just 3) >>= id
Just 3
>>>
foldr id 0 [(^3), (*5), (+2)]
1000
assert :: Bool -> a -> a Source #
If the first argument evaluates to True
, then the result is the
second argument. Otherwise an AssertionFailed
exception
is raised, containing a String
with the source file and line number of the
call to assert
.
Assertions can normally be turned on or off with a compiler flag
(for GHC, assertions are normally on unless optimisation is turned on
with -O
or the -fignore-asserts
option is given). When assertions are turned off, the first
argument to assert
is ignored, and the second argument is
returned as the result.
breakpoint :: a -> a Source #
breakpointCond :: Bool -> a -> a Source #
const x y
always evaluates to x
, ignoring its second argument.
const x = \_ -> x
This function might seem useless at first glance, but it can be very useful in a higher order context.
Examples
>>>
const 42 "hello"
42
>>>
map (const 42) [0..3]
[42,42,42,42]
(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 Source #
Right to left function composition.
(f . g) x = f (g x)
f . id = f = id . f
Examples
>>>
map ((*2) . length) [[], [0, 1, 2], [0]]
[0,6,2]
>>>
foldr (.) id [(+1), (*3), (^3)] 2
25
>>>
let (...) = (.).(.) in ((*2)...(+)) 5 10
30
flip :: (a -> b -> c) -> b -> a -> c Source #
takes its (first) two arguments in the reverse order of flip
ff
.
flip f x y = f y x
flip . flip = id
Examples
>>>
flip (++) "hello" "world"
"worldhello"
>>>
let (.>) = flip (.) in (+1) .> show $ 5
"6"
($) :: (a -> b) -> a -> b infixr 0 Source #
is the function application operator.($)
Applying
to a function ($)
f
and an argument x
gives the same result as applying f
to x
directly. The definition is akin to this:
($) :: (a -> b) -> a -> b ($) f x = f x
This is
specialized from id
a -> a
to (a -> b) -> (a -> b)
which by the associativity of (->)
is the same as (a -> b) -> a -> b
.
On the face of it, this may appear pointless! But it's actually one of the most useful and important operators in Haskell.
The order of operations is very different between ($)
and normal function application. Normal function application has precedence 10 - higher than any operator - and associates to the left. So these two definitions are equivalent:
expr = min 5 1 + 5 expr = ((min 5) 1) + 5
($)
has precedence 0 (the lowest) and associates to the right, so these are equivalent:
expr = min 5 $ 1 + 5 expr = (min 5) (1 + 5)
Examples
A common use cases of ($)
is to avoid parentheses in complex expressions.
For example, instead of using nested parentheses in the following Haskell function:
-- | Sum numbers in a string: strSum "100 5 -7" == 98 strSum ::String
->Int
strSum s =sum
(mapMaybe
readMaybe
(words
s))
we can deploy the function application operator:
-- | Sum numbers in a string: strSum "100 5 -7" == 98 strSum ::String
->Int
strSum s =sum
$
mapMaybe
readMaybe
$
words
s
($)
is also used as a section (a partially applied operator), in order to indicate that we wish to apply some yet-unspecified function to a given value. For example, to apply the argument 5
to a list of functions:
applyFive :: [Int] applyFive = map ($ 5) [(+1), (2^)] >>> [6, 32]
Technical Remark (Representation Polymorphism)
($)
is fully representation-polymorphic. This allows it to also be used with arguments of unlifted and even unboxed kinds, such as unboxed integers:
fastMod :: Int -> Int -> Int fastMod (I# x) (I# m) = I# $ remInt# x m
($!) :: (a -> b) -> a -> b infixr 0 Source #
Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.
until :: (a -> Bool) -> (a -> a) -> a -> a Source #
yields the result of applying until
p ff
until p
holds.
IO
Low-level integer utilities
getTag :: forall {lev :: Levity} (a :: TYPE ('BoxedRep lev)). DataToTag a => a -> Int# Source #
Returns the tag of a constructor application; this function was once used by the deriving code for Eq, Ord and Enum.
shift_mask :: Int# -> Int# -> Int# Source #
This function is used to implement branchless shifts. If the number of bits to shift is greater than or equal to the type size in bits, then the shift must return 0. Instead of doing a test, we use a mask obtained via this function which is branchless too.
shift_mask m b | b < m = 0xFF..FF | otherwise = 0
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)