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 | Unsafe |
Language | Haskell2010 |
GHC.Internal.Base
Description
Basic data types and classes.
Synopsis
- type String = [Char]
- class Applicative m => Monad (m :: Type -> Type) where
- (.) :: (b -> c) -> (a -> b) -> a -> c
- id :: a -> a
- assert :: Bool -> a -> a
- class Functor (f :: Type -> Type) where
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
- sequence :: Monad m => [m a] -> m [a]
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- join :: Monad m => m (m a) -> m a
- when :: Applicative f => Bool -> f () -> f ()
- 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
- failIO :: String -> IO a
- class Semigroup a => Monoid a where
- data NonEmpty a = a :| [a]
- ($) :: (a -> b) -> a -> b
- otherwise :: Bool
- foldr :: (a -> b -> b) -> b -> [a] -> b
- const :: a -> b -> a
- flip :: (a -> b -> c) -> b -> a -> c
- class Functor f => Applicative (f :: Type -> Type) where
- class Semigroup a where
- (++) :: [a] -> [a] -> [a]
- map :: (a -> b) -> [a] -> [b]
- data Void
- absurd :: Void -> a
- vacuous :: Functor f => f Void -> f a
- class Applicative f => Alternative (f :: Type -> Type) where
- ($!) :: (a -> b) -> a -> b
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #)
- remInt :: Int -> Int -> Int
- ord :: Char -> Int
- (<**>) :: 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
- mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
- unsafeChr :: Int -> Char
- eqString :: String -> String -> Bool
- maxInt :: Int
- minInt :: Int
- data Opaque = O a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- returnIO :: a -> IO a
- thenIO :: IO a -> IO b -> IO b
- bindIO :: IO a -> (a -> IO b) -> IO b
- getTag :: forall {lev :: Levity} (a :: TYPE ('BoxedRep lev)). DataToTag a => a -> Int#
- quotInt :: 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#
- class IP (x :: Symbol) a | x -> a where
- ip :: a
- modInt# :: Int# -> Int# -> Int#
- divInt# :: Int# -> Int# -> Int#
- class Eq a where
- class Eq a => Ord a where
- eqWord :: Word -> Word -> Bool
- neWord :: Word -> Word -> Bool
- eqChar :: Char -> Char -> Bool
- neChar :: Char -> Char -> Bool
- eqFloat :: Float -> Float -> Bool
- eqDouble :: Double -> Double -> Bool
- eqInt :: Int -> Int -> Bool
- neInt :: Int -> Int -> Bool
- gtInt :: Int -> Int -> Bool
- geInt :: Int -> Int -> Bool
- ltInt :: Int -> Int -> Bool
- leInt :: Int -> Int -> Bool
- compareInt :: Int -> Int -> Ordering
- compareInt# :: Int# -> Int# -> Ordering
- gtWord :: Word -> Word -> Bool
- geWord :: Word -> Word -> Bool
- ltWord :: Word -> Word -> Bool
- leWord :: Word -> Word -> Bool
- compareWord :: Word -> Word -> Ordering
- compareWord# :: Word# -> Word# -> Ordering
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- divInt8# :: Int8# -> Int8# -> Int8#
- divInt16# :: Int16# -> Int16# -> Int16#
- divInt32# :: Int32# -> Int32# -> Int32#
- 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# #)
- module GHC.CString
- module GHC.Magic
- module GHC.Magic.Dict
- data Word = W# Word#
- data Float = F# Float#
- data Int = I# Int#
- data TYPE (a :: RuntimeRep)
- data CONSTRAINT (a :: RuntimeRep)
- data WordBox (a :: TYPE 'WordRep) = MkWordBox a
- data IntBox (a :: TYPE 'IntRep) = MkIntBox a
- data FloatBox (a :: TYPE 'FloatRep) = MkFloatBox a
- data DoubleBox (a :: TYPE 'DoubleRep) = MkDoubleBox a
- data DictBox a = a => MkDictBox
- data Bool
- data Char = C# Char#
- data Double = D# Double#
- data List a
- data Ordering
- class a ~# b => (a :: k0) ~~ (b :: k1)
- class a ~# b => (a :: k) ~ (b :: k)
- class a ~R# b => Coercible (a :: k) (b :: k)
- data Symbol
- data RuntimeRep
- data Levity
- data VecCount
- data VecElem
- data Multiplicity
- data SPEC
- data TypeLitSort
- data KindRep
- data TyCon = TyCon Word64# Word64# Module TrName Int# KindRep
- data TrName
- data Module = Module TrName TrName
- newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
- type ZeroBitType = TYPE ZeroBitRep
- type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep])
- type UnliftedRep = 'BoxedRep 'Unlifted
- type LiftedRep = 'BoxedRep 'Lifted
- type UnliftedType = TYPE UnliftedRep
- type Type = TYPE LiftedRep
- type Constraint = CONSTRAINT LiftedRep
- type family Any :: k where ...
- type KindBndr = Int
- type Void# = (# #)
- type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ...
- isTrue# :: Int# -> Bool
- data Word# :: TYPE 'WordRep
- data Int# :: TYPE 'IntRep
- data Addr# :: TYPE 'AddrRep
- data Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data ByteArray# :: UnliftedType
- data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data Char# :: TYPE 'WordRep
- data Double# :: TYPE 'DoubleRep
- data Float# :: TYPE 'FloatRep
- data Int8# :: TYPE 'Int8Rep
- data Int16# :: TYPE 'Int16Rep
- data Int32# :: TYPE 'Int32Rep
- data Int64# :: TYPE 'Int64Rep
- data BCO
- data Weak# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutableByteArray# a :: UnliftedType
- data SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType
- data RealWorld
- data StablePtr# (a :: TYPE ('BoxedRep l)) :: TYPE 'AddrRep
- data StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType
- data Compact# :: UnliftedType
- data State# a :: ZeroBitType
- data Proxy# (a :: k) :: ZeroBitType
- data ThreadId# :: UnliftedType
- data Word8# :: TYPE 'Word8Rep
- data Word16# :: TYPE 'Word16Rep
- data Word32# :: TYPE 'Word32Rep
- data Word64# :: TYPE 'Word64Rep
- data StackSnapshot# :: UnliftedType
- data PromptTag# a :: UnliftedType
- data FUN
- data TYPE (a :: RuntimeRep)
- data CONSTRAINT (a :: RuntimeRep)
- data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep)
- data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep)
- data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep)
- data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep)
- data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep)
- data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep)
- data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep)
- data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep)
- data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep)
- data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep)
- data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep)
- data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep)
- data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep)
- data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep)
- data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep)
- data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep)
- data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep)
- data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep)
- data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep)
- data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep)
- data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep)
- data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep)
- data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep)
- data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep)
- data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep)
- data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep)
- data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep)
- data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep)
- data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep)
- data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep)
- prefetchValue0# :: a -> State# d -> State# d
- prefetchAddr0# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue1# :: a -> State# d -> State# d
- prefetchAddr1# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue2# :: a -> State# d -> State# d
- prefetchAddr2# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d
- prefetchValue3# :: a -> State# d -> State# d
- prefetchAddr3# :: Addr# -> Int# -> State# d -> State# d
- prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d
- prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8#
- indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16#
- indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4#
- indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8#
- indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2#
- indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4#
- indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8#
- indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16#
- indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32#
- indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64#
- indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4#
- indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8#
- indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16#
- indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32#
- indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2#
- indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4#
- indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8#
- indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16#
- indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8#
- indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16#
- indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32#
- indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64#
- indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4#
- indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8#
- indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16#
- indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32#
- indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2#
- indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4#
- indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8#
- indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16#
- writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatArrayAsFloatX16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleArrayAsDoubleX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatArrayAsFloatX8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleArrayAsDoubleX2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatArrayAsFloatX4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64ArrayAsWord64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32ArrayAsWord32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16ArrayAsWord16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8ArrayAsWord8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64ArrayAsWord64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32ArrayAsWord32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16ArrayAsWord16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8ArrayAsWord8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64ArrayAsWord64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32ArrayAsWord32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16ArrayAsWord16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8ArrayAsWord8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64ArrayAsInt64X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32ArrayAsInt32X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16ArrayAsInt16X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8ArrayAsInt8X64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64ArrayAsInt64X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32ArrayAsInt32X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16ArrayAsInt16X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8ArrayAsInt8X32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64ArrayAsInt64X2# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32ArrayAsInt32X4# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16ArrayAsInt16X8# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8ArrayAsInt8X16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8#
- indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4#
- indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8#
- indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16#
- indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32#
- indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64#
- indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4#
- indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8#
- indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16#
- indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32#
- indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2#
- indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4#
- indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8#
- indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16#
- indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8#
- indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16#
- indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32#
- indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64#
- indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4#
- indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8#
- indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16#
- indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32#
- indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2#
- indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4#
- indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8#
- indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16#
- writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8#
- indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16#
- indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4#
- indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8#
- indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2#
- indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4#
- indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8#
- indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16#
- indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32#
- indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64#
- indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4#
- indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8#
- indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16#
- indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32#
- indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2#
- indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4#
- indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8#
- indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16#
- indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8#
- indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16#
- indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32#
- indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64#
- indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4#
- indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8#
- indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16#
- indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32#
- indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2#
- indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4#
- indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8#
- indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16#
- writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d
- writeFloatX16Array# :: MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d
- writeDoubleX4Array# :: MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d
- writeFloatX8Array# :: MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d
- writeDoubleX2Array# :: MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d
- writeFloatX4Array# :: MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d
- writeWord64X8Array# :: MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d
- writeWord32X16Array# :: MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d
- writeWord16X32Array# :: MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d
- writeWord8X64Array# :: MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d
- writeWord64X4Array# :: MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d
- writeWord32X8Array# :: MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d
- writeWord16X16Array# :: MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d
- writeWord8X32Array# :: MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d
- writeWord64X2Array# :: MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d
- writeWord32X4Array# :: MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d
- writeWord16X8Array# :: MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d
- writeWord8X16Array# :: MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d
- writeInt64X8Array# :: MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d
- writeInt32X16Array# :: MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d
- writeInt16X32Array# :: MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d
- writeInt8X64Array# :: MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d
- writeInt64X4Array# :: MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d
- writeInt32X8Array# :: MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d
- writeInt16X16Array# :: MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d
- writeInt8X32Array# :: MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d
- writeInt64X2Array# :: MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d
- writeInt32X4Array# :: MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d
- writeInt16X8Array# :: MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d
- writeInt8X16Array# :: MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d
- readDoubleX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #)
- readFloatX16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #)
- readDoubleX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #)
- readFloatX8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #)
- readDoubleX2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #)
- readFloatX4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #)
- readWord64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #)
- readWord32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #)
- readWord16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #)
- readWord8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #)
- readWord64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #)
- readWord32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #)
- readWord16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #)
- readWord8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #)
- readWord64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #)
- readWord32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #)
- readWord16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #)
- readWord8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #)
- readInt64X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #)
- readInt32X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #)
- readInt16X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #)
- readInt8X64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #)
- readInt64X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #)
- readInt32X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #)
- readInt16X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #)
- readInt8X32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #)
- readInt64X2Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #)
- readInt32X4Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #)
- readInt16X8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #)
- readInt8X16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #)
- indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8#
- indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16#
- indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4#
- indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8#
- indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2#
- indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4#
- indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8#
- indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16#
- indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32#
- indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64#
- indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4#
- indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8#
- indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16#
- indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32#
- indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2#
- indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4#
- indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8#
- indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16#
- indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8#
- indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16#
- indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32#
- indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64#
- indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4#
- indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8#
- indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16#
- indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32#
- indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2#
- indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4#
- indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8#
- indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#
- negateDoubleX8# :: DoubleX8# -> DoubleX8#
- negateFloatX16# :: FloatX16# -> FloatX16#
- negateDoubleX4# :: DoubleX4# -> DoubleX4#
- negateFloatX8# :: FloatX8# -> FloatX8#
- negateDoubleX2# :: DoubleX2# -> DoubleX2#
- negateFloatX4# :: FloatX4# -> FloatX4#
- negateInt64X8# :: Int64X8# -> Int64X8#
- negateInt32X16# :: Int32X16# -> Int32X16#
- negateInt16X32# :: Int16X32# -> Int16X32#
- negateInt8X64# :: Int8X64# -> Int8X64#
- negateInt64X4# :: Int64X4# -> Int64X4#
- negateInt32X8# :: Int32X8# -> Int32X8#
- negateInt16X16# :: Int16X16# -> Int16X16#
- negateInt8X32# :: Int8X32# -> Int8X32#
- negateInt64X2# :: Int64X2# -> Int64X2#
- negateInt32X4# :: Int32X4# -> Int32X4#
- negateInt16X8# :: Int16X8# -> Int16X8#
- negateInt8X16# :: Int8X16# -> Int8X16#
- remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8#
- plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16#
- plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4#
- plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8#
- plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2#
- plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
- plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8#
- plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16#
- plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32#
- plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64#
- plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4#
- plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8#
- plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16#
- plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32#
- plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2#
- plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4#
- plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#
- plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16#
- plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8#
- plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16#
- plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32#
- plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64#
- plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4#
- plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8#
- plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16#
- plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32#
- plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2#
- plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4#
- plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8#
- plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16#
- insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8#
- insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16#
- insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4#
- insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8#
- insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2#
- insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4#
- insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8#
- insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16#
- insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32#
- insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64#
- insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4#
- insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8#
- insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16#
- insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32#
- insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2#
- insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4#
- insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8#
- insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16#
- insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8#
- insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16#
- insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32#
- insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64#
- insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4#
- insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8#
- insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16#
- insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32#
- insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2#
- insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4#
- insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8#
- insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16#
- 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# #)
- unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #)
- unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #)
- unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #)
- unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #)
- unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #)
- unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- 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# #)
- 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# #)
- unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #)
- unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #)
- unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- 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# #)
- unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #)
- unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #)
- unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #)
- unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #)
- unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #)
- unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- 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# #)
- 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# #)
- unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #)
- unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #)
- unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- 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# #)
- unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #)
- unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #)
- unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #)
- unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #)
- 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#
- packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4#
- packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8#
- packDoubleX2# :: (# Double#, Double# #) -> DoubleX2#
- packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4#
- packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8#
- packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16#
- 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#
- 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#
- packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4#
- packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8#
- packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16#
- 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#
- packWord64X2# :: (# Word64#, Word64# #) -> Word64X2#
- packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4#
- packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8#
- packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16#
- packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8#
- packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16#
- 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#
- 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#
- packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4#
- packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8#
- packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16#
- 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#
- packInt64X2# :: (# Int64#, Int64# #) -> Int64X2#
- packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4#
- packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8#
- packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16#
- broadcastDoubleX8# :: Double# -> DoubleX8#
- broadcastFloatX16# :: Float# -> FloatX16#
- broadcastDoubleX4# :: Double# -> DoubleX4#
- broadcastFloatX8# :: Float# -> FloatX8#
- broadcastDoubleX2# :: Double# -> DoubleX2#
- broadcastFloatX4# :: Float# -> FloatX4#
- broadcastWord64X8# :: Word64# -> Word64X8#
- broadcastWord32X16# :: Word32# -> Word32X16#
- broadcastWord16X32# :: Word16# -> Word16X32#
- broadcastWord8X64# :: Word8# -> Word8X64#
- broadcastWord64X4# :: Word64# -> Word64X4#
- broadcastWord32X8# :: Word32# -> Word32X8#
- broadcastWord16X16# :: Word16# -> Word16X16#
- broadcastWord8X32# :: Word8# -> Word8X32#
- broadcastWord64X2# :: Word64# -> Word64X2#
- broadcastWord32X4# :: Word32# -> Word32X4#
- broadcastWord16X8# :: Word16# -> Word16X8#
- broadcastWord8X16# :: Word8# -> Word8X16#
- broadcastInt64X8# :: Int64# -> Int64X8#
- broadcastInt32X16# :: Int32# -> Int32X16#
- broadcastInt16X32# :: Int16# -> Int16X32#
- broadcastInt8X64# :: Int8# -> Int8X64#
- broadcastInt64X4# :: Int64# -> Int64X4#
- broadcastInt32X8# :: Int32# -> Int32X8#
- broadcastInt16X16# :: Int16# -> Int16X16#
- broadcastInt8X32# :: Int8# -> Int8X32#
- broadcastInt64X2# :: Int64# -> Int64X2#
- broadcastInt32X4# :: Int32# -> Int32X4#
- broadcastInt16X8# :: Int16# -> Int16X8#
- broadcastInt8X16# :: Int8# -> Int8X16#
- setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld
- traceMarker# :: Addr# -> State# d -> State# d
- traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d
- traceEvent# :: Addr# -> State# d -> State# d
- clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #)
- getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #)
- getCCSOf# :: a -> State# d -> (# State# d, Addr# #)
- getApStackVal# :: a -> Int# -> (# Int#, b #)
- closureSize# :: a -> Int#
- unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #)
- newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #)
- mkApUpd0# :: BCO -> (# a #)
- anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #)
- addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #)
- tagToEnum# :: Int# -> a
- keepAlive# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d b. a -> State# d -> (State# d -> b) -> b
- numSparks# :: State# d -> (# State# d, Int# #)
- getSpark# :: State# d -> (# State# d, Int#, a #)
- seq# :: a -> State# d -> (# State# d, a #)
- spark# :: a -> State# d -> (# State# d, a #)
- par# :: a -> Int#
- reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int#
- compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #)
- compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #)
- compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #)
- compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #)
- compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #)
- compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #)
- compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld
- compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #)
- stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int#
- makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
- eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int#
- deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #)
- makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #)
- touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d
- finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
- deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #)
- addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #)
- mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- 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 #)
- listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #)
- threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #)
- threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #)
- noDuplicate# :: State# d -> State# d
- isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #)
- labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld
- myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #)
- yield# :: State# RealWorld -> State# RealWorld
- killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
- forkOn# :: Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- fork# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
- waitWrite# :: Int# -> State# d -> State# d
- waitRead# :: Int# -> State# d -> State# d
- delay# :: Int# -> State# d -> State# d
- writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #)
- readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #)
- newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #)
- isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #)
- tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #)
- putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d
- tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #)
- takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #)
- newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #)
- writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d
- readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #)
- newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d 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 #)
- catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #)
- atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- control0# :: PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #)
- prompt# :: PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- newPromptTag# :: State# RealWorld -> (# State# RealWorld, PromptTag# a #)
- getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #)
- unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)
- raiseIO# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> State# RealWorld -> (# State# RealWorld, b #)
- raiseDivZero# :: (# #) -> b
- raiseOverflow# :: (# #) -> b
- raiseUnderflow# :: (# #) -> b
- raise# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> b
- 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 #)
- casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #)
- atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #)
- atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #)
- atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #)
- writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d
- readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #)
- newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #)
- atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d
- atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #)
- fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #)
- atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #)
- atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #)
- atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #)
- atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #)
- atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #)
- atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #)
- writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d
- writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d
- writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d
- writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d
- writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d
- writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d
- writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d
- writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d
- writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d
- writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d
- writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d
- writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d
- writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d
- writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d
- writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d
- readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #)
- readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #)
- readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #)
- readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #)
- readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #)
- readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #)
- readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #)
- readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #)
- readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #)
- readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #)
- readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #)
- readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #)
- readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #)
- indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64#
- indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64#
- indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32#
- indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32#
- indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16#
- indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16#
- indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a
- indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double#
- indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float#
- indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr#
- indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word#
- indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int#
- indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char#
- indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char#
- indexWord64OffAddr# :: Addr# -> Int# -> Word64#
- indexInt64OffAddr# :: Addr# -> Int# -> Int64#
- indexWord32OffAddr# :: Addr# -> Int# -> Word32#
- indexInt32OffAddr# :: Addr# -> Int# -> Int32#
- indexWord16OffAddr# :: Addr# -> Int# -> Word16#
- indexInt16OffAddr# :: Addr# -> Int# -> Int16#
- indexWord8OffAddr# :: Addr# -> Int# -> Word8#
- indexInt8OffAddr# :: Addr# -> Int# -> Int8#
- indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
- indexDoubleOffAddr# :: Addr# -> Int# -> Double#
- indexFloatOffAddr# :: Addr# -> Int# -> Float#
- indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- indexWordOffAddr# :: Addr# -> Int# -> Word#
- indexIntOffAddr# :: Addr# -> Int# -> Int#
- indexWideCharOffAddr# :: Addr# -> Int# -> Char#
- indexCharOffAddr# :: Addr# -> Int# -> Char#
- leAddr# :: Addr# -> Addr# -> Int#
- ltAddr# :: Addr# -> Addr# -> Int#
- neAddr# :: Addr# -> Addr# -> Int#
- eqAddr# :: Addr# -> Addr# -> Int#
- geAddr# :: Addr# -> Addr# -> Int#
- gtAddr# :: Addr# -> Addr# -> Int#
- int2Addr# :: Int# -> Addr#
- addr2Int# :: Addr# -> Int#
- remAddr# :: Addr# -> Int# -> Int#
- minusAddr# :: Addr# -> Addr# -> Int#
- plusAddr# :: Addr# -> Int# -> Addr#
- fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #)
- casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #)
- casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #)
- casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #)
- casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #)
- atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld
- setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d
- copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld
- copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d
- copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
- writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d
- writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d
- writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d
- writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d
- writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d
- writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d
- writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
- writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d
- writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d
- writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
- writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d
- writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d
- writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
- writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
- writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
- readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #)
- readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #)
- readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #)
- readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #)
- readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #)
- readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #)
- readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #)
- readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #)
- readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #)
- readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
- readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #)
- readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #)
- readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
- readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
- readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
- indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
- indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
- indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
- indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
- indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
- indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
- indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
- indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
- indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
- indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
- indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
- indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
- indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
- indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
- indexWord64Array# :: ByteArray# -> Int# -> Word64#
- indexInt64Array# :: ByteArray# -> Int# -> Int64#
- indexWord32Array# :: ByteArray# -> Int# -> Word32#
- indexInt32Array# :: ByteArray# -> Int# -> Int32#
- indexWord16Array# :: ByteArray# -> Int# -> Word16#
- indexInt16Array# :: ByteArray# -> Int# -> Int16#
- indexWord8Array# :: ByteArray# -> Int# -> Word8#
- indexInt8Array# :: ByteArray# -> Int# -> Int8#
- indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
- indexDoubleArray# :: ByteArray# -> Int# -> Double#
- indexFloatArray# :: ByteArray# -> Int# -> Float#
- indexAddrArray# :: ByteArray# -> Int# -> Addr#
- indexWordArray# :: ByteArray# -> Int# -> Word#
- indexIntArray# :: ByteArray# -> Int# -> Int#
- indexWideCharArray# :: ByteArray# -> Int# -> Char#
- indexCharArray# :: ByteArray# -> Int# -> Char#
- getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #)
- sizeofMutableByteArray# :: MutableByteArray# d -> Int#
- sizeofByteArray# :: ByteArray# -> Int#
- unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #)
- unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
- resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d
- mutableByteArrayContents# :: MutableByteArray# d -> Addr#
- byteArrayContents# :: ByteArray# -> Addr#
- isByteArrayPinned# :: ByteArray# -> Int#
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #)
- casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #)
- cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #)
- cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a
- copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> 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
- unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #)
- unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #)
- indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #)
- getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #)
- sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int#
- sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int#
- writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d
- readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d
- newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #)
- casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #)
- thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #)
- cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #)
- cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a
- copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> 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
- unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #)
- unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #)
- indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #)
- sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int#
- sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int#
- writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d
- readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #)
- newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #)
- fnmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fnmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fmsubDouble# :: Double# -> Double# -> Double# -> Double#
- fmaddDouble# :: Double# -> Double# -> Double# -> Double#
- fnmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fnmaddFloat# :: Float# -> Float# -> Float# -> Float#
- fmsubFloat# :: Float# -> Float# -> Float# -> Float#
- fmaddFloat# :: Float# -> Float# -> Float# -> Float#
- castWord32ToFloat# :: Word32# -> Float#
- castFloatToWord32# :: Float# -> Word32#
- decodeFloat_Int# :: Float# -> (# Int#, Int# #)
- float2Double# :: Float# -> Double#
- powerFloat# :: Float# -> Float# -> Float#
- atanhFloat# :: Float# -> Float#
- acoshFloat# :: Float# -> Float#
- asinhFloat# :: Float# -> Float#
- tanhFloat# :: Float# -> Float#
- coshFloat# :: Float# -> Float#
- sinhFloat# :: Float# -> Float#
- atanFloat# :: Float# -> Float#
- acosFloat# :: Float# -> Float#
- asinFloat# :: Float# -> Float#
- tanFloat# :: Float# -> Float#
- cosFloat# :: Float# -> Float#
- sinFloat# :: Float# -> Float#
- sqrtFloat# :: Float# -> Float#
- log1pFloat# :: Float# -> Float#
- logFloat# :: Float# -> Float#
- expm1Float# :: Float# -> Float#
- expFloat# :: Float# -> Float#
- float2Int# :: Float# -> Int#
- fabsFloat# :: Float# -> Float#
- negateFloat# :: Float# -> Float#
- divideFloat# :: Float# -> Float# -> Float#
- timesFloat# :: Float# -> Float# -> Float#
- minusFloat# :: Float# -> Float# -> Float#
- plusFloat# :: Float# -> Float# -> Float#
- leFloat# :: Float# -> Float# -> Int#
- ltFloat# :: Float# -> Float# -> Int#
- neFloat# :: Float# -> Float# -> Int#
- eqFloat# :: Float# -> Float# -> Int#
- geFloat# :: Float# -> Float# -> Int#
- gtFloat# :: Float# -> Float# -> Int#
- castWord64ToDouble# :: Word64# -> Double#
- castDoubleToWord64# :: Double# -> Word64#
- decodeDouble_Int64# :: Double# -> (# Int64#, Int# #)
- decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #)
- (**##) :: Double# -> Double# -> Double#
- atanhDouble# :: Double# -> Double#
- acoshDouble# :: Double# -> Double#
- asinhDouble# :: Double# -> Double#
- tanhDouble# :: Double# -> Double#
- coshDouble# :: Double# -> Double#
- sinhDouble# :: Double# -> Double#
- atanDouble# :: Double# -> Double#
- acosDouble# :: Double# -> Double#
- asinDouble# :: Double# -> Double#
- tanDouble# :: Double# -> Double#
- cosDouble# :: Double# -> Double#
- sinDouble# :: Double# -> Double#
- sqrtDouble# :: Double# -> Double#
- log1pDouble# :: Double# -> Double#
- logDouble# :: Double# -> Double#
- expm1Double# :: Double# -> Double#
- expDouble# :: Double# -> Double#
- double2Float# :: Double# -> Float#
- double2Int# :: Double# -> Int#
- fabsDouble# :: Double# -> Double#
- negateDouble# :: Double# -> Double#
- (/##) :: Double# -> Double# -> Double#
- (*##) :: Double# -> Double# -> Double#
- (-##) :: Double# -> Double# -> Double#
- (+##) :: Double# -> Double# -> Double#
- (<=##) :: Double# -> Double# -> Int#
- (<##) :: Double# -> Double# -> Int#
- (/=##) :: Double# -> Double# -> Int#
- (==##) :: Double# -> Double# -> Int#
- (>=##) :: Double# -> Double# -> Int#
- (>##) :: Double# -> Double# -> Int#
- narrow32Word# :: Word# -> Word#
- narrow16Word# :: Word# -> Word#
- narrow8Word# :: Word# -> Word#
- narrow32Int# :: Int# -> Int#
- narrow16Int# :: Int# -> Int#
- narrow8Int# :: Int# -> Int#
- bitReverse# :: Word# -> Word#
- bitReverse64# :: Word64# -> Word64#
- bitReverse32# :: Word# -> Word#
- bitReverse16# :: Word# -> Word#
- bitReverse8# :: Word# -> Word#
- byteSwap# :: Word# -> Word#
- byteSwap64# :: Word64# -> Word64#
- byteSwap32# :: Word# -> Word#
- byteSwap16# :: Word# -> Word#
- ctz# :: Word# -> Word#
- ctz64# :: Word64# -> Word#
- ctz32# :: Word# -> Word#
- ctz16# :: Word# -> Word#
- ctz8# :: Word# -> Word#
- clz# :: Word# -> Word#
- clz64# :: Word64# -> Word#
- clz32# :: Word# -> Word#
- clz16# :: Word# -> Word#
- clz8# :: Word# -> Word#
- pext# :: Word# -> Word# -> Word#
- pext64# :: Word64# -> Word64# -> Word64#
- pext32# :: Word# -> Word# -> Word#
- pext16# :: Word# -> Word# -> Word#
- pext8# :: Word# -> Word# -> Word#
- pdep# :: Word# -> Word# -> Word#
- pdep64# :: Word64# -> Word64# -> Word64#
- pdep32# :: Word# -> Word# -> Word#
- pdep16# :: Word# -> Word# -> Word#
- pdep8# :: Word# -> Word# -> Word#
- popCnt# :: Word# -> Word#
- popCnt64# :: Word64# -> Word#
- popCnt32# :: Word# -> Word#
- popCnt16# :: Word# -> Word#
- popCnt8# :: Word# -> Word#
- leWord# :: Word# -> Word# -> Int#
- ltWord# :: Word# -> Word# -> Int#
- neWord# :: Word# -> Word# -> Int#
- eqWord# :: Word# -> Word# -> Int#
- geWord# :: Word# -> Word# -> Int#
- gtWord# :: Word# -> Word# -> Int#
- word2Int# :: Word# -> Int#
- uncheckedShiftRL# :: Word# -> Int# -> Word#
- uncheckedShiftL# :: Word# -> Int# -> Word#
- not# :: Word# -> Word#
- xor# :: Word# -> Word# -> Word#
- or# :: Word# -> Word# -> Word#
- and# :: Word# -> Word# -> Word#
- quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
- quotRemWord# :: Word# -> Word# -> (# Word#, Word# #)
- remWord# :: Word# -> Word# -> Word#
- quotWord# :: Word# -> Word# -> Word#
- timesWord2# :: Word# -> Word# -> (# Word#, Word# #)
- timesWord# :: Word# -> Word# -> Word#
- minusWord# :: Word# -> Word# -> Word#
- plusWord2# :: Word# -> Word# -> (# Word#, Word# #)
- subWordC# :: Word# -> Word# -> (# Word#, Int# #)
- addWordC# :: Word# -> Word# -> (# Word#, Int# #)
- plusWord# :: Word# -> Word# -> Word#
- uncheckedIShiftRL# :: Int# -> Int# -> Int#
- uncheckedIShiftRA# :: Int# -> Int# -> Int#
- uncheckedIShiftL# :: Int# -> Int# -> Int#
- word2Double# :: Word# -> Double#
- word2Float# :: Word# -> Float#
- int2Double# :: Int# -> Double#
- int2Float# :: Int# -> Float#
- int2Word# :: Int# -> Word#
- chr# :: Int# -> Char#
- (<=#) :: Int# -> Int# -> Int#
- (<#) :: Int# -> Int# -> Int#
- (/=#) :: Int# -> Int# -> Int#
- (==#) :: Int# -> Int# -> Int#
- (>=#) :: Int# -> Int# -> Int#
- (>#) :: Int# -> Int# -> Int#
- subIntC# :: Int# -> Int# -> (# Int#, Int# #)
- addIntC# :: Int# -> Int# -> (# Int#, Int# #)
- negateInt# :: Int# -> Int#
- notI# :: Int# -> Int#
- xorI# :: Int# -> Int# -> Int#
- orI# :: Int# -> Int# -> Int#
- andI# :: Int# -> Int# -> Int#
- quotRemInt# :: Int# -> Int# -> (# Int#, Int# #)
- remInt# :: Int# -> Int# -> Int#
- quotInt# :: Int# -> Int# -> Int#
- mulIntMayOflo# :: Int# -> Int# -> Int#
- timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #)
- (*#) :: Int# -> Int# -> Int#
- (-#) :: Int# -> Int# -> Int#
- (+#) :: Int# -> Int# -> Int#
- neWord64# :: Word64# -> Word64# -> Int#
- ltWord64# :: Word64# -> Word64# -> Int#
- leWord64# :: Word64# -> Word64# -> Int#
- gtWord64# :: Word64# -> Word64# -> Int#
- geWord64# :: Word64# -> Word64# -> Int#
- eqWord64# :: Word64# -> Word64# -> Int#
- word64ToInt64# :: Word64# -> Int64#
- uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftL64# :: Word64# -> Int# -> Word64#
- not64# :: Word64# -> Word64#
- xor64# :: Word64# -> Word64# -> Word64#
- or64# :: Word64# -> Word64# -> Word64#
- and64# :: Word64# -> Word64# -> Word64#
- remWord64# :: Word64# -> Word64# -> Word64#
- quotWord64# :: Word64# -> Word64# -> Word64#
- timesWord64# :: Word64# -> Word64# -> Word64#
- subWord64# :: Word64# -> Word64# -> Word64#
- plusWord64# :: Word64# -> Word64# -> Word64#
- wordToWord64# :: Word# -> Word64#
- word64ToWord# :: Word64# -> Word#
- neInt64# :: Int64# -> Int64# -> Int#
- ltInt64# :: Int64# -> Int64# -> Int#
- leInt64# :: Int64# -> Int64# -> Int#
- gtInt64# :: Int64# -> Int64# -> Int#
- geInt64# :: Int64# -> Int64# -> Int#
- eqInt64# :: Int64# -> Int64# -> Int#
- int64ToWord64# :: Int64# -> Word64#
- uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- remInt64# :: Int64# -> Int64# -> Int64#
- quotInt64# :: Int64# -> Int64# -> Int64#
- timesInt64# :: Int64# -> Int64# -> Int64#
- subInt64# :: Int64# -> Int64# -> Int64#
- plusInt64# :: Int64# -> Int64# -> Int64#
- negateInt64# :: Int64# -> Int64#
- intToInt64# :: Int# -> Int64#
- int64ToInt# :: Int64# -> Int#
- neWord32# :: Word32# -> Word32# -> Int#
- ltWord32# :: Word32# -> Word32# -> Int#
- leWord32# :: Word32# -> Word32# -> Int#
- gtWord32# :: Word32# -> Word32# -> Int#
- geWord32# :: Word32# -> Word32# -> Int#
- eqWord32# :: Word32# -> Word32# -> Int#
- word32ToInt32# :: Word32# -> Int32#
- uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
- uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
- notWord32# :: Word32# -> Word32#
- xorWord32# :: Word32# -> Word32# -> Word32#
- orWord32# :: Word32# -> Word32# -> Word32#
- andWord32# :: Word32# -> Word32# -> Word32#
- quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #)
- remWord32# :: Word32# -> Word32# -> Word32#
- quotWord32# :: Word32# -> Word32# -> Word32#
- timesWord32# :: Word32# -> Word32# -> Word32#
- subWord32# :: Word32# -> Word32# -> Word32#
- plusWord32# :: Word32# -> Word32# -> Word32#
- wordToWord32# :: Word# -> Word32#
- word32ToWord# :: Word32# -> Word#
- neInt32# :: Int32# -> Int32# -> Int#
- ltInt32# :: Int32# -> Int32# -> Int#
- leInt32# :: Int32# -> Int32# -> Int#
- gtInt32# :: Int32# -> Int32# -> Int#
- geInt32# :: Int32# -> Int32# -> Int#
- eqInt32# :: Int32# -> Int32# -> Int#
- int32ToWord32# :: Int32# -> Word32#
- uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
- uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
- quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
- remInt32# :: Int32# -> Int32# -> Int32#
- quotInt32# :: Int32# -> Int32# -> Int32#
- timesInt32# :: Int32# -> Int32# -> Int32#
- subInt32# :: Int32# -> Int32# -> Int32#
- plusInt32# :: Int32# -> Int32# -> Int32#
- negateInt32# :: Int32# -> Int32#
- intToInt32# :: Int# -> Int32#
- int32ToInt# :: Int32# -> Int#
- neWord16# :: Word16# -> Word16# -> Int#
- ltWord16# :: Word16# -> Word16# -> Int#
- leWord16# :: Word16# -> Word16# -> Int#
- gtWord16# :: Word16# -> Word16# -> Int#
- geWord16# :: Word16# -> Word16# -> Int#
- eqWord16# :: Word16# -> Word16# -> Int#
- word16ToInt16# :: Word16# -> Int16#
- uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
- uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
- notWord16# :: Word16# -> Word16#
- xorWord16# :: Word16# -> Word16# -> Word16#
- orWord16# :: Word16# -> Word16# -> Word16#
- andWord16# :: Word16# -> Word16# -> Word16#
- quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #)
- remWord16# :: Word16# -> Word16# -> Word16#
- quotWord16# :: Word16# -> Word16# -> Word16#
- timesWord16# :: Word16# -> Word16# -> Word16#
- subWord16# :: Word16# -> Word16# -> Word16#
- plusWord16# :: Word16# -> Word16# -> Word16#
- wordToWord16# :: Word# -> Word16#
- word16ToWord# :: Word16# -> Word#
- neInt16# :: Int16# -> Int16# -> Int#
- ltInt16# :: Int16# -> Int16# -> Int#
- leInt16# :: Int16# -> Int16# -> Int#
- gtInt16# :: Int16# -> Int16# -> Int#
- geInt16# :: Int16# -> Int16# -> Int#
- eqInt16# :: Int16# -> Int16# -> Int#
- int16ToWord16# :: Int16# -> Word16#
- uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
- uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
- quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
- remInt16# :: Int16# -> Int16# -> Int16#
- quotInt16# :: Int16# -> Int16# -> Int16#
- timesInt16# :: Int16# -> Int16# -> Int16#
- subInt16# :: Int16# -> Int16# -> Int16#
- plusInt16# :: Int16# -> Int16# -> Int16#
- negateInt16# :: Int16# -> Int16#
- intToInt16# :: Int# -> Int16#
- int16ToInt# :: Int16# -> Int#
- neWord8# :: Word8# -> Word8# -> Int#
- ltWord8# :: Word8# -> Word8# -> Int#
- leWord8# :: Word8# -> Word8# -> Int#
- gtWord8# :: Word8# -> Word8# -> Int#
- geWord8# :: Word8# -> Word8# -> Int#
- eqWord8# :: Word8# -> Word8# -> Int#
- word8ToInt8# :: Word8# -> Int8#
- uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
- uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
- notWord8# :: Word8# -> Word8#
- xorWord8# :: Word8# -> Word8# -> Word8#
- orWord8# :: Word8# -> Word8# -> Word8#
- andWord8# :: Word8# -> Word8# -> Word8#
- quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #)
- remWord8# :: Word8# -> Word8# -> Word8#
- quotWord8# :: Word8# -> Word8# -> Word8#
- timesWord8# :: Word8# -> Word8# -> Word8#
- subWord8# :: Word8# -> Word8# -> Word8#
- plusWord8# :: Word8# -> Word8# -> Word8#
- wordToWord8# :: Word# -> Word8#
- word8ToWord# :: Word8# -> Word#
- neInt8# :: Int8# -> Int8# -> Int#
- ltInt8# :: Int8# -> Int8# -> Int#
- leInt8# :: Int8# -> Int8# -> Int#
- gtInt8# :: Int8# -> Int8# -> Int#
- geInt8# :: Int8# -> Int8# -> Int#
- eqInt8# :: Int8# -> Int8# -> Int#
- int8ToWord8# :: Int8# -> Word8#
- uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
- uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
- quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
- remInt8# :: Int8# -> Int8# -> Int8#
- quotInt8# :: Int8# -> Int8# -> Int8#
- timesInt8# :: Int8# -> Int8# -> Int8#
- subInt8# :: Int8# -> Int8# -> Int8#
- plusInt8# :: Int8# -> Int8# -> Int8#
- negateInt8# :: Int8# -> Int8#
- intToInt8# :: Int# -> Int8#
- int8ToInt# :: Int8# -> Int#
- ord# :: Char# -> Int#
- leChar# :: Char# -> Char# -> Int#
- ltChar# :: Char# -> Char# -> Int#
- neChar# :: Char# -> Char# -> Int#
- eqChar# :: Char# -> Char# -> Int#
- geChar# :: Char# -> Char# -> Int#
- gtChar# :: Char# -> Char# -> Int#
- rightSection :: forall {n :: Multiplicity} {o :: Multiplicity} a b c. (a %n -> b %o -> c) -> b %o -> a %n -> c
- leftSection :: forall {n :: Multiplicity} a b. (a %n -> b) -> a %n -> b
- proxy# :: forall {k} (a :: k). Proxy# a
- coerce :: Coercible a b => a -> b
- seq :: a -> b -> b
- nullAddr# :: Addr#
- void# :: (# #)
- realWorld# :: State# RealWorld
- module GHC.Prim.Ext
- module GHC.Prim.PtrEq
- module GHC.Internal.Err
- module GHC.Internal.Maybe
Documentation
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.
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.
Minimal complete definition
Methods
(>>=) :: 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 equivialent 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 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 ReadP Source # | @since base-2.01 |
Monad ReadPrec Source # | @since base-2.01 |
Monad IO Source # | @since base-2.01 |
Monad Maybe Source # | @since base-2.01 |
Monad Solo Source # | @since base-4.15 |
Monad [] Source # | @since base-2.01 |
ArrowApply a => Monad (ArrowMonad a) Source # | @since base-2.01 |
Defined in GHC.Internal.Control.Arrow Methods (>>=) :: 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.01 |
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.01 |
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 (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.01 |
Monad f => Monad (M1 i c f) Source # | @since base-4.9.0.0 |
(.) :: (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
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.
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.
Minimal complete definition
Methods
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 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.01 |
Functor NoIO Source # | @since base-4.8.0.0 |
Functor Par1 Source # | @since base-4.9.0.0 |
Functor ReadP Source # | @since base-2.01 |
Functor ReadPrec Source # | @since base-2.01 |
Functor IO Source # | @since base-2.01 |
Functor Maybe Source # | @since base-2.01 |
Functor Solo Source # | @since base-4.15 |
Functor [] Source # | @since base-2.01 |
Functor (Array i) Source # | @since base-2.01 |
Arrow a => Functor (ArrowMonad a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow Methods 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.01 |
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.01 |
Functor ((,) a) Source # | @since base-2.01 |
Functor m => Functor (Kleisli m a) Source # | @since base-4.14.0.0 |
Functor (Const m :: Type -> Type) Source # | @since base-2.01 |
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 Methods 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 (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.01 |
(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 (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where Source #
Monads that also support choice and failure.
Minimal complete definition
Nothing
Methods
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 ReadP Source # | @since base-2.01 |
MonadPlus ReadPrec Source # | @since base-2.01 |
MonadPlus IO Source # | Takes the first non-throwing @since base-4.9.0.0 |
MonadPlus Maybe Source # | Picks the leftmost @since base-2.01 |
MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. @since base-2.01 |
(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow Methods 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 (f :*: g) Source # | @since base-4.9.0.0 |
MonadPlus f => MonadPlus (M1 i c f) Source # | @since base-4.9.0.0 |
sequence :: Monad m => [m a] -> m [a] Source #
Evaluate each action in the sequence from left to right, and collect the results.
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 Source #
Same as >>=
, but with the arguments interchanged.
as >>= f == f =<< as
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
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:
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 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.
Methods
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 All Source # | @since base-2.01 |
Monoid Any Source # | @since base-2.01 |
Monoid Event Source # | @since base-4.4.0.0 |
Monoid Lifetime Source # |
@since base-4.8.0.0 |
Monoid ExceptionContext Source # | |
Defined in GHC.Internal.Exception.Context Methods mempty :: ExceptionContext Source # mappend :: ExceptionContext -> ExceptionContext -> ExceptionContext Source # mconcat :: [ExceptionContext] -> ExceptionContext Source # | |
Monoid Ordering Source # | @since base-2.01 |
Monoid () Source # | @since base-2.01 |
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.01 |
Monoid (Last a) Source # | @since base-2.01 |
Monoid a => Monoid (Down a) Source # | @since base-4.11.0.0 |
Monoid a => Monoid (Dual a) Source # | @since base-2.01 |
Monoid (Endo a) Source # | @since base-2.01 |
Num a => Monoid (Product a) Source # | @since base-2.01 |
Num a => Monoid (Sum a) Source # | @since base-2.01 |
(Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source # | @since base-4.17.0.0 |
Defined in GHC.Internal.Generics Methods 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 (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.01 |
Monoid a => Monoid (Solo a) Source # | @since base-4.15 |
Monoid [a] Source # | @since base-2.01 |
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.01 |
Monoid b => Monoid (a -> b) Source # | @since base-2.01 |
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.01 |
(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.01 |
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.01 |
Non-empty (and non-strict) list type.
@since base-4.9.0.0
Constructors
a :| [a] infixr 5 |
Instances
($) :: (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
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)...)
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]
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"
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).
Methods
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 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.01 |
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 ReadP Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Text.ParserCombinators.ReadP | |
Applicative ReadPrec Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Text.ParserCombinators.ReadPrec | |
Applicative IO Source # | @since base-2.01 |
Applicative Maybe Source # | @since base-2.01 |
Applicative Solo Source # | @since base-4.15 |
Applicative [] Source # | @since base-2.01 |
Arrow a => Applicative (ArrowMonad a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow Methods 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.01 |
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.01 |
Applicative m => Applicative (Kleisli m a) Source # | @since base-4.14.0.0 |
Defined in GHC.Internal.Control.Arrow Methods 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 Methods 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 Methods 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 (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 Methods 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.01 |
(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 |
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
Methods
(<>) :: 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 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 Lifetime Source # | @since base-4.10.0.0 |
Semigroup ExceptionContext Source # | |
Defined in GHC.Internal.Exception.Context Methods (<>) :: 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 (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 Methods (<>) :: 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 (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 (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 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 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 |
(++) :: [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]
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]
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 Methods 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 Methods 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 |
Defined in GHC.Internal.Ix | |
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 |
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
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
Methods
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 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.01 |
Alternative [] Source # | Combines lists by concatenation, starting from the empty list. @since base-2.01 |
ArrowPlus a => Alternative (ArrowMonad a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow Methods 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 |
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 Methods 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 (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 |
($!) :: (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.
shiftL# :: Word# -> Int# -> Word# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word# Source #
Shift the argument right by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic) (although an arithmetic right shift wouldn't make sense for Word#)
iShiftL# :: Int# -> Int# -> Int# Source #
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int# Source #
Shift the argument right (signed) by the specified number of bits (which must be non-negative). The RA means "right, arithmetic" (as opposed to RL for logical)
iShiftRL# :: Int# -> Int# -> Int# Source #
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic)
breakpoint :: a -> a Source #
breakpointCond :: Bool -> a -> a Source #
(<**>) :: 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.
eqString :: String -> String -> Bool Source #
This String
equality predicate is used when desugaring
pattern-matches against strings.
until :: (a -> Bool) -> (a -> a) -> a -> a Source #
yields the result of applying until
p ff
until p
holds.
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
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 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 Methods (==) :: ClosureType -> ClosureType -> Bool Source # (/=) :: ClosureType -> ClosureType -> Bool Source # | |
Eq BlockReason Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.Conc.Sync Methods (==) :: 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 Methods (==) :: 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.01 |
Eq Any Source # | @since base-2.01 |
Eq SomeTypeRep Source # | |
Defined in GHC.Internal.Data.Typeable.Internal Methods (==) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (/=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # | |
Eq Unique Source # | |
Eq Version Source # | @since base-2.01 |
Eq Event Source # | @since base-4.4.0.0 |
Eq Lifetime Source # | @since base-4.8.1.0 |
Eq FdKey Source # | @since base-4.4.0.0 |
Eq TimeoutKey Source # | |
Defined in GHC.Internal.Event.TimeOut Methods (==) :: TimeoutKey -> TimeoutKey -> Bool Source # (/=) :: TimeoutKey -> TimeoutKey -> Bool Source # | |
Eq ErrorCall Source # | @since base-4.7.0.0 |
Eq ArithException Source # | @since base-3.0 |
Defined in GHC.Internal.Exception.Type Methods (==) :: ArithException -> ArithException -> Bool Source # (/=) :: ArithException -> ArithException -> Bool Source # | |
Eq SpecConstrAnnotation Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.Exts Methods (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # | |
Eq Fingerprint Source # | @since base-4.4.0.0 |
Defined in GHC.Internal.Fingerprint.Type Methods (==) :: Fingerprint -> Fingerprint -> Bool Source # (/=) :: Fingerprint -> Fingerprint -> Bool Source # | |
Eq Errno Source # | @since base-2.01 |
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 Methods (==) :: CSUSeconds -> CSUSeconds -> Bool Source # (/=) :: CSUSeconds -> CSUSeconds -> Bool Source # | |
Eq CShort Source # | |
Eq CSigAtomic Source # | |
Defined in GHC.Internal.Foreign.C.Types Methods (==) :: 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 Associativity Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Generics Methods (==) :: Associativity -> Associativity -> Bool Source # (/=) :: Associativity -> Associativity -> Bool Source # | |
Eq DecidedStrictness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods (==) :: 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 Methods (==) :: SourceStrictness -> SourceStrictness -> Bool Source # (/=) :: SourceStrictness -> SourceStrictness -> Bool Source # | |
Eq SourceUnpackedness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # | |
Eq MaskingState Source # | @since base-4.3.0.0 |
Defined in GHC.Internal.IO Methods (==) :: MaskingState -> MaskingState -> Bool Source # (/=) :: MaskingState -> MaskingState -> Bool Source # | |
Eq BufferState Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Buffer Methods (==) :: BufferState -> BufferState -> Bool Source # (/=) :: BufferState -> BufferState -> Bool Source # | |
Eq IODeviceType Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Device Methods (==) :: 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 Methods (==) :: CodingProgress -> CodingProgress -> Bool Source # (/=) :: CodingProgress -> CodingProgress -> Bool Source # | |
Eq ArrayException Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception Methods (==) :: ArrayException -> ArrayException -> Bool Source # (/=) :: ArrayException -> ArrayException -> Bool Source # | |
Eq AsyncException Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Exception Methods (==) :: 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 Methods (==) :: IOErrorType -> IOErrorType -> Bool Source # (/=) :: IOErrorType -> IOErrorType -> Bool Source # | |
Eq IOException Source # | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Exception Methods (==) :: IOException -> IOException -> Bool Source # (/=) :: IOException -> IOException -> Bool Source # | |
Eq HandlePosn Source # | @since base-4.1.0.0 |
Defined in GHC.Internal.IO.Handle Methods (==) :: HandlePosn -> HandlePosn -> Bool Source # (/=) :: HandlePosn -> HandlePosn -> Bool Source # | |
Eq BufferMode Source # | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types Methods (==) :: 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 Methods (==) :: NewlineMode -> NewlineMode -> Bool Source # (/=) :: NewlineMode -> NewlineMode -> Bool Source # | |
Eq IOMode Source # | @since base-4.2.0.0 |
Eq InfoProv Source # | |
Eq Int16 Source # | @since base-2.01 |
Eq Int32 Source # | @since base-2.01 |
Eq Int64 Source # | @since base-2.01 |
Eq Int8 Source # | @since base-2.01 |
Eq IoSubSystem Source # | |
Defined in GHC.Internal.RTS.Flags Methods (==) :: IoSubSystem -> IoSubSystem -> Bool Source # (/=) :: IoSubSystem -> IoSubSystem -> Bool Source # | |
Eq StackEntry Source # | |
Defined in GHC.Internal.Stack.CloneStack Methods (==) :: 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 Lexeme Source # | @since base-2.01 |
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 Methods (==) :: SomeSymbol -> SomeSymbol -> Bool Source # (/=) :: SomeSymbol -> SomeSymbol -> Bool Source # | |
Eq SomeNat Source # | @since base-4.7.0.0 |
Eq GeneralCategory Source # | @since base-2.01 |
Defined in GHC.Internal.Unicode Methods (==) :: GeneralCategory -> GeneralCategory -> Bool Source # (/=) :: GeneralCategory -> GeneralCategory -> Bool Source # | |
Eq Word16 Source # | @since base-2.01 |
Eq Word32 Source # | @since base-2.01 |
Eq Word64 Source # | @since base-2.01 |
Eq Word8 Source # | @since base-2.01 |
Eq Module | |
Eq Ordering | |
Eq TrName | |
Eq TyCon | |
Eq Integer | |
Eq Natural | |
Eq () | |
Eq Bool | |
Eq Char | |
Eq Double | Note that due to the presence of
Also note that
|
Eq Float | Note that due to the presence of
Also note that
|
Eq Int | |
Eq Word | |
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.01 |
Eq a => Eq (Last a) Source # | @since base-2.01 |
Eq a => Eq (Down a) Source # | @since base-4.6.0.0 |
Eq a => Eq (Dual a) Source # | @since base-2.01 |
Eq a => Eq (Product a) Source # | @since base-2.01 |
Eq a => Eq (Sum a) Source # | @since base-2.01 |
Eq (ConstPtr a) Source # | |
Eq (ForeignPtr a) Source # | @since base-2.01 |
Defined in GHC.Internal.ForeignPtr Methods (==) :: 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 (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.01 |
Eq a => Eq (Ratio a) Source # | @since base-2.01 |
Eq (StablePtr a) Source # | @since base-2.01 |
Eq (StableName a) Source # | @since base-2.01 |
Defined in GHC.Internal.StableName Methods (==) :: StableName a -> StableName a -> Bool Source # (/=) :: StableName a -> StableName a -> Bool 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.01 |
Eq a => Eq (Solo a) | |
Eq a => Eq [a] | |
(Ix i, Eq e) => Eq (Array i e) Source # | @since base-2.01 |
(Eq a, Eq b) => Eq (Either a b) Source # | @since base-2.01 |
Eq (Proxy s) Source # | @since base-4.7.0.0 |
Eq (TypeRep a) Source # | @since base-2.01 |
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.01 |
(Eq a, Eq b) => Eq (a, b) | |
Eq (STArray s i e) Source # | @since base-2.01 |
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 Methods (==) :: 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) | |
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) | |
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) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
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 (==)
.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Methods
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 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 Methods 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 Methods 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 Methods 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.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord Any Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord SomeTypeRep Source # | |
Defined in GHC.Internal.Data.Typeable.Internal Methods 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 # | |
Ord Version Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Version | |
Ord TimeoutKey Source # | |
Defined in GHC.Internal.Event.TimeOut Methods 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 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 Methods 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 Methods 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 # | |
Ord CDouble Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CFloat Source # | |
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 # | |
Ord CLong Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CPtrdiff Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CSChar Source # | |
Ord CSUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types Methods 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 # | |
Ord CSigAtomic Source # | |
Defined in GHC.Internal.Foreign.C.Types Methods 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 # | |
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 # | |
Ord CUSeconds Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CUShort Source # | |
Defined in GHC.Internal.Foreign.C.Types | |
Ord CWchar Source # | |
Ord IntPtr Source # | |
Ord WordPtr Source # | |
Defined in GHC.Internal.Foreign.Ptr | |
Ord Associativity Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Generics Methods 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 Methods 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 |
Ord SourceStrictness Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 |
Ord Int16 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int32 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int64 Source # | @since base-2.01 |
Defined in GHC.Internal.Int | |
Ord Int8 Source # | @since base-2.01 |
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 SomeChar Source # | |
Defined in GHC.Internal.TypeLits | |
Ord SomeSymbol Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.TypeLits Methods 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 |
Defined in GHC.Internal.TypeNats | |
Ord GeneralCategory Source # | @since base-2.01 |
Defined in GHC.Internal.Unicode Methods 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.01 |
Ord Word32 Source # | @since base-2.01 |
Ord Word64 Source # | @since base-2.01 |
Ord Word8 Source # | @since base-2.01 |
Defined in GHC.Internal.Word | |
Ord Ordering | |
Defined in GHC.Classes | |
Ord TyCon | |
Defined in GHC.Classes | |
Ord Integer | |
Ord Natural | |
Ord () | |
Ord Bool | |
Ord Char | |
Ord Double | 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 |
Ord Float | See |
Defined in GHC.Classes | |
Ord Int | |
Ord Word | |
Ord a => Ord (NonEmpty a) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Base Methods 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 Methods 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.01 |
Defined in GHC.Internal.Data.Monoid | |
Ord a => Ord (Last a) Source # | @since base-2.01 |
Ord a => Ord (Down a) Source # | @since base-4.6.0.0 |
Ord a => Ord (Dual a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Product a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord a => Ord (Sum a) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
Ord (ConstPtr a) Source # | |
Defined in GHC.Internal.Foreign.C.ConstPtr Methods 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.01 |
Defined in GHC.Internal.ForeignPtr Methods 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 |
Ord (FunPtr a) Source # | |
Defined in GHC.Internal.Ptr | |
Ord (Ptr a) Source # | @since base-2.01 |
Defined in GHC.Internal.Ptr | |
Integral a => Ord (Ratio a) Source # | @since base-2.0.1 |
Defined in GHC.Internal.Real | |
Ord (SChar c) Source # | @since base-4.19.0.0 |
Defined in GHC.Internal.TypeLits | |
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 |
Ord a => Ord (Maybe a) Source # | @since base-2.01 |
Defined in GHC.Internal.Maybe | |
Ord a => Ord (Solo a) | |
Ord a => Ord [a] | |
(Ix i, Ord e) => Ord (Array i e) Source # | @since base-2.01 |
Defined in GHC.Internal.Arr | |
(Ord a, Ord b) => Ord (Either a b) Source # | @since base-2.01 |
Defined in GHC.Internal.Data.Either Methods 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 |
Defined in GHC.Internal.Generics | |
Ord (V1 p) Source # | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
(Ord a, Ord b) => Ord (a, b) | |
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 |
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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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) | |
Defined in GHC.Classes | |
Ord (a :~~: b) Source # | @since base-4.10.0.0 |
Defined in GHC.Internal.Data.Type.Equality Methods 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 Methods 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 Methods 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) | |
Defined in GHC.Classes Methods 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 p)) => Ord ((f :.: g) p) Source # | @since base-4.7.0.0 |
Defined in GHC.Internal.Generics Methods 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 Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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) | |
Defined in GHC.Classes Methods 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 # |
module GHC.CString
module GHC.Magic
module GHC.Magic.Dict
Instances
Bits Word Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Bits Methods (.&.) :: 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 Methods 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 Methods 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.01 | ||||
Enum Word Source # | @since base-2.01 | ||||
Storable Word Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Foreign.Storable Methods 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 | ||||
Defined in GHC.Internal.Ix | |||||
Num Word Source # | @since base-2.01 | ||||
Read Word Source # | @since base-4.5.0.0 | ||||
Integral Word Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Real | |||||
Real Word Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Real Methods toRational :: Word -> Rational Source # | |||||
Show Word Source # | @since base-2.01 | ||||
Eq Word | |||||
Ord Word | |||||
Generic1 (URec Word :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Foldable (UWord :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Associated Types
| |||||
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 Methods 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 |
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
Data Float Source # | @since base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods 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 # | |||||
Enum Float Source # | @since base-2.01
List generators have extremely peculiar behavior, mandated by Haskell Report 2010:
| ||||
Defined in GHC.Internal.Float Methods succ :: Float -> Float Source # pred :: Float -> Float Source # toEnum :: Int -> Float Source # fromEnum :: Float -> Int Source # enumFrom :: Float -> [Float] Source # enumFromThen :: Float -> Float -> [Float] Source # enumFromTo :: Float -> Float -> [Float] Source # enumFromThenTo :: Float -> Float -> Float -> [Float] Source # | |||||
Floating Float Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Float Methods 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.01 | ||||
Defined in GHC.Internal.Float Methods 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.01 | ||||
Defined in GHC.Internal.Foreign.Storable Methods 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 # | |||||
Num Float Source # | @since base-2.01 This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:
| ||||
Read Float Source # | @since base-2.01 | ||||
Fractional Float Source # | @since base-2.01 This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.
| ||||
Real Float Source # | @since base-2.01 Beware that
| ||||
Defined in GHC.Internal.Float Methods toRational :: Float -> Rational Source # | |||||
RealFrac Float Source # | @since base-2.01 Beware that results for non-finite arguments are garbage:
and get even more non-sensical if you ask for | ||||
Show Float Source # | @since base-2.01 | ||||
Eq Float | Note that due to the presence of
Also note that
| ||||
Ord Float | See | ||||
Defined in GHC.Classes | |||||
Generic1 (URec Float :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Foldable (UFloat :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Associated Types
| |||||
Show (URec Float p) Source # | |||||
Eq (URec Float p) Source # | |||||
Ord (URec Float p) Source # | |||||
Defined in GHC.Internal.Generics Methods 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
Bits Int Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Bits Methods (.&.) :: 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 Methods 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 Methods 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.01 | ||||
Enum Int Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Enum | |||||
Storable Int Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Foreign.Storable | |||||
Ix Int Source # | @since base-2.01 | ||||
Num Int Source # | @since base-2.01 | ||||
Read Int Source # | @since base-2.01 | ||||
Integral Int Source # | @since base-2.0.1 | ||||
Real Int Source # | @since base-2.0.1 | ||||
Defined in GHC.Internal.Real Methods toRational :: Int -> Rational Source # | |||||
Show Int Source # | @since base-2.01 | ||||
Eq Int | |||||
Ord Int | |||||
Generic1 (URec Int :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Foldable (UInt :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
Functor (URec Int :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Generic (URec Int p) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
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 Methods 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 |
data TYPE (a :: RuntimeRep) Source #
Instances
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Identity Source # | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
Generic1 First Source # | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic1 Last Source # | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 ZipList Source # | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Solo Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source # | @since base-3.0 | ||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Category (->) Source # | @since base-3.0 | ||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Control.Arrow Associated Types
| |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 # | |||||
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 | ||||
Foldable (Proxy :: Type -> Type) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
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 | ||||
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 Methods 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 Methods 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.01 | ||||
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 Methods 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 | ||||
Data t => Data (Proxy t) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | @since base-4.9.0.0 | ||||
(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 (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 (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 (f :*: g) Source # | @since base-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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 (f :*: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 Methods 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 (f :*: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source # sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source # sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) Source # | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source # sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source # sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) Source # | |||||
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 | |||||
(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 (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 (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 | ||||
(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 Methods 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 Methods 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 Methods 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 (f :.: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 (f :.: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source # sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source # sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) Source # | |||||
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 Methods 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 Methods 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 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 (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 (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 (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 CONSTRAINT (a :: RuntimeRep) Source #
Data type Dict
provides a simple way to wrap up a (lifted)
constraint as a type
Constructors
a => MkDictBox |
Instances
Bits Bool Source # | Interpret @since base-4.7.0.0 |
Defined in GHC.Internal.Bits Methods (.&.) :: 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 Methods 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 Methods 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.01 |
Enum Bool Source # | @since base-2.01 |
Storable Bool Source # | @since base-2.01 |
Defined in GHC.Internal.Foreign.Storable Methods 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 | |
Ix Bool Source # | @since base-2.01 |
Defined in GHC.Internal.Ix | |
Read Bool Source # | @since base-2.01 |
Show Bool Source # | @since base-2.01 |
Eq Bool | |
Ord Bool | |
type Rep Bool Source # | @since base-4.6.0.0 |
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
Data Char Source # | @since base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods 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.01 | ||||
Enum Char Source # | @since base-2.01 | ||||
Storable Char Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Foreign.Storable Methods 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.01 | ||||
Defined in GHC.Internal.Ix | |||||
Read Char Source # | @since base-2.01 | ||||
Show Char Source # | @since base-2.01 | ||||
Eq Char | |||||
Ord Char | |||||
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 | |||||
Generic1 (URec Char :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Foldable (UChar :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Associated Types
| |||||
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 Methods 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 |
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
Data Double Source # | @since base-4.0.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods 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 # | |||||
Enum Double Source # | @since base-2.01
List generators have extremely peculiar behavior, mandated by Haskell Report 2010:
| ||||
Defined in GHC.Internal.Float Methods succ :: Double -> Double Source # pred :: Double -> Double Source # toEnum :: Int -> Double Source # fromEnum :: Double -> Int Source # enumFrom :: Double -> [Double] Source # enumFromThen :: Double -> Double -> [Double] Source # enumFromTo :: Double -> Double -> [Double] Source # enumFromThenTo :: Double -> Double -> Double -> [Double] Source # | |||||
Floating Double Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Float Methods 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.01 | ||||
Defined in GHC.Internal.Float Methods 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.01 | ||||
Defined in GHC.Internal.Foreign.Storable Methods 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 # | |||||
Num Double Source # | @since base-2.01 This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:
| ||||
Defined in GHC.Internal.Float | |||||
Read Double Source # | @since base-2.01 | ||||
Fractional Double Source # | @since base-2.01 This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.
| ||||
Real Double Source # | @since base-2.01 Beware that
| ||||
Defined in GHC.Internal.Float Methods toRational :: Double -> Rational Source # | |||||
RealFrac Double Source # | @since base-2.01 Beware that results for non-finite arguments are garbage:
and get even more non-sensical if you ask for | ||||
Show Double Source # | @since base-2.01 | ||||
Eq Double | Note that due to the presence of
Also note that
| ||||
Ord Double | 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 | ||||
Generic1 (URec Double :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Foldable (UDouble :: Type -> Type) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Associated Types
| |||||
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 Methods 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 |
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
Alternative [] Source # | Combines lists by concatenation, starting from the empty list. @since base-2.01 | ||||
Applicative [] Source # | @since base-2.01 | ||||
Functor [] Source # | @since base-2.01 | ||||
Monad [] Source # | @since base-2.01 | ||||
MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. @since base-2.01 | ||||
MonadFail [] Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Control.Monad.Fail | |||||
MonadFix [] Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
Foldable [] Source # | @since base-2.01 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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.01 | ||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Monoid [a] Source # | @since base-2.01 | ||||
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 Methods 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.01 | ||||
Defined in GHC.Internal.Data.String Methods fromString :: String -> [a] Source # | |||||
Generic [a] Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
IsList [a] Source # | @since base-4.7.0.0 | ||||
Read a => Read [a] Source # | @since base-2.01 | ||||
Show a => Show [a] Source # | @since base-2.01 | ||||
Eq a => Eq [a] | |||||
Ord a => Ord [a] | |||||
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 |
Instances
Monoid Ordering Source # | @since base-2.01 |
Semigroup Ordering Source # | @since base-4.9.0.0 |
Data Ordering Source # | @since base-4.0.0.0 |
Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering Source # toConstr :: Ordering -> Constr Source # dataTypeOf :: Ordering -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) Source # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering Source # | |
Bounded Ordering Source # | @since base-2.01 |
Enum Ordering Source # | @since base-2.01 |
Defined in GHC.Internal.Enum Methods succ :: Ordering -> Ordering Source # pred :: Ordering -> Ordering Source # toEnum :: Int -> Ordering Source # fromEnum :: Ordering -> Int Source # enumFrom :: Ordering -> [Ordering] Source # enumFromThen :: Ordering -> Ordering -> [Ordering] Source # enumFromTo :: Ordering -> Ordering -> [Ordering] Source # enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source # | |
Generic Ordering Source # | |
Defined in GHC.Internal.Generics | |
Ix Ordering Source # | @since base-2.01 |
Defined in GHC.Internal.Ix | |
Read Ordering Source # | @since base-2.01 |
Show Ordering Source # | @since base-2.01 |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
type Rep Ordering Source # | @since base-4.6.0.0 |
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 :~~:
.
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 ~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
(Kind) This is the kind of type-level symbols.
Instances
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 | |
type Compare (a :: Symbol) (b :: Symbol) Source # | |
Defined in GHC.Internal.Data.Type.Ord |
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).
Constructors
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 |
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 Methods 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 |
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 Methods 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
Constructors
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 Methods 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 |
data Multiplicity Source #
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 #
Constructors
TypeLitSymbol | |
TypeLitNat | |
TypeLitChar |
Instances
Show TypeLitSort Source # | @since base-4.11.0.0 |
Defined in GHC.Internal.Show |
The representation produced by GHC for conjuring up the kind of a
TypeRep
.
Constructors
TyCon | |
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
Alternative IO Source # | Takes the first non-throwing @since base-4.9.0.0 |
Applicative IO Source # | @since base-2.01 |
Functor IO Source # | @since base-2.01 |
Monad IO Source # | @since base-2.01 |
MonadPlus IO Source # | Takes the first non-throwing @since base-4.9.0.0 |
MonadFail IO Source # | @since base-4.9.0.0 |
MonadFix IO Source # | @since base-2.01 |
GHCiSandboxIO IO Source # | @since base-4.4.0.0 |
Defined in GHC.Internal.GHCi Methods ghciStepIO :: IO a -> IO a Source # | |
Monoid a => Monoid (IO a) Source # | @since base-4.9.0.0 |
Semigroup a => Semigroup (IO a) Source # | @since base-4.10.0.0 |
type ZeroBitType = TYPE ZeroBitRep Source #
The kind of the empty unboxed tuple type (# #)
type ZeroBitRep = 'TupleRep ('[] :: [RuntimeRep]) Source #
The runtime representation of a zero-width tuple, represented by no bits at all
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
.
type Constraint = CONSTRAINT LiftedRep Source #
The kind of lifted constraints
type family Any :: k where ... Source #
The type constructor Any
is type to which you can unsafely coerce any
lifted type, and back. More concretely, for a lifted type t
and
value x :: t
, unsafeCoerce (unsafeCoerce x :: Any) :: t
is equivalent
to x
.
type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ... Source #
isTrue# :: Int# -> Bool Source #
Alias for tagToEnum#
. Returns True if its parameter is 1# and False
if it is 0#.
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 SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
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 SmallMutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #
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 StableName# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #
data Compact# :: UnliftedType Source #
data State# a :: ZeroBitType Source #
data Proxy# (a :: k) :: ZeroBitType Source #
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 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 PromptTag# a :: UnliftedType Source #
See GHC.Prim.
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 |
Monoid b => Monoid (a -> b) Source # | @since base-2.01 |
Semigroup b => Semigroup (a -> b) Source # | @since base-4.9.0.0 |
Arrow (->) Source # | @since base-2.01 |
ArrowApply (->) Source # | @since base-2.01 |
Defined in GHC.Internal.Control.Arrow | |
ArrowChoice (->) Source # | @since base-2.01 |
ArrowLoop (->) Source # | @since base-2.01 |
Defined in GHC.Internal.Control.Arrow | |
Applicative ((->) r) Source # | @since base-2.01 |
Functor ((->) r) Source # | @since base-2.01 |
Monad ((->) r) Source # | @since base-2.01 |
MonadFix ((->) r) Source # | @since base-2.01 |
Defined in GHC.Internal.Control.Monad.Fix |
data TYPE (a :: RuntimeRep) Source #
Instances
Generic1 NonEmpty Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Identity Source # | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
Generic1 First Source # | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic1 Last Source # | |||||
Defined in GHC.Internal.Data.Monoid Associated Types
| |||||
Generic1 Down Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Dual Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 Product Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 Sum Source # | |||||
Defined in GHC.Internal.Data.Semigroup.Internal Associated Types
| |||||
Generic1 ZipList Source # | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
Generic1 Par1 Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Maybe Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 Solo Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 [] Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source # | @since base-3.0 | ||||
Generic1 (Either a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,) a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Category (->) Source # | @since base-3.0 | ||||
Generic1 (Kleisli m a :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Control.Arrow Associated Types
| |||||
Generic1 ((,,) a b :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,) a b c :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,) a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Functor f => Generic1 (f :.: g :: k -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
| |||||
Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Internal.Generics Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 Associated Types
Methods 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 # | |||||
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 | ||||
Foldable (Proxy :: Type -> Type) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
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 | ||||
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 Methods 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 Methods 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.01 | ||||
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 Methods 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 | ||||
Data t => Data (Proxy t) Source # | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Data.Data Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) Source # | @since base-4.9.0.0 | ||||
(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 (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 (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 (f :*: g) Source # | @since base-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 Methods 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 Methods 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 Methods 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 Methods 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 Methods 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 (f :*: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 Methods 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 (f :*: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source # sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source # sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) Source # | |||||
(Traversable f, Traversable g) => Traversable (f :+: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source # sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source # sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) Source # | |||||
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 | |||||
(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 (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 (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 | ||||
(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 Methods 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 Methods 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 Methods 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 (f :.: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable Methods 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 Methods 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 (f :.: g) Source # | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable Methods traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source # sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source # mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source # sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) Source # | |||||
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 Methods 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 Methods 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 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 (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 (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 (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 CONSTRAINT (a :: RuntimeRep) Source #
data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep) Source #
Warning: this is only available on LLVM.
data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep) Source #
Warning: this is only available on LLVM.
data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep) Source #
Warning: this is only available on LLVM.
data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep) Source #
Warning: this is only available on LLVM.
data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep) Source #
Warning: this is only available on LLVM.
data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep) Source #
Warning: this is only available on LLVM.
data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep) Source #
Warning: this is only available on LLVM.
data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep) Source #
Warning: this is only available on LLVM.
data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep) Source #
Warning: this is only available on LLVM.
prefetchValue0# :: a -> State# d -> State# d Source #
prefetchMutableByteArray0# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray0# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue1# :: a -> State# d -> State# d Source #
prefetchMutableByteArray1# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue2# :: a -> State# d -> State# d Source #
prefetchMutableByteArray2# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# d -> State# d Source #
prefetchValue3# :: a -> State# d -> State# d Source #
prefetchMutableByteArray3# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #
prefetchByteArray3# :: ByteArray# -> Int# -> State# d -> State# d Source #
writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in scalar elements.
Warning: this is only available on LLVM.
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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and can fail with an unchecked exception.
indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# Source #
Read a vector from specified index of immutable array of scalars; offset is in scalar elements.
Warning: this is only available on LLVM.
writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# d -> State# d Source #
Write vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readDoubleX2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readFloatX4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readWord8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt64X2OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt32X4OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt16X8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
readInt8X16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM and can fail with an unchecked exception.
indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# Source #
Reads vector; offset in bytes.
Warning: this is only available on LLVM.
writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #
Write a vector to specified index of mutable array.
Warning: this is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and 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 is only available on LLVM and can fail with an unchecked exception.
indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #
Read a vector from specified index of immutable array.
Warning: this is only available on LLVM.
indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16#