ghc-internal-9.1001.0: Basic libraries
Copyright(c) The University of Glasgow 1992-2002
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC extensions)
Safe HaskellUnsafe
LanguageHaskell2010

GHC.Internal.Base

Description

Basic data types and classes.

Synopsis

Documentation

type String = [Char] Source #

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

Expand

[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 >>= bs' can be understood as the do 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 >> bs' can be understood as the do expression

do as
   bs

or in terms of (>>=) as

as >>= const bs

return :: a -> m a Source #

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

Instances details
Monad NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b Source #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b Source #

return :: a -> NonEmpty a Source #

Monad STM Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(>>=) :: STM a -> (a -> STM b) -> STM b Source #

(>>) :: STM a -> STM b -> STM b Source #

return :: a -> STM a Source #

Monad Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b Source #

(>>) :: Identity a -> Identity b -> Identity b Source #

return :: a -> Identity a Source #

Monad First Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(>>=) :: First a -> (a -> First b) -> First b Source #

(>>) :: First a -> First b -> First b Source #

return :: a -> First a Source #

Monad Last Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b Source #

(>>) :: Last a -> Last b -> Last b Source #

return :: a -> Last a Source #

Monad Down Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(>>=) :: Down a -> (a -> Down b) -> Down b Source #

(>>) :: Down a -> Down b -> Down b Source #

return :: a -> Down a Source #

Monad Dual Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b Source #

(>>) :: Dual a -> Dual b -> Dual b Source #

return :: a -> Dual a Source #

Monad Product Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b Source #

(>>) :: Product a -> Product b -> Product b Source #

return :: a -> Product a Source #

Monad Sum Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b Source #

(>>) :: Sum a -> Sum b -> Sum b Source #

return :: a -> Sum a Source #

Monad NoIO Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.GHCi

Methods

(>>=) :: NoIO a -> (a -> NoIO b) -> NoIO b Source #

(>>) :: NoIO a -> NoIO b -> NoIO b Source #

return :: a -> NoIO a Source #

Monad Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: Par1 a -> (a -> Par1 b) -> Par1 b Source #

(>>) :: Par1 a -> Par1 b -> Par1 b Source #

return :: a -> Par1 a Source #

Monad ReadP Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

(>>=) :: ReadP a -> (a -> ReadP b) -> ReadP b Source #

(>>) :: ReadP a -> ReadP b -> ReadP b Source #

return :: a -> ReadP a Source #

Monad ReadPrec Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

Methods

(>>=) :: ReadPrec a -> (a -> ReadPrec b) -> ReadPrec b Source #

(>>) :: ReadPrec a -> ReadPrec b -> ReadPrec b Source #

return :: a -> ReadPrec a Source #

Monad IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b Source #

(>>) :: IO a -> IO b -> IO b Source #

return :: a -> IO a Source #

Monad Maybe Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b Source #

(>>) :: Maybe a -> Maybe b -> Maybe b Source #

return :: a -> Maybe a Source #

Monad Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: Solo a -> (a -> Solo b) -> Solo b Source #

(>>) :: Solo a -> Solo b -> Solo b Source #

return :: a -> Solo a Source #

Monad [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: [a] -> (a -> [b]) -> [b] Source #

(>>) :: [a] -> [b] -> [b] Source #

return :: a -> [a] Source #

ArrowApply a => Monad (ArrowMonad a) Source #

@since base-2.01

Instance details

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

Instance details

Defined in GHC.Internal.Control.Monad.ST.Lazy.Imp

Methods

(>>=) :: ST s a -> (a -> ST s b) -> ST s b Source #

(>>) :: ST s a -> ST s b -> ST s b Source #

return :: a -> ST s a Source #

Monad (Either e) Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b Source #

(>>) :: Either e a -> Either e b -> Either e b Source #

return :: a -> Either e a Source #

Monad (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source #

(>>) :: Proxy a -> Proxy b -> Proxy b Source #

return :: a -> Proxy a Source #

Monad (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: U1 a -> (a -> U1 b) -> U1 b Source #

(>>) :: U1 a -> U1 b -> U1 b Source #

return :: a -> U1 a Source #

Monad (ST s) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ST

Methods

(>>=) :: ST s a -> (a -> ST s b) -> ST s b Source #

(>>) :: ST s a -> ST s b -> ST s b Source #

return :: a -> ST s a Source #

Monoid a => Monad ((,) a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: (a, a0) -> (a0 -> (a, b)) -> (a, b) Source #

(>>) :: (a, a0) -> (a, b) -> (a, b) Source #

return :: a0 -> (a, a0) Source #

Monad m => Monad (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

(>>=) :: Kleisli m a a0 -> (a0 -> Kleisli m a b) -> Kleisli m a b Source #

(>>) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a b Source #

return :: a0 -> Kleisli m a a0 Source #

Monad m => Monad (StateT s m) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b Source #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b Source #

return :: a -> StateT s m a Source #

Monad f => Monad (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b Source #

(>>) :: Ap f a -> Ap f b -> Ap f b Source #

return :: a -> Ap f a Source #

Monad f => Monad (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b Source #

(>>) :: Alt f a -> Alt f b -> Alt f b Source #

return :: a -> Alt f a Source #

Monad f => Monad (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b Source #

(>>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

return :: a -> Rec1 f a Source #

(Monoid a, Monoid b) => Monad ((,,) a b) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: (a, b, a0) -> (a0 -> (a, b, b0)) -> (a, b, b0) Source #

(>>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

return :: a0 -> (a, b, a0) Source #

(Monad f, Monad g) => Monad (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b Source #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

return :: a -> (f :*: g) a Source #

(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: (a, b, c, a0) -> (a0 -> (a, b, c, b0)) -> (a, b, c, b0) Source #

(>>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source #

return :: a0 -> (a, b, c, a0) Source #

Monad ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b Source #

(>>) :: (r -> a) -> (r -> b) -> r -> b Source #

return :: a -> r -> a Source #

Monad f => Monad (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b Source #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

return :: a -> M1 i c f a Source #

(.) :: (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

Expand
>>> map ((*2) . length) [[], [0, 1, 2], [0]]
[0,6,2]
>>> foldr (.) id [(+1), (*3), (^3)] 2
25
>>> let (...) = (.).(.) in ((*2)...(+)) 5 10
30

id :: a -> a Source #

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

Expand
>>> 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:

Identity
fmap id == id
Composition
fmap (f . g) == fmap f . fmap g

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

fmap

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 Bifunctor instance that allows both the last and the penultimate parameters to be mapped over.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> fmap show Nothing
Nothing
>>> fmap show (Just 3)
Just "3"

Convert from an Either Int Int to an Either 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)

(<$) :: a -> f b -> f a infixl 4 Source #

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

Examples

Expand

Perform a computation with Maybe and replace the result with a constant value if it is Just:

>>> 'a' <$ Just 2
Just 'a'
>>> 'a' <$ Nothing
Nothing

Instances

Instances details
Functor NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b Source #

(<$) :: a -> NonEmpty b -> NonEmpty a Source #

Functor STM Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

fmap :: (a -> b) -> STM a -> STM b Source #

(<$) :: a -> STM b -> STM a Source #

Functor Handler Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Control.Exception

Methods

fmap :: (a -> b) -> Handler a -> Handler b Source #

(<$) :: a -> Handler b -> Handler a Source #

Functor Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

fmap :: (a -> b) -> Identity a -> Identity b Source #

(<$) :: a -> Identity b -> Identity a Source #

Functor First Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fmap :: (a -> b) -> First a -> First b Source #

(<$) :: a -> First b -> First a Source #

Functor Last Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fmap :: (a -> b) -> Last a -> Last b Source #

(<$) :: a -> Last b -> Last a Source #

Functor Down Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

fmap :: (a -> b) -> Down a -> Down b Source #

(<$) :: a -> Down b -> Down a Source #

Functor Dual Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Dual a -> Dual b Source #

(<$) :: a -> Dual b -> Dual a Source #

Functor Product Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b Source #

(<$) :: a -> Product b -> Product a Source #

Functor Sum Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source #

(<$) :: a -> Sum b -> Sum a Source #

Functor ZipList Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Functor.ZipList

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b Source #

(<$) :: a -> ZipList b -> ZipList a Source #

Functor NoIO Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.GHCi

Methods

fmap :: (a -> b) -> NoIO a -> NoIO b Source #

(<$) :: a -> NoIO b -> NoIO a Source #

Functor Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b Source #

(<$) :: a -> Par1 b -> Par1 a Source #

Functor ReadP Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

fmap :: (a -> b) -> ReadP a -> ReadP b Source #

(<$) :: a -> ReadP b -> ReadP a Source #

Functor ReadPrec Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

Methods

fmap :: (a -> b) -> ReadPrec a -> ReadPrec b Source #

(<$) :: a -> ReadPrec b -> ReadPrec a Source #

Functor IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> IO a -> IO b Source #

(<$) :: a -> IO b -> IO a Source #

Functor Maybe Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b Source #

(<$) :: a -> Maybe b -> Maybe a Source #

Functor Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> Solo a -> Solo b Source #

(<$) :: a -> Solo b -> Solo a Source #

Functor [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> [a] -> [b] Source #

(<$) :: a -> [b] -> [a] Source #

Functor (Array i) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Arr

Methods

fmap :: (a -> b) -> Array i a -> Array i b Source #

(<$) :: a -> Array i b -> Array i a Source #

Arrow a => Functor (ArrowMonad a) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Control.Monad.ST.Lazy.Imp

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source #

(<$) :: a -> ST s b -> ST s a Source #

Functor (Either a) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

Functor (StateL s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateL s a -> StateL s b Source #

(<$) :: a -> StateL s b -> StateL s a Source #

Functor (StateR s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateR s a -> StateR s b Source #

(<$) :: a -> StateR s b -> StateR s a Source #

Functor (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b Source #

(<$) :: a -> Proxy b -> Proxy a Source #

Functor (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b Source #

(<$) :: a -> U1 b -> U1 a Source #

Functor (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> V1 a -> V1 b Source #

(<$) :: a -> V1 b -> V1 a Source #

Functor (ST s) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ST

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source #

(<$) :: a -> ST s b -> ST s a Source #

Functor ((,) a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b) -> (a, a0) -> (a, b) Source #

(<$) :: a0 -> (a, b) -> (a, a0) Source #

Functor m => Functor (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

fmap :: (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b Source #

(<$) :: a0 -> Kleisli m a b -> Kleisli m a a0 Source #

Functor (Const m :: Type -> Type) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source #

(<$) :: a -> Const m b -> Const m a Source #

Monad m => Functor (StateT s m) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b Source #

(<$) :: a -> StateT s m b -> StateT s m a Source #

Functor f => Functor (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b Source #

(<$) :: a -> Ap f b -> Ap f a Source #

Functor f => Functor (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source #

(<$) :: a -> Alt f b -> Alt f a Source #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> Rec1 f a -> Rec1 f b Source #

(<$) :: a -> Rec1 f b -> Rec1 f a Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Functor (URec Char :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Functor (URec Int :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Functor (URec Word :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Functor ((,,) a b) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

(<$) :: a0 -> (a, b, b0) -> (a, b, a0) Source #

(Functor f, Functor g) => Functor (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(<$) :: a -> (f :*: g) b -> (f :*: g) a Source #

(Functor f, Functor g) => Functor (f :+: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(<$) :: a -> (f :+: g) b -> (f :+: g) a Source #

Functor (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b Source #

(<$) :: a -> K1 i c b -> K1 i c a Source #

Functor ((,,,) a b c) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source #

(<$) :: a0 -> (a, b, c, b0) -> (a, b, c, a0) Source #

Functor ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> (r -> a) -> r -> b Source #

(<$) :: a -> (r -> b) -> r -> a Source #

(Functor f, Functor g) => Functor (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

Functor f => Functor (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b Source #

(<$) :: a -> M1 i c f b -> M1 i c f a Source #

Functor ((,,,,) a b c d) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, a0) -> (a, b, c, d, b0) Source #

(<$) :: a0 -> (a, b, c, d, b0) -> (a, b, c, d, a0) Source #

Functor ((,,,,,) a b c d e) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, a0) -> (a, b, c, d, e, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, b0) -> (a, b, c, d, e, a0) Source #

Functor ((,,,,,,) a b c d e f) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, f, a0) -> (a, b, c, d, e, f, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, f, b0) -> (a, b, c, d, e, f, a0) Source #

class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where Source #

Monads that also support choice and failure.

Minimal complete definition

Nothing

Methods

mzero :: m a Source #

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

Instances details
MonadPlus STM Source #

Takes the first non-retrying STM action.

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

mzero :: STM a Source #

mplus :: STM a -> STM a -> STM a Source #

MonadPlus ReadP Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

mzero :: ReadP a Source #

mplus :: ReadP a -> ReadP a -> ReadP a Source #

MonadPlus ReadPrec Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

MonadPlus IO Source #

Takes the first non-throwing IO action's result. mzero throws an exception.

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: IO a Source #

mplus :: IO a -> IO a -> IO a Source #

MonadPlus Maybe Source #

Picks the leftmost Just value, or, alternatively, Nothing.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: Maybe a Source #

mplus :: Maybe a -> Maybe a -> Maybe a Source #

MonadPlus [] Source #

Combines lists by concatenation, starting from the empty list.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: [a] Source #

mplus :: [a] -> [a] -> [a] Source #

(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a Source #

mplus :: Proxy a -> Proxy a -> Proxy a Source #

MonadPlus (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: U1 a Source #

mplus :: U1 a -> U1 a -> U1 a Source #

MonadPlus m => MonadPlus (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

mzero :: Kleisli m a a0 Source #

mplus :: Kleisli m a a0 -> Kleisli m a a0 -> Kleisli m a a0 Source #

MonadPlus f => MonadPlus (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mzero :: Ap f a Source #

mplus :: Ap f a -> Ap f a -> Ap f a Source #

MonadPlus f => MonadPlus (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mzero :: Alt f a Source #

mplus :: Alt f a -> Alt f a -> Alt f a Source #

MonadPlus f => MonadPlus (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: Rec1 f a Source #

mplus :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: (f :*: g) a Source #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

MonadPlus f => MonadPlus (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: M1 i c f a Source #

mplus :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

mapM :: Monad m => (a -> m b) -> [a] -> m [b] Source #

mapM f is equivalent to sequence . map f.

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.

'join bss' can be understood as the do expression

do bs <- bss
   bs

Examples

Expand
>>> 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

to run an STM transaction and the IO action it returns.

when :: Applicative f => Bool -> f () -> f () Source #

Conditional execution of Applicative expressions. For example,

Examples

Expand
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

Expand
>>> 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).

ap :: Monad m => m (a -> b) -> m a -> m b Source #

In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.

return f `ap` x1 `ap` ... `ap` xn

is equivalent to

liftM<n> f x1 x2 ... xn

Examples

Expand
>>> pure (\x y z -> x + y * z) `ap` Just 1 `ap` Just 5 `ap` Just 10
Just 51

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) <> z (Semigroup 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 newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty | mconcat

Methods

mempty :: a Source #

Identity of mappend

Examples

Expand
>>> "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 mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since 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.

mconcat :: [a] -> a Source #

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

Instances details
Monoid All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Monoid Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Monoid Event Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Monoid Lifetime Source #

mappend takes the longer of two lifetimes.

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Monoid ExceptionContext Source # 
Instance details

Defined in GHC.Internal.Exception.Context

Monoid Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Monoid () Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: () Source #

mappend :: () -> () -> () Source #

mconcat :: [()] -> () Source #

Monoid a => Monoid (STM a) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

mempty :: STM a Source #

mappend :: STM a -> STM a -> STM a Source #

mconcat :: [STM a] -> STM a Source #

FiniteBits a => Monoid (And a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

mempty :: And a Source #

mappend :: And a -> And a -> And a Source #

mconcat :: [And a] -> And a Source #

FiniteBits a => Monoid (Iff a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

mempty :: Iff a Source #

mappend :: Iff a -> Iff a -> Iff a Source #

mconcat :: [Iff a] -> Iff a Source #

Bits a => Monoid (Ior a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

mempty :: Ior a Source #

mappend :: Ior a -> Ior a -> Ior a Source #

mconcat :: [Ior a] -> Ior a Source #

Bits a => Monoid (Xor a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

mempty :: Xor a Source #

mappend :: Xor a -> Xor a -> Xor a Source #

mconcat :: [Xor a] -> Xor a Source #

Monoid a => Monoid (Identity a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Ord a => Monoid (Max a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

mempty :: Max a Source #

mappend :: Max a -> Max a -> Max a Source #

mconcat :: [Max a] -> Max a Source #

Ord a => Monoid (Min a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

mempty :: Min a Source #

mappend :: Min a -> Min a -> Min a Source #

mconcat :: [Min a] -> Min a Source #

Monoid (First a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mempty :: First a Source #

mappend :: First a -> First a -> First a Source #

mconcat :: [First a] -> First a Source #

Monoid (Last a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mempty :: Last a Source #

mappend :: Last a -> Last a -> Last a Source #

mconcat :: [Last a] -> Last a Source #

Monoid a => Monoid (Down a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

mempty :: Down a Source #

mappend :: Down a -> Down a -> Down a Source #

mconcat :: [Down a] -> Down a Source #

Monoid a => Monoid (Dual a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Dual a Source #

mappend :: Dual a -> Dual a -> Dual a Source #

mconcat :: [Dual a] -> Dual a Source #

Monoid (Endo a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Endo a Source #

mappend :: Endo a -> Endo a -> Endo a Source #

mconcat :: [Endo a] -> Endo a Source #

Num a => Monoid (Product a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Monoid (Sum a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Sum a Source #

mappend :: Sum a -> Sum a -> Sum a Source #

mconcat :: [Sum a] -> Sum a Source #

(Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Monoid p => Monoid (Par1 p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: Par1 p Source #

mappend :: Par1 p -> Par1 p -> Par1 p Source #

mconcat :: [Par1 p] -> Par1 p Source #

Monoid a => Monoid (IO a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: IO a Source #

mappend :: IO a -> IO a -> IO a Source #

mconcat :: [IO a] -> IO a Source #

Semigroup a => Monoid (Maybe a) Source #

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: Maybe a Source #

mappend :: Maybe a -> Maybe a -> Maybe a Source #

mconcat :: [Maybe a] -> Maybe a Source #

Monoid a => Monoid (Solo a) Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: Solo a Source #

mappend :: Solo a -> Solo a -> Solo a Source #

mconcat :: [Solo a] -> Solo a Source #

Monoid [a] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: [a] Source #

mappend :: [a] -> [a] -> [a] Source #

mconcat :: [[a]] -> [a] Source #

Monoid (Proxy s) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mempty :: Proxy s Source #

mappend :: Proxy s -> Proxy s -> Proxy s Source #

mconcat :: [Proxy s] -> Proxy s Source #

Monoid (U1 p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: U1 p Source #

mappend :: U1 p -> U1 p -> U1 p Source #

mconcat :: [U1 p] -> U1 p Source #

Monoid a => Monoid (ST s a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ST

Methods

mempty :: ST s a Source #

mappend :: ST s a -> ST s a -> ST s a Source #

mconcat :: [ST s a] -> ST s a Source #

(Monoid a, Monoid b) => Monoid (a, b) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b) Source #

mappend :: (a, b) -> (a, b) -> (a, b) Source #

mconcat :: [(a, b)] -> (a, b) Source #

Monoid b => Monoid (a -> b) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: a -> b Source #

mappend :: (a -> b) -> (a -> b) -> a -> b Source #

mconcat :: [a -> b] -> a -> b Source #

Monoid a => Monoid (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

mempty :: Const a b Source #

mappend :: Const a b -> Const a b -> Const a b Source #

mconcat :: [Const a b] -> Const a b Source #

(Applicative f, Monoid a) => Monoid (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mempty :: Ap f a Source #

mappend :: Ap f a -> Ap f a -> Ap f a Source #

mconcat :: [Ap f a] -> Ap f a Source #

Alternative f => Monoid (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Alt f a Source #

mappend :: Alt f a -> Alt f a -> Alt f a Source #

mconcat :: [Alt f a] -> Alt f a Source #

Monoid (f p) => Monoid (Rec1 f p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: Rec1 f p Source #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

mconcat :: [Rec1 f p] -> Rec1 f p Source #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c) Source #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

mconcat :: [(a, b, c)] -> (a, b, c) Source #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: (f :*: g) p Source #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

mconcat :: [(f :*: g) p] -> (f :*: g) p Source #

Monoid c => Monoid (K1 i c p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: K1 i c p Source #

mappend :: K1 i c p -> K1 i c p -> K1 i c p Source #

mconcat :: [K1 i c p] -> K1 i c p Source #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c, d) Source #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) Source #

Monoid (f (g p)) => Monoid ((f :.: g) p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: (f :.: g) p Source #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

mconcat :: [(f :.: g) p] -> (f :.: g) p Source #

Monoid (f p) => Monoid (M1 i c f p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mempty :: M1 i c f p Source #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

mconcat :: [M1 i c f p] -> M1 i c f p Source #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c, d, e) Source #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) Source #

data NonEmpty a Source #

Non-empty (and non-strict) list type.

@since base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
Applicative NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> NonEmpty a Source #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b Source #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b Source #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a Source #

Functor NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b Source #

(<$) :: a -> NonEmpty b -> NonEmpty a Source #

Monad NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b Source #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b Source #

return :: a -> NonEmpty a Source #

MonadFix NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a Source #

Foldable NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m Source #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m Source #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m Source #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b Source #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b Source #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b Source #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b Source #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a Source #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a Source #

toList :: NonEmpty a -> [a] Source #

null :: NonEmpty a -> Bool Source #

length :: NonEmpty a -> Int Source #

elem :: Eq a => a -> NonEmpty a -> Bool Source #

maximum :: Ord a => NonEmpty a -> a Source #

minimum :: Ord a => NonEmpty a -> a Source #

sum :: Num a => NonEmpty a -> a Source #

product :: Num a => NonEmpty a -> a Source #

Traversable NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) Source #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) Source #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) Source #

Generic1 NonEmpty Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 NonEmpty

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Semigroup (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Data a => Data (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) Source #

toConstr :: NonEmpty a -> Constr Source #

dataTypeOf :: NonEmpty a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) Source #

gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) Source #

Generic (NonEmpty a) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (NonEmpty a)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x Source #

to :: Rep (NonEmpty a) x -> NonEmpty a Source #

IsList (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.IsList

Associated Types

type Item (NonEmpty a) 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a
Read a => Read (NonEmpty a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Read

Show a => Show (NonEmpty a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

Eq a => Eq (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool Source #

(/=) :: NonEmpty a -> NonEmpty a -> Bool Source #

Ord a => Ord (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

type Rep1 NonEmpty Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (NonEmpty a) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Item (NonEmpty a) Source # 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a

($) :: (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 id specialized from 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

Expand

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)

Expand

($) 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

otherwise :: Bool Source #

otherwise is defined as the value True. It helps to make guards more readable. eg.

 f x | x < 0     = ...
     | otherwise = ...

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 :: a -> b -> a Source #

const x y always evaluates to x, ignoring its second argument.

const x = \_ -> x

This function might seem useless at first glance, but it can be very useful in a higher order context.

Examples

Expand
>>> const 42 "hello"
42
>>> map (const 42) [0..3]
[42,42,42,42]

flip :: (a -> b -> c) -> b -> a -> c Source #

flip f takes its (first) two arguments in the reverse order of f.

flip f x y = f y x
flip . flip = id

Examples

Expand
>>> 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

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*> and liftA2).

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).

Minimal complete definition

pure, ((<*>) | liftA2)

Methods

pure :: a -> f a Source #

Lift a value into the Structure.

Examples

Expand
>>> 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

Expand

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

Expand
>>> 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

Expand

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

Instances details
Applicative NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> NonEmpty a Source #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b Source #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b Source #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a Source #

Applicative STM Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

pure :: a -> STM a Source #

(<*>) :: STM (a -> b) -> STM a -> STM b Source #

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c Source #

(*>) :: STM a -> STM b -> STM b Source #

(<*) :: STM a -> STM b -> STM a Source #

Applicative Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

pure :: a -> Identity a Source #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b Source #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

(*>) :: Identity a -> Identity b -> Identity b Source #

(<*) :: Identity a -> Identity b -> Identity a Source #

Applicative First Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

pure :: a -> First a Source #

(<*>) :: First (a -> b) -> First a -> First b Source #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c Source #

(*>) :: First a -> First b -> First b Source #

(<*) :: First a -> First b -> First a Source #

Applicative Last Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

pure :: a -> Last a Source #

(<*>) :: Last (a -> b) -> Last a -> Last b Source #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c Source #

(*>) :: Last a -> Last b -> Last b Source #

(<*) :: Last a -> Last b -> Last a Source #

Applicative Down Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

pure :: a -> Down a Source #

(<*>) :: Down (a -> b) -> Down a -> Down b Source #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c Source #

(*>) :: Down a -> Down b -> Down b Source #

(<*) :: Down a -> Down b -> Down a Source #

Applicative Dual Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Dual a Source #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b Source #

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source #

(*>) :: Dual a -> Dual b -> Dual b Source #

(<*) :: Dual a -> Dual b -> Dual a Source #

Applicative Product Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Product a Source #

(<*>) :: Product (a -> b) -> Product a -> Product b Source #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c Source #

(*>) :: Product a -> Product b -> Product b Source #

(<*) :: Product a -> Product b -> Product a Source #

Applicative Sum Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Sum a Source #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b Source #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source #

(*>) :: Sum a -> Sum b -> Sum b Source #

(<*) :: Sum a -> Sum b -> Sum a Source #

Applicative ZipList Source #
f <$> ZipList xs1 <*> ... <*> ZipList xsN
    = ZipList (zipWithN f xs1 ... xsN)

where zipWithN refers to the zipWith function of the appropriate arity (zipWith, zipWith3, zipWith4, ...). For example:

(\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

Instance details

Defined in GHC.Internal.Functor.ZipList

Methods

pure :: a -> ZipList a Source #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b Source #

liftA2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

(*>) :: ZipList a -> ZipList b -> ZipList b Source #

(<*) :: ZipList a -> ZipList b -> ZipList a Source #

Applicative NoIO Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.GHCi

Methods

pure :: a -> NoIO a Source #

(<*>) :: NoIO (a -> b) -> NoIO a -> NoIO b Source #

liftA2 :: (a -> b -> c) -> NoIO a -> NoIO b -> NoIO c Source #

(*>) :: NoIO a -> NoIO b -> NoIO b Source #

(<*) :: NoIO a -> NoIO b -> NoIO a Source #

Applicative Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> Par1 a Source #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b Source #

liftA2 :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c Source #

(*>) :: Par1 a -> Par1 b -> Par1 b Source #

(<*) :: Par1 a -> Par1 b -> Par1 a Source #

Applicative ReadP Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

pure :: a -> ReadP a Source #

(<*>) :: ReadP (a -> b) -> ReadP a -> ReadP b Source #

liftA2 :: (a -> b -> c) -> ReadP a -> ReadP b -> ReadP c Source #

(*>) :: ReadP a -> ReadP b -> ReadP b Source #

(<*) :: ReadP a -> ReadP b -> ReadP a Source #

Applicative ReadPrec Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

Methods

pure :: a -> ReadPrec a Source #

(<*>) :: ReadPrec (a -> b) -> ReadPrec a -> ReadPrec b Source #

liftA2 :: (a -> b -> c) -> ReadPrec a -> ReadPrec b -> ReadPrec c Source #

(*>) :: ReadPrec a -> ReadPrec b -> ReadPrec b Source #

(<*) :: ReadPrec a -> ReadPrec b -> ReadPrec a Source #

Applicative IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> IO a Source #

(<*>) :: IO (a -> b) -> IO a -> IO b Source #

liftA2 :: (a -> b -> c) -> IO a -> IO b -> IO c Source #

(*>) :: IO a -> IO b -> IO b Source #

(<*) :: IO a -> IO b -> IO a Source #

Applicative Maybe Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> Maybe a Source #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b Source #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

(*>) :: Maybe a -> Maybe b -> Maybe b Source #

(<*) :: Maybe a -> Maybe b -> Maybe a Source #

Applicative Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> Solo a Source #

(<*>) :: Solo (a -> b) -> Solo a -> Solo b Source #

liftA2 :: (a -> b -> c) -> Solo a -> Solo b -> Solo c Source #

(*>) :: Solo a -> Solo b -> Solo b Source #

(<*) :: Solo a -> Solo b -> Solo a Source #

Applicative [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> [a] Source #

(<*>) :: [a -> b] -> [a] -> [b] Source #

liftA2 :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

(*>) :: [a] -> [b] -> [b] Source #

(<*) :: [a] -> [b] -> [a] Source #

Arrow a => Applicative (ArrowMonad a) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Control.Monad.ST.Lazy.Imp

Methods

pure :: a -> ST s a Source #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b Source #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

(*>) :: ST s a -> ST s b -> ST s b Source #

(<*) :: ST s a -> ST s b -> ST s a Source #

Applicative (Either e) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

pure :: a -> Either e a Source #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b Source #

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c Source #

(*>) :: Either e a -> Either e b -> Either e b Source #

(<*) :: Either e a -> Either e b -> Either e a Source #

Applicative (StateL s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

pure :: a -> StateL s a Source #

(<*>) :: StateL s (a -> b) -> StateL s a -> StateL s b Source #

liftA2 :: (a -> b -> c) -> StateL s a -> StateL s b -> StateL s c Source #

(*>) :: StateL s a -> StateL s b -> StateL s b Source #

(<*) :: StateL s a -> StateL s b -> StateL s a Source #

Applicative (StateR s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

pure :: a -> StateR s a Source #

(<*>) :: StateR s (a -> b) -> StateR s a -> StateR s b Source #

liftA2 :: (a -> b -> c) -> StateR s a -> StateR s b -> StateR s c Source #

(*>) :: StateR s a -> StateR s b -> StateR s b Source #

(<*) :: StateR s a -> StateR s b -> StateR s a Source #

Applicative (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a Source #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b Source #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

(*>) :: Proxy a -> Proxy b -> Proxy b Source #

(<*) :: Proxy a -> Proxy b -> Proxy a Source #

Applicative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> U1 a Source #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b Source #

liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c Source #

(*>) :: U1 a -> U1 b -> U1 b Source #

(<*) :: U1 a -> U1 b -> U1 a Source #

Applicative (ST s) Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.ST

Methods

pure :: a -> ST s a Source #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b Source #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

(*>) :: ST s a -> ST s b -> ST s b Source #

(<*) :: ST s a -> ST s b -> ST s a Source #

Monoid a => Applicative ((,) a) Source #

For tuples, the Monoid constraint on a determines how the first values merge. For example, Strings concatenate:

("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a0 -> (a, a0) Source #

(<*>) :: (a, a0 -> b) -> (a, a0) -> (a, b) Source #

liftA2 :: (a0 -> b -> c) -> (a, a0) -> (a, b) -> (a, c) Source #

(*>) :: (a, a0) -> (a, b) -> (a, b) Source #

(<*) :: (a, a0) -> (a, b) -> (a, a0) Source #

Applicative m => Applicative (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

pure :: a -> Const m a Source #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b Source #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c Source #

(*>) :: Const m a -> Const m b -> Const m b Source #

(<*) :: Const m a -> Const m b -> Const m a Source #

Monad m => Applicative (StateT s m) Source #

@since base-4.18.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

pure :: a -> Ap f a Source #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b Source #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c Source #

(*>) :: Ap f a -> Ap f b -> Ap f b Source #

(<*) :: Ap f a -> Ap f b -> Ap f a Source #

Applicative f => Applicative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Alt f a Source #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b Source #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source #

(*>) :: Alt f a -> Alt f b -> Alt f b Source #

(<*) :: Alt f a -> Alt f b -> Alt f a Source #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> Rec1 f a Source #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b Source #

liftA2 :: (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c Source #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a Source #

(Monoid a, Monoid b) => Applicative ((,,) a b) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a0 -> (a, b, a0) Source #

(<*>) :: (a, b, a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

liftA2 :: (a0 -> b0 -> c) -> (a, b, a0) -> (a, b, b0) -> (a, b, c) Source #

(*>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

(<*) :: (a, b, a0) -> (a, b, b0) -> (a, b, a0) Source #

(Applicative f, Applicative g) => Applicative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :*: g) a Source #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c Source #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a Source #

Monoid c => Applicative (K1 i c :: Type -> Type) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> K1 i c a Source #

(<*>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b Source #

liftA2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 Source #

(*>) :: K1 i c a -> K1 i c b -> K1 i c b Source #

(<*) :: K1 i c a -> K1 i c b -> K1 i c a Source #

(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) Source #

@since base-4.14.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> r -> a Source #

(<*>) :: (r -> (a -> b)) -> (r -> a) -> r -> b Source #

liftA2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> c Source #

(*>) :: (r -> a) -> (r -> b) -> r -> b Source #

(<*) :: (r -> a) -> (r -> b) -> r -> a Source #

(Applicative f, Applicative g) => Applicative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :.: g) a Source #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source #

Applicative f => Applicative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> M1 i c f a Source #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b Source #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 Source #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a Source #

class Semigroup a where Source #

The class of semigroups (types with an associative binary operation).

Instances should satisfy the following:

Associativity
x <> (y <> z) = (x <> y) <> z

You can alternatively define sconcat instead of (<>), in which case the laws are:

Unit
sconcat (pure x) = x
Multiplication
sconcat (join xss) = sconcat (fmap sconcat xss)

@since base-4.9.0.0

Minimal complete definition

(<>) | sconcat

Methods

(<>) :: a -> a -> a infixr 6 Source #

An associative operation.

Examples

Expand
>>> [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

Expand

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 = stimesIdempotent or stimes = stimesIdempotentMonoid respectively.

Examples

Expand
>>> stimes 4 [1]
[1,1,1,1]
>>> stimes 5 (putStr "hi!")
hi!hi!hi!hi!hi!
>>> stimes 3 (Right ":)")
Right ":)"

Instances

Instances details
Semigroup Void Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup All Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All Source #

sconcat :: NonEmpty All -> All Source #

stimes :: Integral b => b -> All -> All Source #

Semigroup Any Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any Source #

sconcat :: NonEmpty Any -> Any Source #

stimes :: Integral b => b -> Any -> Any Source #

Semigroup Event Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Semigroup Lifetime Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Semigroup ExceptionContext Source # 
Instance details

Defined in GHC.Internal.Exception.Context

Semigroup Ordering Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup () Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: () -> () -> () Source #

sconcat :: NonEmpty () -> () Source #

stimes :: Integral b => b -> () -> () Source #

Semigroup (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Semigroup a => Semigroup (STM a) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(<>) :: STM a -> STM a -> STM a Source #

sconcat :: NonEmpty (STM a) -> STM a Source #

stimes :: Integral b => b -> STM a -> STM a Source #

Bits a => Semigroup (And a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: And a -> And a -> And a Source #

sconcat :: NonEmpty (And a) -> And a Source #

stimes :: Integral b => b -> And a -> And a Source #

FiniteBits a => Semigroup (Iff a) Source #

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Iff a -> Iff a -> Iff a Source #

sconcat :: NonEmpty (Iff a) -> Iff a Source #

stimes :: Integral b => b -> Iff a -> Iff a Source #

Bits a => Semigroup (Ior a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Ior a -> Ior a -> Ior a Source #

sconcat :: NonEmpty (Ior a) -> Ior a Source #

stimes :: Integral b => b -> Ior a -> Ior a Source #

Bits a => Semigroup (Xor a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(<>) :: Xor a -> Xor a -> Xor a Source #

sconcat :: NonEmpty (Xor a) -> Xor a Source #

stimes :: Integral b => b -> Xor a -> Xor a Source #

Semigroup a => Semigroup (Identity a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Ord a => Semigroup (Max a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

(<>) :: Max a -> Max a -> Max a Source #

sconcat :: NonEmpty (Max a) -> Max a Source #

stimes :: Integral b => b -> Max a -> Max a Source #

Ord a => Semigroup (Min a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

(<>) :: Min a -> Min a -> Min a Source #

sconcat :: NonEmpty (Min a) -> Min a Source #

stimes :: Integral b => b -> Min a -> Min a Source #

Semigroup (First a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: First a -> First a -> First a Source #

sconcat :: NonEmpty (First a) -> First a Source #

stimes :: Integral b => b -> First a -> First a Source #

Semigroup (Last a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a Source #

sconcat :: NonEmpty (Last a) -> Last a Source #

stimes :: Integral b => b -> Last a -> Last a Source #

Semigroup a => Semigroup (Down a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(<>) :: Down a -> Down a -> Down a Source #

sconcat :: NonEmpty (Down a) -> Down a Source #

stimes :: Integral b => b -> Down a -> Down a Source #

Semigroup a => Semigroup (Dual a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a Source #

sconcat :: NonEmpty (Dual a) -> Dual a Source #

stimes :: Integral b => b -> Dual a -> Dual a Source #

Semigroup (Endo a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a Source #

sconcat :: NonEmpty (Endo a) -> Endo a Source #

stimes :: Integral b => b -> Endo a -> Endo a Source #

Num a => Semigroup (Product a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a Source #

sconcat :: NonEmpty (Product a) -> Product a Source #

stimes :: Integral b => b -> Product a -> Product a Source #

Num a => Semigroup (Sum a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a Source #

sconcat :: NonEmpty (Sum a) -> Sum a Source #

stimes :: Integral b => b -> Sum a -> Sum a Source #

(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Semigroup p => Semigroup (Par1 p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: Par1 p -> Par1 p -> Par1 p Source #

sconcat :: NonEmpty (Par1 p) -> Par1 p Source #

stimes :: Integral b => b -> Par1 p -> Par1 p Source #

Semigroup a => Semigroup (IO a) Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: IO a -> IO a -> IO a Source #

sconcat :: NonEmpty (IO a) -> IO a Source #

stimes :: Integral b => b -> IO a -> IO a Source #

Semigroup a => Semigroup (Maybe a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a Source #

sconcat :: NonEmpty (Maybe a) -> Maybe a Source #

stimes :: Integral b => b -> Maybe a -> Maybe a Source #

Semigroup a => Semigroup (Solo a) Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: Solo a -> Solo a -> Solo a Source #

sconcat :: NonEmpty (Solo a) -> Solo a Source #

stimes :: Integral b => b -> Solo a -> Solo a Source #

Semigroup [a] Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: [a] -> [a] -> [a] Source #

sconcat :: NonEmpty [a] -> [a] Source #

stimes :: Integral b => b -> [a] -> [a] Source #

Semigroup (Either a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b Source #

sconcat :: NonEmpty (Either a b) -> Either a b Source #

stimes :: Integral b0 => b0 -> Either a b -> Either a b Source #

Semigroup (Proxy s) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s Source #

sconcat :: NonEmpty (Proxy s) -> Proxy s Source #

stimes :: Integral b => b -> Proxy s -> Proxy s Source #

Semigroup (U1 p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: U1 p -> U1 p -> U1 p Source #

sconcat :: NonEmpty (U1 p) -> U1 p Source #

stimes :: Integral b => b -> U1 p -> U1 p Source #

Semigroup (V1 p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: V1 p -> V1 p -> V1 p Source #

sconcat :: NonEmpty (V1 p) -> V1 p Source #

stimes :: Integral b => b -> V1 p -> V1 p Source #

Semigroup a => Semigroup (ST s a) Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ST

Methods

(<>) :: ST s a -> ST s a -> ST s a Source #

sconcat :: NonEmpty (ST s a) -> ST s a Source #

stimes :: Integral b => b -> ST s a -> ST s a Source #

(Semigroup a, Semigroup b) => Semigroup (a, b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) Source #

sconcat :: NonEmpty (a, b) -> (a, b) Source #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) Source #

Semigroup b => Semigroup (a -> b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b Source #

sconcat :: NonEmpty (a -> b) -> a -> b Source #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b Source #

Semigroup a => Semigroup (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b Source #

sconcat :: NonEmpty (Const a b) -> Const a b Source #

stimes :: Integral b0 => b0 -> Const a b -> Const a b Source #

(Applicative f, Semigroup a) => Semigroup (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a Source #

sconcat :: NonEmpty (Ap f a) -> Ap f a Source #

stimes :: Integral b => b -> Ap f a -> Ap f a Source #

Alternative f => Semigroup (Alt f a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a Source #

sconcat :: NonEmpty (Alt f a) -> Alt f a Source #

stimes :: Integral b => b -> Alt f a -> Alt f a Source #

Semigroup (f p) => Semigroup (Rec1 f p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

sconcat :: NonEmpty (Rec1 f p) -> Rec1 f p Source #

stimes :: Integral b => b -> Rec1 f p -> Rec1 f p Source #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) Source #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) Source #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p Source #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p Source #

Semigroup c => Semigroup (K1 i c p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: K1 i c p -> K1 i c p -> K1 i c p Source #

sconcat :: NonEmpty (K1 i c p) -> K1 i c p Source #

stimes :: Integral b => b -> K1 i c p -> K1 i c p Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) Source #

Semigroup (f (g p)) => Semigroup ((f :.: g) p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

sconcat :: NonEmpty ((f :.: g) p) -> (f :.: g) p Source #

stimes :: Integral b => b -> (f :.: g) p -> (f :.: g) p Source #

Semigroup (f p) => Semigroup (M1 i c f p) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

sconcat :: NonEmpty (M1 i c f p) -> M1 i c f p Source #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

(++) :: [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

Expand

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

Expand
>>> [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

Expand
>>> 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]

data Void Source #

Uninhabited data type

@since base-4.8.0.0

Instances

Instances details
Semigroup Void Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Data Void Source #

@since base-4.8.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Exception.Type

Generic Void Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep Void

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Void = D1 ('MetaData "Void" "GHC.Internal.Base" "ghc-internal" 'False) (V1 :: Type -> Type)

Methods

from :: Void -> Rep Void x Source #

to :: Rep Void x -> Void Source #

Ix Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Ix

Read Void Source #

Reading a Void value is always a parse error, considering Void as a data type with no constructors.

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Read

Show Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

Eq Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(==) :: Void -> Void -> Bool Source #

(/=) :: Void -> Void -> Bool Source #

Ord Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

type Rep Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Void = D1 ('MetaData "Void" "GHC.Internal.Base" "ghc-internal" 'False) (V1 :: Type -> Type)

absurd :: Void -> a Source #

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

vacuous :: Functor f => f Void -> f a Source #

If Void is uninhabited then any Functor that holds only values of type Void is holding no values. It is implemented in terms of fmap absurd.

@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

Expand
>>> Nothing <|> Just 42
Just 42
>>> [1, 2] <|> [3, 4]
[1,2,3,4]
>>> empty <|> print (2^15)
32768

Minimal complete definition

empty, (<|>)

Methods

empty :: f a Source #

The identity of <|>

empty <|> a     == a
a     <|> empty == a

(<|>) :: f a -> f a -> f a infixl 3 Source #

An associative binary operation

some :: f a -> f [a] Source #

One or more.

Examples

Expand
>>> 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.

many :: f a -> f [a] Source #

Zero or more.

Examples

Expand
>>> 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

Instances details
Alternative STM Source #

Takes the first non-retrying STM action.

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

empty :: STM a Source #

(<|>) :: STM a -> STM a -> STM a Source #

some :: STM a -> STM [a] Source #

many :: STM a -> STM [a] Source #

Alternative ZipList Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Alternative ReadP Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

empty :: ReadP a Source #

(<|>) :: ReadP a -> ReadP a -> ReadP a Source #

some :: ReadP a -> ReadP [a] Source #

many :: ReadP a -> ReadP [a] Source #

Alternative ReadPrec Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

Alternative IO Source #

Takes the first non-throwing IO action's result. empty throws an exception.

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

empty :: IO a Source #

(<|>) :: IO a -> IO a -> IO a Source #

some :: IO a -> IO [a] Source #

many :: IO a -> IO [a] Source #

Alternative Maybe Source #

Picks the leftmost Just value, or, alternatively, Nothing.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

empty :: Maybe a Source #

(<|>) :: Maybe a -> Maybe a -> Maybe a Source #

some :: Maybe a -> Maybe [a] Source #

many :: Maybe a -> Maybe [a] Source #

Alternative [] Source #

Combines lists by concatenation, starting from the empty list.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

empty :: [a] Source #

(<|>) :: [a] -> [a] -> [a] Source #

some :: [a] -> [[a]] Source #

many :: [a] -> [[a]] Source #

ArrowPlus a => Alternative (ArrowMonad a) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

empty :: Proxy a Source #

(<|>) :: Proxy a -> Proxy a -> Proxy a Source #

some :: Proxy a -> Proxy [a] Source #

many :: Proxy a -> Proxy [a] Source #

Alternative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: U1 a Source #

(<|>) :: U1 a -> U1 a -> U1 a Source #

some :: U1 a -> U1 [a] Source #

many :: U1 a -> U1 [a] Source #

Alternative m => Alternative (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

empty :: Kleisli m a a0 Source #

(<|>) :: Kleisli m a a0 -> Kleisli m a a0 -> Kleisli m a a0 Source #

some :: Kleisli m a a0 -> Kleisli m a [a0] Source #

many :: Kleisli m a a0 -> Kleisli m a [a0] Source #

Alternative f => Alternative (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

empty :: Ap f a Source #

(<|>) :: Ap f a -> Ap f a -> Ap f a Source #

some :: Ap f a -> Ap f [a] Source #

many :: Ap f a -> Ap f [a] Source #

Alternative f => Alternative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

empty :: Alt f a Source #

(<|>) :: Alt f a -> Alt f a -> Alt f a Source #

some :: Alt f a -> Alt f [a] Source #

many :: Alt f a -> Alt f [a] Source #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Alternative f => Alternative (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: Rec1 f a Source #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

some :: Rec1 f a -> Rec1 f [a] Source #

many :: Rec1 f a -> Rec1 f [a] Source #

(Alternative f, Alternative g) => Alternative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :*: g) a Source #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

some :: (f :*: g) a -> (f :*: g) [a] Source #

many :: (f :*: g) a -> (f :*: g) [a] Source #

(Alternative f, Applicative g) => Alternative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :.: g) a Source #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

some :: (f :.: g) a -> (f :.: g) [a] Source #

many :: (f :.: g) a -> (f :.: g) [a] Source #

Alternative f => Alternative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: M1 i c f a Source #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

some :: M1 i c f a -> M1 i c f [a] Source #

many :: M1 i c f a -> M1 i c f [a] Source #

($!) :: (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)

build :: (forall b. (a -> b -> b) -> b -> b) -> [a] Source #

A list producer that can be fused with foldr. This function is merely

   build g = g (:) []

but GHC's simplifier will transform an expression of the form foldr k z (build g), which may arise after inlining, to g k z, which avoids producing an intermediate list.

augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] Source #

A list producer that can be fused with foldr. This function is merely

   augment g xs = g (:) xs

but GHC's simplifier will transform an expression of the form foldr k z (augment g xs), which may arise after inlining, to g k (foldr k z xs), which avoids producing an intermediate list.

breakpoint :: a -> a Source #

ord :: Char -> Int Source #

The fromEnum method restricted to the type Char.

(<**>) :: 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 flip (<*>) in that the effects are resolved in the order the arguments are presented.

Examples

Expand
>>> (<**>) (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

Expand

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.

mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst Source #

eqString :: String -> String -> Bool Source #

This String equality predicate is used when desugaring pattern-matches against strings.

data Opaque Source #

Constructors

O a 

until :: (a -> Bool) -> (a -> a) -> a -> a Source #

until p f yields the result of applying f until p holds.

asTypeOf :: a -> a -> a Source #

asTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the second.

returnIO :: a -> IO a Source #

thenIO :: IO a -> IO b -> IO b Source #

bindIO :: IO a -> (a -> IO b) -> IO b Source #

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.

quotInt :: Int -> Int -> Int Source #

Used to implement quot for the Integral typeclass. This performs integer division on its two parameters, truncated towards zero.

Example

Expand
>>> quotInt 10 2
5
>>> quot 10 2
5

remInt :: Int -> Int -> Int Source #

Used to implement rem for the Integral typeclass. This gives the remainder after integer division of its two parameters, satisfying

((x `quot` y) * y) + (x `rem` y) == x

Example

Expand
>>> remInt 3 2
1
>>> rem 3 2
1

divInt :: Int -> Int -> Int Source #

Used to implement div for the Integral typeclass. This performs integer division on its two parameters, truncated towards negative infinity.

Example

Expand
>>> 10 `divInt` 2
5
>>> 10 `div` 2
5

modInt :: Int -> Int -> Int Source #

Used to implement mod for the Integral typeclass. This performs the modulo operation, satisfying

((x `div` y) * y) + (x `mod` y) == x

Example

Expand
>>> 7 `modInt` 3
1
>>> 7 `mod` 3
1

quotRemInt :: Int -> Int -> (Int, Int) Source #

Used to implement quotRem for the Integral typeclass. This gives a tuple equivalent to

(quot x y, mod x y)

Example

Expand
>>> quotRemInt 10 2
(5,0)
>>> quotRem 10 2
(5,0)

divModInt :: Int -> Int -> (Int, Int) Source #

Used to implement divMod for the Integral typeclass. This gives a tuple equivalent to

(div x y, mod x y)

Example

Expand
>>> divModInt 10 2
(5,0)
>>> divMod 10 2
(5,0)

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

Methods

ip :: a Source #

class Eq a where Source #

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:

Reflexivity
x == x = True
Symmetry
x == y = y == x
Transitivity
if x == y && y == z = True, then x == z = True
Extensionality
if x == y = True and f is a function whose return type is an instance of Eq, then f x == f y = True
Negation
x /= y = not (x == y)

Minimal complete definition

(==) | (/=)

Methods

(==) :: a -> a -> Bool infix 4 Source #

(/=) :: a -> a -> Bool infix 4 Source #

Instances

Instances details
Eq BigNat 
Instance details

Defined in GHC.Num.BigNat

Eq Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(==) :: Void -> Void -> Bool Source #

(/=) :: Void -> Void -> Bool Source #

Eq ByteOrder Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Eq ClosureType Source # 
Instance details

Defined in GHC.Internal.ClosureTypes

Eq BlockReason Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq ThreadId Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq ThreadStatus Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq Constr Source #

Equality of constructors

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq ConstrRep Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq DataRep Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq Fixity Source #

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: All -> All -> Bool Source #

(/=) :: All -> All -> Bool Source #

Eq Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Any -> Any -> Bool Source #

(/=) :: Any -> Any -> Bool Source #

Eq SomeTypeRep Source # 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Eq Unique Source # 
Instance details

Defined in GHC.Internal.Data.Unique

Eq Version Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Version

Eq Event Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

(==) :: Event -> Event -> Bool Source #

(/=) :: Event -> Event -> Bool Source #

Eq Lifetime Source #

@since base-4.8.1.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Eq FdKey Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Methods

(==) :: FdKey -> FdKey -> Bool Source #

(/=) :: FdKey -> FdKey -> Bool Source #

Eq TimeoutKey Source # 
Instance details

Defined in GHC.Internal.Event.TimeOut

Eq ErrorCall Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Exception

Eq ArithException Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Eq SpecConstrAnnotation Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Exts

Eq Fingerprint Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Eq Errno Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.C.Error

Methods

(==) :: Errno -> Errno -> Bool Source #

(/=) :: Errno -> Errno -> Bool Source #

Eq CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CBool -> CBool -> Bool Source #

(/=) :: CBool -> CBool -> Bool Source #

Eq CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CChar -> CChar -> Bool Source #

(/=) :: CChar -> CChar -> Bool Source #

Eq CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CInt -> CInt -> Bool Source #

(/=) :: CInt -> CInt -> Bool Source #

Eq CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CLong -> CLong -> Bool Source #

(/=) :: CLong -> CLong -> Bool Source #

Eq CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CSize -> CSize -> Bool Source #

(/=) :: CSize -> CSize -> Bool Source #

Eq CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CTime -> CTime -> Bool Source #

(/=) :: CTime -> CTime -> Bool Source #

Eq CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

(==) :: CUInt -> CUInt -> Bool Source #

(/=) :: CUInt -> CUInt -> Bool Source #

Eq CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq Associativity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Eq DecidedStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq Fixity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Eq SourceStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq SourceUnpackedness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq MaskingState Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO

Eq BufferState Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Buffer

Eq IODeviceType Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Eq SeekMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Eq CodingProgress Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Eq ArrayException Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq AsyncException Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq ExitCode Source # 
Instance details

Defined in GHC.Internal.IO.Exception

Eq IOErrorType Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq IOException Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq HandlePosn Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle

Eq BufferMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq Handle Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq Newline Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq NewlineMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq IOMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Eq IoSubSystem Source # 
Instance details

Defined in GHC.Internal.IO.SubSystem

Eq InfoProv Source # 
Instance details

Defined in GHC.Internal.InfoProv.Types

Eq Int16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Methods

(==) :: Int16 -> Int16 -> Bool Source #

(/=) :: Int16 -> Int16 -> Bool Source #

Eq Int32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Methods

(==) :: Int32 -> Int32 -> Bool Source #

(/=) :: Int32 -> Int32 -> Bool Source #

Eq Int64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Methods

(==) :: Int64 -> Int64 -> Bool Source #

(/=) :: Int64 -> Int64 -> Bool Source #

Eq Int8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Methods

(==) :: Int8 -> Int8 -> Bool Source #

(/=) :: Int8 -> Int8 -> Bool Source #

Eq IoManagerFlag Source # 
Instance details

Defined in GHC.Internal.RTS.Flags

Eq StackEntry Source # 
Instance details

Defined in GHC.Internal.Stack.CloneStack

Eq SrcLoc Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Stack.Types

Eq CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CCc -> CCc -> Bool Source #

(/=) :: CCc -> CCc -> Bool Source #

Eq CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CDev -> CDev -> Bool Source #

(/=) :: CDev -> CDev -> Bool Source #

Eq CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CGid -> CGid -> Bool Source #

(/=) :: CGid -> CGid -> Bool Source #

Eq CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CId -> CId -> Bool Source #

(/=) :: CId -> CId -> Bool Source #

Eq CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CIno -> CIno -> Bool Source #

(/=) :: CIno -> CIno -> Bool Source #

Eq CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CKey -> CKey -> Bool Source #

(/=) :: CKey -> CKey -> Bool Source #

Eq CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CMode -> CMode -> Bool Source #

(/=) :: CMode -> CMode -> Bool Source #

Eq CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CNfds -> CNfds -> Bool Source #

(/=) :: CNfds -> CNfds -> Bool Source #

Eq CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: COff -> COff -> Bool Source #

(/=) :: COff -> COff -> Bool Source #

Eq CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CPid -> CPid -> Bool Source #

(/=) :: CPid -> CPid -> Bool Source #

Eq CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CRLim -> CRLim -> Bool Source #

(/=) :: CRLim -> CRLim -> Bool Source #

Eq CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CTimer Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: CUid -> CUid -> Bool Source #

(/=) :: CUid -> CUid -> Bool Source #

Eq Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(==) :: Fd -> Fd -> Bool Source #

(/=) :: Fd -> Fd -> Bool Source #

Eq Lexeme Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.Read.Lex

Eq Number Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.Read.Lex

Eq SomeChar Source # 
Instance details

Defined in GHC.Internal.TypeLits

Eq SomeSymbol Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeLits

Eq SomeNat Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeNats

Eq GeneralCategory Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Unicode

Eq Word16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Eq Word32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Eq Word64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Eq Word8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Methods

(==) :: Word8 -> Word8 -> Bool Source #

(/=) :: Word8 -> Word8 -> Bool Source #

Eq Module 
Instance details

Defined in GHC.Classes

Eq Ordering 
Instance details

Defined in GHC.Classes

Eq TrName 
Instance details

Defined in GHC.Classes

Eq TyCon 
Instance details

Defined in GHC.Classes

Methods

(==) :: TyCon -> TyCon -> Bool Source #

(/=) :: TyCon -> TyCon -> Bool Source #

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Eq () 
Instance details

Defined in GHC.Classes

Methods

(==) :: () -> () -> Bool Source #

(/=) :: () -> () -> Bool Source #

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

(==) :: Bool -> Bool -> Bool Source #

(/=) :: Bool -> Bool -> Bool Source #

Eq Char 
Instance details

Defined in GHC.Classes

Methods

(==) :: Char -> Char -> Bool Source #

(/=) :: Char -> Char -> Bool Source #

Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy extensionality:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

(==) :: Float -> Float -> Bool Source #

(/=) :: Float -> Float -> Bool Source #

Eq Int 
Instance details

Defined in GHC.Classes

Methods

(==) :: Int -> Int -> Bool Source #

(/=) :: Int -> Int -> Bool Source #

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool Source #

(/=) :: Word -> Word -> Bool Source #

Eq a => Eq (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool Source #

(/=) :: NonEmpty a -> NonEmpty a -> Bool Source #

Eq (TVar a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(==) :: TVar a -> TVar a -> Bool Source #

(/=) :: TVar a -> TVar a -> Bool Source #

Eq a => Eq (And a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(==) :: And a -> And a -> Bool Source #

(/=) :: And a -> And a -> Bool Source #

Eq a => Eq (Iff a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(==) :: Iff a -> Iff a -> Bool Source #

(/=) :: Iff a -> Iff a -> Bool Source #

Eq a => Eq (Ior a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(==) :: Ior a -> Ior a -> Bool Source #

(/=) :: Ior a -> Ior a -> Bool Source #

Eq a => Eq (Xor a) Source #

@since base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

(==) :: Xor a -> Xor a -> Bool Source #

(/=) :: Xor a -> Xor a -> Bool Source #

Eq a => Eq (Identity a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

(==) :: Identity a -> Identity a -> Bool Source #

(/=) :: Identity a -> Identity a -> Bool Source #

Eq a => Eq (First a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(==) :: First a -> First a -> Bool Source #

(/=) :: First a -> First a -> Bool Source #

Eq a => Eq (Last a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(==) :: Last a -> Last a -> Bool Source #

(/=) :: Last a -> Last a -> Bool Source #

Eq a => Eq (Down a) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(==) :: Down a -> Down a -> Bool Source #

(/=) :: Down a -> Down a -> Bool Source #

Eq a => Eq (Dual a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Dual a -> Dual a -> Bool Source #

(/=) :: Dual a -> Dual a -> Bool Source #

Eq a => Eq (Product a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Product a -> Product a -> Bool Source #

(/=) :: Product a -> Product a -> Bool Source #

Eq a => Eq (Sum a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Sum a -> Sum a -> Bool Source #

(/=) :: Sum a -> Sum a -> Bool Source #

Eq (ConstPtr a) Source # 
Instance details

Defined in GHC.Internal.Foreign.C.ConstPtr

Methods

(==) :: ConstPtr a -> ConstPtr a -> Bool Source #

(/=) :: ConstPtr a -> ConstPtr a -> Bool Source #

Eq (ForeignPtr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ForeignPtr

Eq a => Eq (ZipList a) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Methods

(==) :: ZipList a -> ZipList a -> Bool Source #

(/=) :: ZipList a -> ZipList a -> Bool Source #

Eq p => Eq (Par1 p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: Par1 p -> Par1 p -> Bool Source #

(/=) :: Par1 p -> Par1 p -> Bool Source #

Eq (IORef a) Source #

Pointer equality.

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.IORef

Methods

(==) :: IORef a -> IORef a -> Bool Source #

(/=) :: IORef a -> IORef a -> Bool Source #

Eq (MVar a) Source #

Compares the underlying pointers.

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.MVar

Methods

(==) :: MVar a -> MVar a -> Bool Source #

(/=) :: MVar a -> MVar a -> Bool Source #

Eq (FunPtr a) Source # 
Instance details

Defined in GHC.Internal.Ptr

Methods

(==) :: FunPtr a -> FunPtr a -> Bool Source #

(/=) :: FunPtr a -> FunPtr a -> Bool Source #

Eq (Ptr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool Source #

(/=) :: Ptr a -> Ptr a -> Bool Source #

Eq a => Eq (Ratio a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Methods

(==) :: Ratio a -> Ratio a -> Bool Source #

(/=) :: Ratio a -> Ratio a -> Bool Source #

Eq (StablePtr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Stable

Eq (StableName a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.StableName

Eq (SChar c) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

(==) :: SChar c -> SChar c -> Bool Source #

(/=) :: SChar c -> SChar c -> Bool Source #

Eq (SSymbol s) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

(==) :: SSymbol s -> SSymbol s -> Bool Source #

(/=) :: SSymbol s -> SSymbol s -> Bool Source #

Eq (SNat n) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

(==) :: SNat n -> SNat n -> Bool Source #

(/=) :: SNat n -> SNat n -> Bool Source #

Eq a => Eq (Maybe a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Maybe

Methods

(==) :: Maybe a -> Maybe a -> Bool Source #

(/=) :: Maybe a -> Maybe a -> Bool Source #

Eq a => Eq (Solo a) 
Instance details

Defined in GHC.Classes

Methods

(==) :: Solo a -> Solo a -> Bool Source #

(/=) :: Solo a -> Solo a -> Bool Source #

Eq a => Eq [a] 
Instance details

Defined in GHC.Classes

Methods

(==) :: [a] -> [a] -> Bool Source #

(/=) :: [a] -> [a] -> Bool Source #

(Ix i, Eq e) => Eq (Array i e) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Arr

Methods

(==) :: Array i e -> Array i e -> Bool Source #

(/=) :: Array i e -> Array i e -> Bool Source #

(Eq a, Eq b) => Eq (Either a b) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Either

Methods

(==) :: Either a b -> Either a b -> Bool Source #

(/=) :: Either a b -> Either a b -> Bool Source #

Eq (Proxy s) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool Source #

(/=) :: Proxy s -> Proxy s -> Bool Source #

Eq (TypeRep a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Methods

(==) :: TypeRep a -> TypeRep a -> Bool Source #

(/=) :: TypeRep a -> TypeRep a -> Bool Source #

Eq (U1 p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: U1 p -> U1 p -> Bool Source #

(/=) :: U1 p -> U1 p -> Bool Source #

Eq (V1 p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: V1 p -> V1 p -> Bool Source #

(/=) :: V1 p -> V1 p -> Bool Source #

Eq (IOArray i e) Source #

@since base-4.1.0.0

Instance details

Defined in GHC.Internal.IOArray

Methods

(==) :: IOArray i e -> IOArray i e -> Bool Source #

(/=) :: IOArray i e -> IOArray i e -> Bool Source #

Eq (STRef s a) Source #

Pointer equality.

@since base-2.01

Instance details

Defined in GHC.Internal.STRef

Methods

(==) :: STRef s a -> STRef s a -> Bool Source #

(/=) :: STRef s a -> STRef s a -> Bool Source #

(Eq a, Eq b) => Eq (a, b) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b) -> (a, b) -> Bool Source #

(/=) :: (a, b) -> (a, b) -> Bool Source #

Eq (STArray s i e) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Arr

Methods

(==) :: STArray s i e -> STArray s i e -> Bool Source #

(/=) :: STArray s i e -> STArray s i e -> Bool Source #

Eq a => Eq (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(==) :: Const a b -> Const a b -> Bool Source #

(/=) :: Const a b -> Const a b -> Bool Source #

Eq (f a) => Eq (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(==) :: Ap f a -> Ap f a -> Bool Source #

(/=) :: Ap f a -> Ap f a -> Bool Source #

Eq (f a) => Eq (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> Bool Source #

(/=) :: Alt f a -> Alt f a -> Bool Source #

Eq (Coercion a b) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Coercion

Methods

(==) :: Coercion a b -> Coercion a b -> Bool Source #

(/=) :: Coercion a b -> Coercion a b -> Bool Source #

Eq (a :~: b) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

(==) :: (a :~: b) -> (a :~: b) -> Bool Source #

(/=) :: (a :~: b) -> (a :~: b) -> Bool Source #

Eq (OrderingI a b) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

Methods

(==) :: OrderingI a b -> OrderingI a b -> Bool Source #

(/=) :: OrderingI a b -> OrderingI a b -> Bool Source #

(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (f p) => Eq (Rec1 f p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: Rec1 f p -> Rec1 f p -> Bool Source #

(/=) :: Rec1 f p -> Rec1 f p -> Bool Source #

Eq (URec (Ptr ()) p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

Eq (URec Char p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Char p -> URec Char p -> Bool Source #

(/=) :: URec Char p -> URec Char p -> Bool Source #

Eq (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool Source #

(/=) :: URec Double p -> URec Double p -> Bool Source #

Eq (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool Source #

(/=) :: URec Float p -> URec Float p -> Bool Source #

Eq (URec Int p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Int p -> URec Int p -> Bool Source #

(/=) :: URec Int p -> URec Int p -> Bool Source #

Eq (URec Word p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool Source #

(/=) :: URec Word p -> URec Word p -> Bool Source #

(Eq a, Eq b, Eq c) => Eq (a, b, c) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool Source #

(/=) :: (a, b, c) -> (a, b, c) -> Bool Source #

Eq (a :~~: b) Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

(==) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(/=) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(/=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

Eq c => Eq (K1 i c p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: K1 i c p -> K1 i c p -> Bool Source #

(/=) :: K1 i c p -> K1 i c p -> Bool Source #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(/=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

Eq (f (g p)) => Eq ((f :.: g) p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(/=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

Eq (f p) => Eq (M1 i c f p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: M1 i c f p -> M1 i c f p -> Bool Source #

(/=) :: M1 i c f p -> M1 i c f p -> Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

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, then x <= z = True
Reflexivity
x <= x = True
Antisymmetry
if x <= y && y <= x = True, then x == y = True

The following operator interactions are expected to hold:

  1. x >= y = y <= x
  2. x < y = x <= y && x /= y
  3. x > y = y < x
  4. x < y = compare x y == LT
  5. x > y = compare x y == GT
  6. x == y = compare x y == EQ
  7. min x y == if x <= y then x else y = True
  8. 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.

Minimal complete definition

compare | (<=)

Methods

compare :: a -> a -> Ordering Source #

(<) :: a -> a -> Bool infix 4 Source #

(<=) :: a -> a -> Bool infix 4 Source #

(>) :: a -> a -> Bool infix 4 Source #

(>=) :: a -> a -> Bool infix 4 Source #

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances

Instances details
Ord BigNat 
Instance details

Defined in GHC.Num.BigNat

Ord Void Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

Ord ByteOrder Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Ord ClosureType Source # 
Instance details

Defined in GHC.Internal.ClosureTypes

Ord BlockReason Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord ThreadId Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord ThreadStatus Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord All Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering Source #

(<) :: All -> All -> Bool Source #

(<=) :: All -> All -> Bool Source #

(>) :: All -> All -> Bool Source #

(>=) :: All -> All -> Bool Source #

max :: All -> All -> All Source #

min :: All -> All -> All Source #

Ord Any Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering Source #

(<) :: Any -> Any -> Bool Source #

(<=) :: Any -> Any -> Bool Source #

(>) :: Any -> Any -> Bool Source #

(>=) :: Any -> Any -> Bool Source #

max :: Any -> Any -> Any Source #

min :: Any -> Any -> Any Source #

Ord SomeTypeRep Source # 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Ord Unique Source # 
Instance details

Defined in GHC.Internal.Data.Unique

Ord Version Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Version

Ord TimeoutKey Source # 
Instance details

Defined in GHC.Internal.Event.TimeOut

Ord ErrorCall Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Exception

Ord ArithException Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Ord Fingerprint Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Ord CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord Associativity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Ord DecidedStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Ord Fixity Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Ord SourceStrictness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Ord SourceUnpackedness Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Ord SeekMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Ord ArrayException Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Ord AsyncException Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Ord ExitCode Source # 
Instance details

Defined in GHC.Internal.IO.Exception

Ord BufferMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Ord Newline Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Ord NewlineMode Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Ord IOMode Source #

@since base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Ord Int16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Ord Int32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Ord Int64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Ord Int8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Int

Ord CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CCc -> CCc -> Ordering Source #

(<) :: CCc -> CCc -> Bool Source #

(<=) :: CCc -> CCc -> Bool Source #

(>) :: CCc -> CCc -> Bool Source #

(>=) :: CCc -> CCc -> Bool Source #

max :: CCc -> CCc -> CCc Source #

min :: CCc -> CCc -> CCc Source #

Ord CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: CId -> CId -> Ordering Source #

(<) :: CId -> CId -> Bool Source #

(<=) :: CId -> CId -> Bool Source #

(>) :: CId -> CId -> Bool Source #

(>=) :: CId -> CId -> Bool Source #

max :: CId -> CId -> CId Source #

min :: CId -> CId -> CId Source #

Ord CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CTimer Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Ord Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

compare :: Fd -> Fd -> Ordering Source #

(<) :: Fd -> Fd -> Bool Source #

(<=) :: Fd -> Fd -> Bool Source #

(>) :: Fd -> Fd -> Bool Source #

(>=) :: Fd -> Fd -> Bool Source #

max :: Fd -> Fd -> Fd Source #

min :: Fd -> Fd -> Fd Source #

Ord SomeChar Source # 
Instance details

Defined in GHC.Internal.TypeLits

Ord SomeSymbol Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeLits

Ord SomeNat Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeNats

Ord GeneralCategory Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Unicode

Ord Word16 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Ord Word32 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Ord Word64 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Ord Word8 Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Word

Ord Ordering 
Instance details

Defined in GHC.Classes

Ord TyCon 
Instance details

Defined in GHC.Classes

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Ord Natural 
Instance details

Defined in GHC.Num.Natural

Ord () 
Instance details

Defined in GHC.Classes

Methods

compare :: () -> () -> Ordering Source #

(<) :: () -> () -> Bool Source #

(<=) :: () -> () -> Bool Source #

(>) :: () -> () -> Bool Source #

(>=) :: () -> () -> Bool Source #

max :: () -> () -> () Source #

min :: () -> () -> () Source #

Ord Bool 
Instance details

Defined in GHC.Classes

Ord Char 
Instance details

Defined in GHC.Classes

Ord Double

IEEE 754 Double-precision type includes not only numbers, but also positive and negative infinities and a special element called NaN (which can be quiet or signal).

IEEE 754-2008, section 5.11 requires that if at least one of arguments of <=, <, >, >= is NaN then the result of the comparison is False, and instance Ord Double complies with this requirement. This violates the reflexivity: both NaN <= NaN and NaN >= NaN are False.

IEEE 754-2008, section 5.10 defines totalOrder predicate. Unfortunately, compare on Doubles violates the IEEE standard and does not define a total order. More specifically, both compare NaN x and compare x NaN always return GT.

Thus, users must be extremely cautious when using instance Ord Double. For instance, one should avoid ordered containers with keys represented by Double, because data loss and corruption may happen. An IEEE-compliant compare is available in fp-ieee package as TotallyOrdered newtype.

Moving further, the behaviour of min and max with regards to NaN is also non-compliant. IEEE 754-2008, section 5.3.1 defines that quiet NaN should be treated as a missing data by minNum and maxNum functions, for example, minNum(NaN, 1) = minNum(1, NaN) = 1. Some languages such as Java deviate from the standard implementing minNum(NaN, 1) = minNum(1, NaN) = NaN. However, min / max in base are even worse: min NaN 1 is 1, but min 1 NaN is NaN.

IEEE 754-2008 compliant min / max can be found in ieee754 package under minNum / maxNum names. Implementations compliant with minimumNumber / maximumNumber from a newer IEEE 754-2019, section 9.6 are available from fp-ieee package.

Instance details

Defined in GHC.Classes

Ord Float

See instance Ord Double for discussion of deviations from IEEE 754 standard.

Instance details

Defined in GHC.Classes

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering Source #

(<) :: Int -> Int -> Bool Source #

(<=) :: Int -> Int -> Bool Source #

(>) :: Int -> Int -> Bool Source #

(>=) :: Int -> Int -> Bool Source #

max :: Int -> Int -> Int Source #

min :: Int -> Int -> Int Source #

Ord Word 
Instance details

Defined in GHC.Classes

Ord a => Ord (NonEmpty a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Ord a => Ord (Identity a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Ord a => Ord (First a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

compare :: First a -> First a -> Ordering Source #

(<) :: First a -> First a -> Bool Source #

(<=) :: First a -> First a -> Bool Source #

(>) :: First a -> First a -> Bool Source #

(>=) :: First a -> First a -> Bool Source #

max :: First a -> First a -> First a Source #

min :: First a -> First a -> First a Source #

Ord a => Ord (Last a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

compare :: Last a -> Last a -> Ordering Source #

(<) :: Last a -> Last a -> Bool Source #

(<=) :: Last a -> Last a -> Bool Source #

(>) :: Last a -> Last a -> Bool Source #

(>=) :: Last a -> Last a -> Bool Source #

max :: Last a -> Last a -> Last a Source #

min :: Last a -> Last a -> Last a Source #

Ord a => Ord (Down a) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

compare :: Down a -> Down a -> Ordering Source #

(<) :: Down a -> Down a -> Bool Source #

(<=) :: Down a -> Down a -> Bool Source #

(>) :: Down a -> Down a -> Bool Source #

(>=) :: Down a -> Down a -> Bool Source #

max :: Down a -> Down a -> Down a Source #

min :: Down a -> Down a -> Down a Source #

Ord a => Ord (Dual a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> Ordering Source #

(<) :: Dual a -> Dual a -> Bool Source #

(<=) :: Dual a -> Dual a -> Bool Source #

(>) :: Dual a -> Dual a -> Bool Source #

(>=) :: Dual a -> Dual a -> Bool Source #

max :: Dual a -> Dual a -> Dual a Source #

min :: Dual a -> Dual a -> Dual a Source #

Ord a => Ord (Product a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Ord a => Ord (Sum a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering Source #

(<) :: Sum a -> Sum a -> Bool Source #

(<=) :: Sum a -> Sum a -> Bool Source #

(>) :: Sum a -> Sum a -> Bool Source #

(>=) :: Sum a -> Sum a -> Bool Source #

max :: Sum a -> Sum a -> Sum a Source #

min :: Sum a -> Sum a -> Sum a Source #

Ord (ConstPtr a) Source # 
Instance details

Defined in GHC.Internal.Foreign.C.ConstPtr

Ord (ForeignPtr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ForeignPtr

Ord a => Ord (ZipList a) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Ord p => Ord (Par1 p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: Par1 p -> Par1 p -> Ordering Source #

(<) :: Par1 p -> Par1 p -> Bool Source #

(<=) :: Par1 p -> Par1 p -> Bool Source #

(>) :: Par1 p -> Par1 p -> Bool Source #

(>=) :: Par1 p -> Par1 p -> Bool Source #

max :: Par1 p -> Par1 p -> Par1 p Source #

min :: Par1 p -> Par1 p -> Par1 p Source #

Ord (FunPtr a) Source # 
Instance details

Defined in GHC.Internal.Ptr

Methods

compare :: FunPtr a -> FunPtr a -> Ordering Source #

(<) :: FunPtr a -> FunPtr a -> Bool Source #

(<=) :: FunPtr a -> FunPtr a -> Bool Source #

(>) :: FunPtr a -> FunPtr a -> Bool Source #

(>=) :: FunPtr a -> FunPtr a -> Bool Source #

max :: FunPtr a -> FunPtr a -> FunPtr a Source #

min :: FunPtr a -> FunPtr a -> FunPtr a Source #

Ord (Ptr a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering Source #

(<) :: Ptr a -> Ptr a -> Bool Source #

(<=) :: Ptr a -> Ptr a -> Bool Source #

(>) :: Ptr a -> Ptr a -> Bool Source #

(>=) :: Ptr a -> Ptr a -> Bool Source #

max :: Ptr a -> Ptr a -> Ptr a Source #

min :: Ptr a -> Ptr a -> Ptr a Source #

Integral a => Ord (Ratio a) Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

compare :: Ratio a -> Ratio a -> Ordering Source #

(<) :: Ratio a -> Ratio a -> Bool Source #

(<=) :: Ratio a -> Ratio a -> Bool Source #

(>) :: Ratio a -> Ratio a -> Bool Source #

(>=) :: Ratio a -> Ratio a -> Bool Source #

max :: Ratio a -> Ratio a -> Ratio a Source #

min :: Ratio a -> Ratio a -> Ratio a Source #

Ord (SChar c) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

compare :: SChar c -> SChar c -> Ordering Source #

(<) :: SChar c -> SChar c -> Bool Source #

(<=) :: SChar c -> SChar c -> Bool Source #

(>) :: SChar c -> SChar c -> Bool Source #

(>=) :: SChar c -> SChar c -> Bool Source #

max :: SChar c -> SChar c -> SChar c Source #

min :: SChar c -> SChar c -> SChar c Source #

Ord (SSymbol s) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Ord (SNat n) Source #

@since base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

compare :: SNat n -> SNat n -> Ordering Source #

(<) :: SNat n -> SNat n -> Bool Source #

(<=) :: SNat n -> SNat n -> Bool Source #

(>) :: SNat n -> SNat n -> Bool Source #

(>=) :: SNat n -> SNat n -> Bool Source #

max :: SNat n -> SNat n -> SNat n Source #

min :: SNat n -> SNat n -> SNat n Source #

Ord a => Ord (Maybe a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering Source #

(<) :: Maybe a -> Maybe a -> Bool Source #

(<=) :: Maybe a -> Maybe a -> Bool Source #

(>) :: Maybe a -> Maybe a -> Bool Source #

(>=) :: Maybe a -> Maybe a -> Bool Source #

max :: Maybe a -> Maybe a -> Maybe a Source #

min :: Maybe a -> Maybe a -> Maybe a Source #

Ord a => Ord (Solo a) 
Instance details

Defined in GHC.Classes

Methods

compare :: Solo a -> Solo a -> Ordering Source #

(<) :: Solo a -> Solo a -> Bool Source #

(<=) :: Solo a -> Solo a -> Bool Source #

(>) :: Solo a -> Solo a -> Bool Source #

(>=) :: Solo a -> Solo a -> Bool Source #

max :: Solo a -> Solo a -> Solo a Source #

min :: Solo a -> Solo a -> Solo a Source #

Ord a => Ord [a] 
Instance details

Defined in GHC.Classes

Methods

compare :: [a] -> [a] -> Ordering Source #

(<) :: [a] -> [a] -> Bool Source #

(<=) :: [a] -> [a] -> Bool Source #

(>) :: [a] -> [a] -> Bool Source #

(>=) :: [a] -> [a] -> Bool Source #

max :: [a] -> [a] -> [a] Source #

min :: [a] -> [a] -> [a] Source #

(Ix i, Ord e) => Ord (Array i e) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Arr

Methods

compare :: Array i e -> Array i e -> Ordering Source #

(<) :: Array i e -> Array i e -> Bool Source #

(<=) :: Array i e -> Array i e -> Bool Source #

(>) :: Array i e -> Array i e -> Bool Source #

(>=) :: Array i e -> Array i e -> Bool Source #

max :: Array i e -> Array i e -> Array i e Source #

min :: Array i e -> Array i e -> Array i e Source #

(Ord a, Ord b) => Ord (Either a b) Source #

@since base-2.01

Instance details

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 #

max :: Either a b -> Either a b -> Either a b Source #

min :: Either a b -> Either a b -> Either a b Source #

Ord (Proxy s) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering Source #

(<) :: Proxy s -> Proxy s -> Bool Source #

(<=) :: Proxy s -> Proxy s -> Bool Source #

(>) :: Proxy s -> Proxy s -> Bool Source #

(>=) :: Proxy s -> Proxy s -> Bool Source #

max :: Proxy s -> Proxy s -> Proxy s Source #

min :: Proxy s -> Proxy s -> Proxy s Source #

Ord (TypeRep a) Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Ord (U1 p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: U1 p -> U1 p -> Ordering Source #

(<) :: U1 p -> U1 p -> Bool Source #

(<=) :: U1 p -> U1 p -> Bool Source #

(>) :: U1 p -> U1 p -> Bool Source #

(>=) :: U1 p -> U1 p -> Bool Source #

max :: U1 p -> U1 p -> U1 p Source #

min :: U1 p -> U1 p -> U1 p Source #

Ord (V1 p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: V1 p -> V1 p -> Ordering Source #

(<) :: V1 p -> V1 p -> Bool Source #

(<=) :: V1 p -> V1 p -> Bool Source #

(>) :: V1 p -> V1 p -> Bool Source #

(>=) :: V1 p -> V1 p -> Bool Source #

max :: V1 p -> V1 p -> V1 p Source #

min :: V1 p -> V1 p -> V1 p Source #

(Ord a, Ord b) => Ord (a, b) 
Instance details

Defined in GHC.Classes

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 #

max :: (a, b) -> (a, b) -> (a, b) Source #

min :: (a, b) -> (a, b) -> (a, b) Source #

Ord a => Ord (Const a b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

compare :: Const a b -> Const a b -> Ordering Source #

(<) :: Const a b -> Const a b -> Bool Source #

(<=) :: Const a b -> Const a b -> Bool Source #

(>) :: Const a b -> Const a b -> Bool Source #

(>=) :: Const a b -> Const a b -> Bool Source #

max :: Const a b -> Const a b -> Const a b Source #

min :: Const a b -> Const a b -> Const a b Source #

Ord (f a) => Ord (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

compare :: Ap f a -> Ap f a -> Ordering Source #

(<) :: Ap f a -> Ap f a -> Bool Source #

(<=) :: Ap f a -> Ap f a -> Bool Source #

(>) :: Ap f a -> Ap f a -> Bool Source #

(>=) :: Ap f a -> Ap f a -> Bool Source #

max :: Ap f a -> Ap f a -> Ap f a Source #

min :: Ap f a -> Ap f a -> Ap f a Source #

Ord (f a) => Ord (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> Ordering Source #

(<) :: Alt f a -> Alt f a -> Bool Source #

(<=) :: Alt f a -> Alt f a -> Bool Source #

(>) :: Alt f a -> Alt f a -> Bool Source #

(>=) :: Alt f a -> Alt f a -> Bool Source #

max :: Alt f a -> Alt f a -> Alt f a Source #

min :: Alt f a -> Alt f a -> Alt f a Source #

Ord (Coercion a b) Source #

@since base-4.7.0.0

Instance details

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

Instance details

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 #

max :: (a :~: b) -> (a :~: b) -> a :~: b Source #

min :: (a :~: b) -> (a :~: b) -> a :~: b Source #

(Generic1 f, Ord (Rep1 f a)) => Ord (Generically1 f a) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Generics

Ord (f p) => Ord (Rec1 f p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: Rec1 f p -> Rec1 f p -> Ordering Source #

(<) :: Rec1 f p -> Rec1 f p -> Bool Source #

(<=) :: Rec1 f p -> Rec1 f p -> Bool Source #

(>) :: Rec1 f p -> Rec1 f p -> Bool Source #

(>=) :: Rec1 f p -> Rec1 f p -> Bool Source #

max :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

min :: Rec1 f p -> Rec1 f p -> Rec1 f p Source #

Ord (URec (Ptr ()) p) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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 #

max :: URec Char p -> URec Char p -> URec Char p Source #

min :: URec Char p -> URec Char p -> URec Char p Source #

Ord (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Ord (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Ord (URec Int p) Source #

@since base-4.9.0.0

Instance details

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 #

max :: URec Int p -> URec Int p -> URec Int p Source #

min :: URec Int p -> URec Int p -> URec Int p Source #

Ord (URec Word p) Source #

@since base-4.9.0.0

Instance details

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 #

max :: URec Word p -> URec Word p -> URec Word p Source #

min :: URec Word p -> URec Word p -> URec Word p Source #

(Ord a, Ord b, Ord c) => Ord (a, b, c) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering Source #

(<) :: (a, b, c) -> (a, b, c) -> Bool Source #

(<=) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>=) :: (a, b, c) -> (a, b, c) -> Bool Source #

max :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

min :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

Ord (a :~~: b) Source #

@since base-4.10.0.0

Instance details

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 #

max :: (a :~~: b) -> (a :~~: b) -> a :~~: b Source #

min :: (a :~~: b) -> (a :~~: b) -> a :~~: b Source #

(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) Source #

@since base-4.7.0.0

Instance details

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 #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) Source #

@since base-4.7.0.0

Instance details

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 #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

Ord c => Ord (K1 i c p) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: K1 i c p -> K1 i c p -> Ordering Source #

(<) :: K1 i c p -> K1 i c p -> Bool Source #

(<=) :: K1 i c p -> K1 i c p -> Bool Source #

(>) :: K1 i c p -> K1 i c p -> Bool Source #

(>=) :: K1 i c p -> K1 i c p -> Bool Source #

max :: K1 i c p -> K1 i c p -> K1 i c p Source #

min :: K1 i c p -> K1 i c p -> K1 i c p Source #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 
Instance details

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

Instance details

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 #

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

Ord (f p) => Ord (M1 i c f p) Source #

@since base-4.7.0.0

Instance details

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 #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

min :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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 #

(&&) :: Bool -> Bool -> Bool infixr 3 Source #

Boolean "and", lazy in the second argument

(||) :: Bool -> Bool -> Bool infixr 2 Source #

Boolean "or", lazy in the second argument

not :: Bool -> Bool Source #

Boolean "not"

divModInt# :: Int# -> Int# -> (# Int#, Int# #) Source #

module GHC.Magic

data Word Source #

A Word is an unsigned integral type, with the same size as Int.

Constructors

W# Word# 

Instances

Instances details
Bits Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Bits

FiniteBits Word Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Bits

Data Word Source #

@since base-4.0.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Enum

Enum Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Storable Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Ix Word Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Ix

Num Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Read Word Source #

@since base-4.5.0.0

Instance details

Defined in GHC.Internal.Read

Integral Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Real Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Real

Show Word Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool Source #

(/=) :: Word -> Word -> Bool Source #

Ord Word 
Instance details

Defined in GHC.Classes

Generic1 (URec Word :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Word :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Word a -> Rep1 (URec Word :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Word :: k -> Type) a -> URec Word a Source #

Foldable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UWord a -> a Source #

product :: Num a => UWord a -> a Source #

Traversable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) Source #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) Source #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) Source #

sequence :: Monad m => UWord (m a) -> m (UWord a) Source #

Functor (URec Word :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Generic (URec Word p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Word p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

Methods

from :: URec Word p -> Rep (URec Word p) x Source #

to :: Rep (URec Word p) x -> URec Word p Source #

Show (URec Word p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Word p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool Source #

(/=) :: URec Word p -> URec Word p -> Bool Source #

Ord (URec Word p) Source #

@since base-4.9.0.0

Instance details

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 #

max :: URec Word p -> URec Word p -> URec Word p Source #

min :: URec Word p -> URec Word p -> URec Word p Source #

data URec Word (p :: k) Source #

Used for marking occurrences of Word#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Word (p :: k) = UWord {}
type Rep1 (URec Word :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

data Float Source #

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.

Constructors

F# Float# 

Instances

Instances details
Data Float Source #

@since base-4.0.0.0

Instance details

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

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5 :: Float]
[0.0,1.0,2.0]
Instance details

Defined in GHC.Internal.Float

Floating Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Storable Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

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:

>>> (0.1 + 0.1 :: Float) + 0.5 == 0.1 + (0.1 + 0.5)
False
>>> (0.1 + 0.2 :: Float) * 0.9 == 0.1 * 0.9 + 0.2 * 0.9
False
>>> (0.1 * 0.1 :: Float) * 0.9 == 0.1 * (0.1 * 0.9)
False
Instance details

Defined in GHC.Internal.Float

Read Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Fractional Float Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
>>> map (/ 0) [-1, 0, 1 :: Float]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1 :: Float]
[NaN,NaN,NaN]
Instance details

Defined in GHC.Internal.Float

Real Float Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0 :: Float)
340282366920938463463374607431768211456 % 1
>>> toRational (0/0 :: Float)
510423550381407695195061911147652317184 % 1
Instance details

Defined in GHC.Internal.Float

RealFrac Float Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0 :: Float] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Float)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

Defined in GHC.Internal.Float

Methods

properFraction :: Integral b => Float -> (b, Float) Source #

truncate :: Integral b => Float -> b Source #

round :: Integral b => Float -> b Source #

ceiling :: Integral b => Float -> b Source #

floor :: Integral b => Float -> b Source #

Show Float Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Eq Float

Note that due to the presence of NaN, Float's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float's Eq instance does not satisfy extensionality:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

(==) :: Float -> Float -> Bool Source #

(/=) :: Float -> Float -> Bool Source #

Ord Float

See instance Ord Double for discussion of deviations from IEEE 754 standard.

Instance details

Defined in GHC.Classes

Generic1 (URec Float :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Float :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Float a -> Rep1 (URec Float :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Float :: k -> Type) a -> URec Float a Source #

Foldable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UFloat a -> a Source #

product :: Num a => UFloat a -> a Source #

Traversable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Generic (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Float p) 
Instance details

Defined in GHC.Internal.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

Methods

from :: URec Float p -> Rep (URec Float p) x Source #

to :: Rep (URec Float p) x -> URec Float p Source #

Show (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Eq (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Float p -> URec Float p -> Bool Source #

(/=) :: URec Float p -> URec Float p -> Bool Source #

Ord (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

data URec Float (p :: k) Source #

Used for marking occurrences of Float#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Float (p :: k) = UFloat {}
type Rep1 (URec Float :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type)))
type Rep (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

data Int Source #

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.

Constructors

I# Int# 

Instances

Instances details
Bits Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Bits

FiniteBits Int Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Bits

Data Int Source #

@since base-4.0.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Enum

Enum Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Storable Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Ix Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Num Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Read Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Integral Int Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

quotRem :: Int -> Int -> (Int, Int) Source #

divMod :: Int -> Int -> (Int, Int) Source #

toInteger :: Int -> Integer Source #

Real Int Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Int Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Int 
Instance details

Defined in GHC.Classes

Methods

(==) :: Int -> Int -> Bool Source #

(/=) :: Int -> Int -> Bool Source #

Ord Int 
Instance details

Defined in GHC.Classes

Methods

compare :: Int -> Int -> Ordering Source #

(<) :: Int -> Int -> Bool Source #

(<=) :: Int -> Int -> Bool Source #

(>) :: Int -> Int -> Bool Source #

(>=) :: Int -> Int -> Bool Source #

max :: Int -> Int -> Int Source #

min :: Int -> Int -> Int Source #

Generic1 (URec Int :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Int :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Int a -> Rep1 (URec Int :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Int :: k -> Type) a -> URec Int a Source #

Foldable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UInt a -> a Source #

product :: Num a => UInt a -> a Source #

Traversable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source #

sequence :: Monad m => UInt (m a) -> m (UInt a) Source #

Functor (URec Int :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Generic (URec Int p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Int p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

Methods

from :: URec Int p -> Rep (URec Int p) x Source #

to :: Rep (URec Int p) x -> URec Int p Source #

Show (URec Int p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Int p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Int p -> URec Int p -> Bool Source #

(/=) :: URec Int p -> URec Int p -> Bool Source #

Ord (URec Int p) Source #

@since base-4.9.0.0

Instance details

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 #

max :: URec Int p -> URec Int p -> URec Int p Source #

min :: URec Int p -> URec Int p -> URec Int p Source #

data URec Int (p :: k) Source #

Used for marking occurrences of Int#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Int (p :: k) = UInt {}
type Rep1 (URec Int :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))
type Rep (URec Int p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

data TYPE (a :: RuntimeRep) Source #

Instances

Instances details
Generic1 NonEmpty Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 NonEmpty

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Generic1 Identity Source # 
Instance details

Defined in GHC.Internal.Data.Functor.Identity

Associated Types

type Rep1 Identity

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "GHC.Internal.Data.Functor.Identity" "ghc-internal" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Generic1 First Source # 
Instance details

Defined in GHC.Internal.Data.Monoid

Associated Types

type Rep1 First

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 First = D1 ('MetaData "First" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))

Methods

from1 :: First a -> Rep1 First a Source #

to1 :: Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in GHC.Internal.Data.Monoid

Associated Types

type Rep1 Last

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))

Methods

from1 :: Last a -> Rep1 Last a Source #

to1 :: Rep1 Last a -> Last a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Down

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Down = D1 ('MetaData "Down" "GHC.Internal.Data.Ord" "ghc-internal" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Down a -> Rep1 Down a Source #

to1 :: Rep1 Down a -> Down a Source #

Generic1 Dual Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Dual

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Dual a -> Rep1 Dual a Source #

to1 :: Rep1 Dual a -> Dual a Source #

Generic1 Product Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Product

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Generic1 Sum Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Sum

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Sum a -> Rep1 Sum a Source #

to1 :: Rep1 Sum a -> Sum a Source #

Generic1 ZipList Source # 
Instance details

Defined in GHC.Internal.Functor.ZipList

Associated Types

type Rep1 ZipList

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

type Rep1 ZipList = D1 ('MetaData "ZipList" "GHC.Internal.Functor.ZipList" "ghc-internal" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
Generic1 Par1 Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Par1

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Par1 a -> Rep1 Par1 a Source #

to1 :: Rep1 Par1 a -> Par1 a Source #

Generic1 Maybe Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Maybe

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Maybe a -> Rep1 Maybe a Source #

to1 :: Rep1 Maybe a -> Maybe a Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Solo

@since base-4.15

Instance details

Defined in GHC.Internal.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Solo a -> Rep1 Solo a Source #

to1 :: Rep1 Solo a -> Solo a Source #

Generic1 [] Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 []

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: [a] -> Rep1 [] a Source #

to1 :: Rep1 [] a -> [a] Source #

Monad m => Category (Kleisli m :: Type -> Type -> Type) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

id :: Kleisli m a a Source #

(.) :: Kleisli m b c -> Kleisli m a b -> Kleisli m a c Source #

Generic1 (Either a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Either a :: Type -> Type)

@since base-4.6.0.0

Instance details

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))

Methods

from1 :: Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: Rep1 (Either a) a0 -> Either a a0 Source #

Generic1 ((,) a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,) a :: Type -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, a0) -> Rep1 ((,) a) a0 Source #

to1 :: Rep1 ((,) a) a0 -> (a, a0) Source #

Category (->) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: a -> a Source #

(.) :: (b -> c) -> (a -> b) -> a -> c Source #

Generic1 (Kleisli m a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Control.Arrow

Associated Types

type Rep1 (Kleisli m a :: Type -> Type)

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "GHC.Internal.Control.Arrow" "ghc-internal" 'True) (C1 ('MetaCons "Kleisli" 'PrefixI 'True) (S1 ('MetaSel ('Just "runKleisli") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ((FUN 'Many a :: Type -> Type) :.: Rec1 m)))

Methods

from1 :: Kleisli m a a0 -> Rep1 (Kleisli m a) a0 Source #

to1 :: Rep1 (Kleisli m a) a0 -> Kleisli m a a0 Source #

Generic1 ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,) a b :: Type -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, a0) -> Rep1 ((,,) a b) a0 Source #

to1 :: Rep1 ((,,) a b) a0 -> (a, b, a0) Source #

Generic1 ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, a0) -> Rep1 ((,,,) a b c) a0 Source #

to1 :: Rep1 ((,,,) a b c) a0 -> (a, b, c, a0) Source #

Generic1 ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, a0) -> Rep1 ((,,,,) a b c d) a0 Source #

to1 :: Rep1 ((,,,,) a b c d) a0 -> (a, b, c, d, a0) Source #

Functor f => Generic1 (f :.: g :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (f :.: g :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Comp1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComp1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))

Methods

from1 :: forall (a :: k). (f :.: g) a -> Rep1 (f :.: g) a Source #

to1 :: forall (a :: k). Rep1 (f :.: g) a -> (f :.: g) a Source #

Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, a0) -> Rep1 ((,,,,,) a b c d e) a0 Source #

to1 :: Rep1 ((,,,,,) a b c d e) a0 -> (a, b, c, d, e, a0) Source #

Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, f, a0) -> Rep1 ((,,,,,,) a b c d e f) a0 Source #

to1 :: Rep1 ((,,,,,,) a b c d e f) a0 -> (a, b, c, d, e, f, a0) Source #

Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, f, g, a0) -> Rep1 ((,,,,,,,) a b c d e f g) a0 Source #

to1 :: Rep1 ((,,,,,,,) a b c d e f g) a0 -> (a, b, c, d, e, f, g, a0) Source #

Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type)

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type)

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

empty :: Proxy a Source #

(<|>) :: Proxy a -> Proxy a -> Proxy a Source #

some :: Proxy a -> Proxy [a] Source #

many :: Proxy a -> Proxy [a] Source #

Alternative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: U1 a Source #

(<|>) :: U1 a -> U1 a -> U1 a Source #

some :: U1 a -> U1 [a] Source #

many :: U1 a -> U1 [a] Source #

Applicative (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a Source #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b Source #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

(*>) :: Proxy a -> Proxy b -> Proxy b Source #

(<*) :: Proxy a -> Proxy b -> Proxy a Source #

Applicative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> U1 a Source #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b Source #

liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c Source #

(*>) :: U1 a -> U1 b -> U1 b Source #

(<*) :: U1 a -> U1 b -> U1 a Source #

Functor (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b Source #

(<$) :: a -> Proxy b -> Proxy a Source #

Functor (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b Source #

(<$) :: a -> U1 b -> U1 a Source #

Functor (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> V1 a -> V1 b Source #

(<$) :: a -> V1 b -> V1 a Source #

Monad (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source #

(>>) :: Proxy a -> Proxy b -> Proxy b Source #

return :: a -> Proxy a Source #

Monad (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: U1 a -> (a -> U1 b) -> U1 b Source #

(>>) :: U1 a -> U1 b -> U1 b Source #

return :: a -> U1 a Source #

MonadPlus (Proxy :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a Source #

mplus :: Proxy a -> Proxy a -> Proxy a Source #

MonadPlus (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: U1 a Source #

mplus :: U1 a -> U1 a -> U1 a Source #

Foldable (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

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 #

sum :: Num a => Proxy a -> a Source #

product :: Num a => Proxy a -> a Source #

Foldable (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

null :: U1 a -> Bool 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 #

sum :: Num a => U1 a -> a Source #

product :: Num a => U1 a -> a Source #

Foldable (UAddr :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Foldable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UChar a -> a Source #

product :: Num a => UChar a -> a Source #

Foldable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UDouble a -> a Source #

product :: Num a => UDouble a -> a Source #

Foldable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UFloat a -> a Source #

product :: Num a => UFloat a -> a Source #

Foldable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UInt a -> a Source #

product :: Num a => UInt a -> a Source #

Foldable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UWord a -> a Source #

product :: Num a => UWord a -> a Source #

Foldable (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

null :: V1 a -> Bool 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 #

sum :: Num a => V1 a -> a Source #

product :: Num a => V1 a -> a Source #

Traversable (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) Source #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) Source #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) Source #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) Source #

Traversable (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> U1 a -> f (U1 b) Source #

sequenceA :: Applicative f => U1 (f a) -> f (U1 a) Source #

mapM :: Monad m => (a -> m b) -> U1 a -> m (U1 b) Source #

sequence :: Monad m => U1 (m a) -> m (U1 a) Source #

Traversable (UAddr :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Traversable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

Traversable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Traversable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Traversable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source #

sequence :: Monad m => UInt (m a) -> m (UInt a) Source #

Traversable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) Source #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) Source #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) Source #

sequence :: Monad m => UWord (m a) -> m (UWord a) Source #

Traversable (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> V1 a -> f (V1 b) Source #

sequenceA :: Applicative f => V1 (f a) -> f (V1 a) Source #

mapM :: Monad m => (a -> m b) -> V1 a -> m (V1 b) Source #

sequence :: Monad m => V1 (m a) -> m (V1 a) Source #

Alternative f => Alternative (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

empty :: Ap f a Source #

(<|>) :: Ap f a -> Ap f a -> Ap f a Source #

some :: Ap f a -> Ap f [a] Source #

many :: Ap f a -> Ap f [a] Source #

Alternative f => Alternative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

empty :: Alt f a Source #

(<|>) :: Alt f a -> Alt f a -> Alt f a Source #

some :: Alt f a -> Alt f [a] Source #

many :: Alt f a -> Alt f [a] Source #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Alternative f => Alternative (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: Rec1 f a Source #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

some :: Rec1 f a -> Rec1 f [a] Source #

many :: Rec1 f a -> Rec1 f [a] Source #

Monoid m => Applicative (Const m :: Type -> Type) Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

pure :: a -> Const m a Source #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b Source #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c Source #

(*>) :: Const m a -> Const m b -> Const m b Source #

(<*) :: Const m a -> Const m b -> Const m a Source #

Applicative f => Applicative (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

pure :: a -> Ap f a Source #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b Source #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c Source #

(*>) :: Ap f a -> Ap f b -> Ap f b Source #

(<*) :: Ap f a -> Ap f b -> Ap f a Source #

Applicative f => Applicative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Alt f a Source #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b Source #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source #

(*>) :: Alt f a -> Alt f b -> Alt f b Source #

(<*) :: Alt f a -> Alt f b -> Alt f a Source #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> Rec1 f a Source #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b Source #

liftA2 :: (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c Source #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a Source #

Functor (Const m :: Type -> Type) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source #

(<$) :: a -> Const m b -> Const m a Source #

Functor f => Functor (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b Source #

(<$) :: a -> Ap f b -> Ap f a Source #

Functor f => Functor (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source #

(<$) :: a -> Alt f b -> Alt f a Source #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> Rec1 f a -> Rec1 f b Source #

(<$) :: a -> Rec1 f b -> Rec1 f a Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Functor (URec Char :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Functor (URec Int :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Functor (URec Word :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Monad f => Monad (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b Source #

(>>) :: Ap f a -> Ap f b -> Ap f b Source #

return :: a -> Ap f a Source #

Monad f => Monad (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b Source #

(>>) :: Alt f a -> Alt f b -> Alt f b Source #

return :: a -> Alt f a Source #

Monad f => Monad (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b Source #

(>>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

return :: a -> Rec1 f a Source #

MonadPlus f => MonadPlus (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mzero :: Ap f a Source #

mplus :: Ap f a -> Ap f a -> Ap f a Source #

MonadPlus f => MonadPlus (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mzero :: Alt f a Source #

mplus :: Alt f a -> Alt f a -> Alt f a Source #

MonadPlus f => MonadPlus (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: Rec1 f a Source #

mplus :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

MonadFail f => MonadFail (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fail :: String -> Ap f a Source #

MonadFix f => MonadFix (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Ap f a) -> Ap f a Source #

MonadFix f => MonadFix (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Alt f a) -> Alt f a Source #

MonadFix f => MonadFix (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Rec1 f a) -> Rec1 f a Source #

Data t => Data (Proxy t) Source #

@since base-4.7.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => Const m a -> a Source #

product :: Num a => Const m a -> a Source #

Foldable f => Foldable (Ap f) Source #

@since base-4.12.0.0

Instance details

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 #

sum :: Num a => Ap f a -> a Source #

product :: Num a => Ap f a -> a Source #

Foldable f => Foldable (Alt f) Source #

@since base-4.12.0.0

Instance details

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 #

sum :: Num a => Alt f a -> a Source #

product :: Num a => Alt f a -> a Source #

Foldable f => Foldable (Rec1 f) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => Rec1 f a -> a Source #

product :: Num a => Rec1 f a -> a Source #

Traversable (Const m :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Const m a -> f (Const m b) Source #

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) Source #

mapM :: Monad m0 => (a -> m0 b) -> Const m a -> m0 (Const m b) Source #

sequence :: Monad m0 => Const m (m0 a) -> m0 (Const m a) Source #

Traversable f => Traversable (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Ap f a -> f0 (Ap f b) Source #

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) Source #

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) Source #

sequence :: Monad m => Ap f (m a) -> m (Ap f a) Source #

Traversable f => Traversable (Alt f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alt f a -> f0 (Alt f b) Source #

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) Source #

mapM :: Monad m => (a -> m b) -> Alt f a -> m (Alt f b) Source #

sequence :: Monad m => Alt f (m a) -> m (Alt f a) Source #

Traversable f => Traversable (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) Source #

sequenceA :: Applicative f0 => Rec1 f (f0 a) -> f0 (Rec1 f a) Source #

mapM :: Monad m => (a -> m b) -> Rec1 f a -> m (Rec1 f b) Source #

sequence :: Monad m => Rec1 f (m a) -> m (Rec1 f a) Source #

(Alternative f, Alternative g) => Alternative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :*: g) a Source #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

some :: (f :*: g) a -> (f :*: g) [a] Source #

many :: (f :*: g) a -> (f :*: g) [a] Source #

(Applicative f, Applicative g) => Applicative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :*: g) a Source #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c Source #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a Source #

Monoid c => Applicative (K1 i c :: Type -> Type) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> K1 i c a Source #

(<*>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b Source #

liftA2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 Source #

(*>) :: K1 i c a -> K1 i c b -> K1 i c b Source #

(<*) :: K1 i c a -> K1 i c b -> K1 i c a Source #

(Functor f, Functor g) => Functor (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(<$) :: a -> (f :*: g) b -> (f :*: g) a Source #

(Functor f, Functor g) => Functor (f :+: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(<$) :: a -> (f :+: g) b -> (f :+: g) a Source #

Functor (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b Source #

(<$) :: a -> K1 i c b -> K1 i c a Source #

(Monad f, Monad g) => Monad (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b Source #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

return :: a -> (f :*: g) a Source #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: (f :*: g) a Source #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

(Applicative f, Monoid a) => Monoid (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mempty :: Ap f a Source #

mappend :: Ap f a -> Ap f a -> Ap f a Source #

mconcat :: [Ap f a] -> Ap f a Source #

Alternative f => Monoid (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Alt f a Source #

mappend :: Alt f a -> Alt f a -> Alt f a Source #

mconcat :: [Alt f a] -> Alt f a Source #

(Applicative f, Semigroup a) => Semigroup (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a Source #

sconcat :: NonEmpty (Ap f a) -> Ap f a Source #

stimes :: Integral b => b -> Ap f a -> Ap f a Source #

Alternative f => Semigroup (Alt f a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a Source #

sconcat :: NonEmpty (Alt f a) -> Alt f a Source #

stimes :: Integral b => b -> Alt f a -> Alt f a Source #

(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> (f :*: g) a) -> (f :*: g) a Source #

(Data (f a), Data a, Typeable f) => Data (Ap f a) Source #

@since base-4.12.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => (f :*: g) a -> a Source #

product :: Num a => (f :*: g) a -> a Source #

(Foldable f, Foldable g) => Foldable (f :+: g) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => (f :+: g) a -> a Source #

product :: Num a => (f :+: g) a -> a Source #

Foldable (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => K1 i c a -> a Source #

product :: Num a => K1 i c a -> a Source #

(Traversable f, Traversable g) => Traversable (f :*: g) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> K1 i c a -> f (K1 i c b) Source #

sequenceA :: Applicative f => K1 i c (f a) -> f (K1 i c a) Source #

mapM :: Monad m => (a -> m b) -> K1 i c a -> m (K1 i c b) Source #

sequence :: Monad m => K1 i c (m a) -> m (K1 i c a) Source #

(Applicative f, Bounded a) => Bounded (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

minBound :: Ap f a Source #

maxBound :: Ap f a Source #

(Applicative f, Num a) => Num (Ap f a) Source #

Note that even if the underlying Num and Applicative instances are lawful, for most Applicatives, this instance will not be lawful. If you use this instance with the list Applicative, the following customary laws will not hold:

Commutativity:

>>> Ap [10,20] + Ap [1,2]
Ap {getAp = [11,12,21,22]}
>>> Ap [1,2] + Ap [10,20]
Ap {getAp = [11,21,12,22]}

Additive inverse:

>>> Ap [] + negate (Ap [])
Ap {getAp = []}
>>> fromInteger 0 :: Ap [] Int
Ap {getAp = [0]}

Distributivity:

>>> Ap [1,2] * (3 + 4)
Ap {getAp = [7,14]}
>>> (Ap [1,2] * 3) + (Ap [1,2] * 4)
Ap {getAp = [7,11,10,14]}

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a Source #

(-) :: Ap f a -> Ap f a -> Ap f a Source #

(*) :: Ap f a -> Ap f a -> Ap f a Source #

negate :: Ap f a -> Ap f a Source #

abs :: Ap f a -> Ap f a Source #

signum :: Ap f a -> Ap f a Source #

fromInteger :: Integer -> Ap f a Source #

(Alternative f, Applicative g) => Alternative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :.: g) a Source #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

some :: (f :.: g) a -> (f :.: g) [a] Source #

many :: (f :.: g) a -> (f :.: g) [a] Source #

Alternative f => Alternative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: M1 i c f a Source #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

some :: M1 i c f a -> M1 i c f [a] Source #

many :: M1 i c f a -> M1 i c f [a] Source #

(Applicative f, Applicative g) => Applicative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :.: g) a Source #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source #

Applicative f => Applicative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> M1 i c f a Source #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b Source #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 Source #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a Source #

(Functor f, Functor g) => Functor (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

Functor f => Functor (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b Source #

(<$) :: a -> M1 i c f b -> M1 i c f a Source #

Monad f => Monad (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b Source #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

return :: a -> M1 i c f a Source #

MonadPlus f => MonadPlus (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: M1 i c f a Source #

mplus :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

MonadFix f => MonadFix (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> M1 i c f a) -> M1 i c f a Source #

(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => (f :.: g) a -> a Source #

product :: Num a => (f :.: g) a -> a Source #

Foldable f => Foldable (M1 i c f) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => M1 i c f a -> a Source #

product :: Num a => M1 i c f a -> a Source #

(Traversable f, Traversable g) => Traversable (f :.: g) Source #

@since base-4.9.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> M1 i c f a -> f0 (M1 i c f b) Source #

sequenceA :: Applicative f0 => M1 i c f (f0 a) -> f0 (M1 i c f a) Source #

mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) Source #

sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) Source #

(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

Defined in GHC.Internal.Generics

type Rep1 Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "GHC.Internal.Data.Functor.Identity" "ghc-internal" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 First Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 First = D1 ('MetaData "First" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))
type Rep1 Last Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))
type Rep1 Down Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Down = D1 ('MetaData "Down" "GHC.Internal.Data.Ord" "ghc-internal" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Dual Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Product Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Sum Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 ZipList Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

type Rep1 ZipList = D1 ('MetaData "ZipList" "GHC.Internal.Functor.ZipList" "ghc-internal" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
type Rep1 Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Maybe Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 [] Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Either a :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Kleisli m a :: Type -> Type) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "GHC.Internal.Control.Arrow" "ghc-internal" 'True) (C1 ('MetaCons "Kleisli" 'PrefixI 'True) (S1 ('MetaSel ('Just "runKleisli") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ((FUN 'Many a :: Type -> Type) :.: Rec1 m)))
type Rep1 ((,,) a b :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,) a b c :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,) a b c d :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Comp1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComp1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))
type Rep1 ((,,,,,) a b c d e :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

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

Instance details

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

Instance details

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 WordBox (a :: TYPE 'WordRep) Source #

Constructors

MkWordBox a 

data IntBox (a :: TYPE 'IntRep) Source #

Constructors

MkIntBox a 

data FloatBox (a :: TYPE 'FloatRep) Source #

Constructors

MkFloatBox a 

data DoubleBox (a :: TYPE 'DoubleRep) Source #

Constructors

MkDoubleBox a 

data DictBox a Source #

Data type Dict provides a simple way to wrap up a (lifted) constraint as a type

Constructors

a => MkDictBox 

data Bool Source #

Constructors

False 
True 

Instances

Instances details
Bits Bool Source #

Interpret Bool as 1-bit bit-field

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Bits

FiniteBits Bool Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Bits

Data Bool Source #

@since base-4.0.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Enum

Enum Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Storable Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Generic Bool Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep Bool

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

Ix Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Read Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Show Bool Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

(==) :: Bool -> Bool -> Bool Source #

(/=) :: Bool -> Bool -> Bool Source #

Ord Bool 
Instance details

Defined in GHC.Classes

type Rep Bool Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))

data Char Source #

The character type Char represents Unicode codespace and its elements are code points as in definitions D9 and D10 of the Unicode Standard.

Character literals in Haskell are single-quoted: 'Q', 'Я' or 'Ω'. To represent a single quote itself use '\'', and to represent a backslash use '\\'. The full grammar can be found in the section 2.6 of the Haskell 2010 Language Report.

To specify a character by its code point one can use decimal, hexadecimal or octal notation: '\65', '\x41' and '\o101' are all alternative forms of 'A'. The largest code point is '\x10ffff'.

There is a special escape syntax for ASCII control characters:

EscapeAlternativesMeaning
'\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

Data.Char provides utilities to work with Char.

Constructors

C# Char# 

Instances

Instances details
Data Char Source #

@since base-4.0.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Enum

Enum Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Storable Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Ix Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Read Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Show Char Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Char 
Instance details

Defined in GHC.Classes

Methods

(==) :: Char -> Char -> Bool Source #

(/=) :: Char -> Char -> Bool Source #

Ord Char 
Instance details

Defined in GHC.Classes

TestCoercion SChar Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testCoercion :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (Coercion a b) Source #

TestEquality SChar Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testEquality :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (a :~: b) Source #

Generic1 (URec Char :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Char :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Char a -> Rep1 (URec Char :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Char :: k -> Type) a -> URec Char a Source #

Foldable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UChar a -> a Source #

product :: Num a => UChar a -> a Source #

Traversable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

Functor (URec Char :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Generic (URec Char p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Char p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

Methods

from :: URec Char p -> Rep (URec Char p) x Source #

to :: Rep (URec Char p) x -> URec Char p Source #

Show (URec Char p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Char p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Char p -> URec Char p -> Bool Source #

(/=) :: URec Char p -> URec Char p -> Bool Source #

Ord (URec Char p) Source #

@since base-4.9.0.0

Instance details

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 #

max :: URec Char p -> URec Char p -> URec Char p Source #

min :: URec Char p -> URec Char p -> URec Char p Source #

data URec Char (p :: k) Source #

Used for marking occurrences of Char#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Char (p :: k) = UChar {}
type Compare (a :: Char) (b :: Char) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Char) (b :: Char) = CmpChar a b
type Rep1 (URec Char :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))
type Rep (URec Char p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

data Double Source #

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.

Constructors

D# Double# 

Instances

Instances details
Data Double Source #

@since base-4.0.0.0

Instance details

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

fromEnum just truncates its argument, beware of all sorts of overflows.

List generators have extremely peculiar behavior, mandated by Haskell Report 2010:

>>> [0..1.5]
[0.0,1.0,2.0]
Instance details

Defined in GHC.Internal.Float

Floating Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

RealFloat Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Storable Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

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:

>>> (0.1 + 0.1) + 0.4 == 0.1 + (0.1 + 0.4)
False
>>> (0.1 + 0.2) * 0.3 == 0.1 * 0.3 + 0.2 * 0.3
False
>>> (0.1 * 0.1) * 0.3 == 0.1 * (0.1 * 0.3)
False
Instance details

Defined in GHC.Internal.Float

Read Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Fractional Double Source #

@since base-2.01

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero.

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
>>> map (/ 0) [-1, 0, 1]
[-Infinity,NaN,Infinity]
>>> map (* 0) $ map (/ 0) [-1, 0, 1]
[NaN,NaN,NaN]
Instance details

Defined in GHC.Internal.Float

Real Double Source #

@since base-2.01

Beware that toRational generates garbage for non-finite arguments:

>>> toRational (1/0)
179769313 (and 300 more digits...) % 1
>>> toRational (0/0)
269653970 (and 300 more digits...) % 1
Instance details

Defined in GHC.Internal.Float

RealFrac Double Source #

@since base-2.01

Beware that results for non-finite arguments are garbage:

>>> [ f x | f <- [round, floor, ceiling], x <- [-1/0, 0/0, 1/0] ] :: [Int]
[0,0,0,0,0,0,0,0,0]
>>> map properFraction [-1/0, 0/0, 1/0] :: [(Int, Double)]
[(0,0.0),(0,0.0),(0,0.0)]

and get even more non-sensical if you ask for Integer instead of Int.

Instance details

Defined in GHC.Internal.Float

Show Double Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Float

Eq Double

Note that due to the presence of NaN, Double's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Ord Double

IEEE 754 Double-precision type includes not only numbers, but also positive and negative infinities and a special element called NaN (which can be quiet or signal).

IEEE 754-2008, section 5.11 requires that if at least one of arguments of <=, <, >, >= is NaN then the result of the comparison is False, and instance Ord Double complies with this requirement. This violates the reflexivity: both NaN <= NaN and NaN >= NaN are False.

IEEE 754-2008, section 5.10 defines totalOrder predicate. Unfortunately, compare on Doubles violates the IEEE standard and does not define a total order. More specifically, both compare NaN x and compare x NaN always return GT.

Thus, users must be extremely cautious when using instance Ord Double. For instance, one should avoid ordered containers with keys represented by Double, because data loss and corruption may happen. An IEEE-compliant compare is available in fp-ieee package as TotallyOrdered newtype.

Moving further, the behaviour of min and max with regards to NaN is also non-compliant. IEEE 754-2008, section 5.3.1 defines that quiet NaN should be treated as a missing data by minNum and maxNum functions, for example, minNum(NaN, 1) = minNum(1, NaN) = 1. Some languages such as Java deviate from the standard implementing minNum(NaN, 1) = minNum(1, NaN) = NaN. However, min / max in base are even worse: min NaN 1 is 1, but min 1 NaN is NaN.

IEEE 754-2008 compliant min / max can be found in ieee754 package under minNum / maxNum names. Implementations compliant with minimumNumber / maximumNumber from a newer IEEE 754-2019, section 9.6 are available from fp-ieee package.

Instance details

Defined in GHC.Classes

Generic1 (URec Double :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec Double :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))

Methods

from1 :: forall (a :: k). URec Double a -> Rep1 (URec Double :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec Double :: k -> Type) a -> URec Double a Source #

Foldable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UDouble a -> a Source #

product :: Num a => UDouble a -> a Source #

Traversable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Generic (URec Double p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Double p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

Methods

from :: URec Double p -> Rep (URec Double p) x Source #

to :: Rep (URec Double p) x -> URec Double p Source #

Show (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec Double p -> URec Double p -> Bool Source #

(/=) :: URec Double p -> URec Double p -> Bool Source #

Ord (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Double (p :: k) Source #

Used for marking occurrences of Double#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec Double (p :: k) = UDouble {}
type Rep1 (URec Double :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type)))
type Rep (URec Double p) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

data List a Source #

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

Expand

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

Expand
>>> ['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

Instances details
Alternative [] Source #

Combines lists by concatenation, starting from the empty list.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

empty :: [a] Source #

(<|>) :: [a] -> [a] -> [a] Source #

some :: [a] -> [[a]] Source #

many :: [a] -> [[a]] Source #

Applicative [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> [a] Source #

(<*>) :: [a -> b] -> [a] -> [b] Source #

liftA2 :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

(*>) :: [a] -> [b] -> [b] Source #

(<*) :: [a] -> [b] -> [a] Source #

Functor [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> [a] -> [b] Source #

(<$) :: a -> [b] -> [a] Source #

Monad [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: [a] -> (a -> [b]) -> [b] Source #

(>>) :: [a] -> [b] -> [b] Source #

return :: a -> [a] Source #

MonadPlus [] Source #

Combines lists by concatenation, starting from the empty list.

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: [a] Source #

mplus :: [a] -> [a] -> [a] Source #

MonadFail [] Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fail

Methods

fail :: String -> [a] Source #

MonadFix [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> [a]) -> [a] Source #

Foldable [] Source #

@since base-2.01

Instance details

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 #

toList :: [a] -> [a] Source #

null :: [a] -> Bool Source #

length :: [a] -> Int Source #

elem :: Eq a => a -> [a] -> Bool Source #

maximum :: Ord a => [a] -> a Source #

minimum :: Ord a => [a] -> a Source #

sum :: Num a => [a] -> a Source #

product :: Num a => [a] -> a Source #

Traversable [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> [a] -> f [b] Source #

sequenceA :: Applicative f => [f a] -> f [a] Source #

mapM :: Monad m => (a -> m b) -> [a] -> m [b] Source #

sequence :: Monad m => [m a] -> m [a] Source #

Generic1 [] Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 []

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: [a] -> Rep1 [] a Source #

to1 :: Rep1 [] a -> [a] Source #

Monoid [a] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: [a] Source #

mappend :: [a] -> [a] -> [a] Source #

mconcat :: [[a]] -> [a] Source #

Semigroup [a] Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: [a] -> [a] -> [a] Source #

sconcat :: NonEmpty [a] -> [a] Source #

stimes :: Integral b => b -> [a] -> [a] Source #

Data a => Data [a] Source #

For historical reasons, the constructor name used for (:) is "(:)". In a derived instance, it would be ":".

@since base-4.0.0.0

Instance details

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 #

(a ~ Char) context was introduced in 4.9.0.0

@since base-2.01

Instance details

Defined in GHC.Internal.Data.String

Methods

fromString :: String -> [a] Source #

Generic [a] Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep [a]

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from :: [a] -> Rep [a] x Source #

to :: Rep [a] x -> [a] Source #

IsList [a] Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.IsList

Associated Types

type Item [a] 
Instance details

Defined in GHC.Internal.IsList

type Item [a] = a

Methods

fromList :: [Item [a]] -> [a] Source #

fromListN :: Int -> [Item [a]] -> [a] Source #

toList :: [a] -> [Item [a]] Source #

Read a => Read [a] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Show a => Show [a] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Methods

showsPrec :: Int -> [a] -> ShowS Source #

show :: [a] -> String Source #

showList :: [[a]] -> ShowS Source #

Eq a => Eq [a] 
Instance details

Defined in GHC.Classes

Methods

(==) :: [a] -> [a] -> Bool Source #

(/=) :: [a] -> [a] -> Bool Source #

Ord a => Ord [a] 
Instance details

Defined in GHC.Classes

Methods

compare :: [a] -> [a] -> Ordering Source #

(<) :: [a] -> [a] -> Bool Source #

(<=) :: [a] -> [a] -> Bool Source #

(>) :: [a] -> [a] -> Bool Source #

(>=) :: [a] -> [a] -> Bool Source #

max :: [a] -> [a] -> [a] Source #

min :: [a] -> [a] -> [a] Source #

type Rep1 [] Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep [a] Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Item [a] Source # 
Instance details

Defined in GHC.Internal.IsList

type Item [a] = a

data Ordering Source #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Monoid Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Semigroup Ordering Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Data Ordering Source #

@since base-4.0.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Enum

Enum Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Generic Ordering Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep Ordering

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))
Ix Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Read Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Show Ordering Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Ordering 
Instance details

Defined in GHC.Classes

Ord Ordering 
Instance details

Defined in GHC.Classes

type Rep Ordering Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

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

data Symbol Source #

(Kind) This is the kind of type-level symbols.

Instances

Instances details
TestCoercion SSymbol Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testCoercion :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (Coercion a b) Source #

TestEquality SSymbol Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testEquality :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (a :~: b) Source #

type Compare (a :: Symbol) (b :: Symbol) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b

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

Instances details
Show RuntimeRep Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

data Levity Source #

Whether a boxed type is lifted or unlifted.

Constructors

Lifted 
Unlifted 

Instances

Instances details
Bounded Levity Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Enum

Enum Levity Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Enum

Show Levity Source #

@since base-4.15.0.0

Instance details

Defined in GHC.Internal.Show

data VecCount Source #

Length of a SIMD vector type

Constructors

Vec2 
Vec4 
Vec8 
Vec16 
Vec32 
Vec64 

Instances

Instances details
Bounded VecCount Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Enum

Enum VecCount Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Enum

Show VecCount Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

data VecElem Source #

Element of a SIMD vector type

Instances

Instances details
Bounded VecElem Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Enum

Enum VecElem Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Enum

Show VecElem Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

data Multiplicity Source #

Constructors

One 
Many 

data SPEC 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

Constructors

SPEC 
SPEC2 

data TypeLitSort Source #

Instances

Instances details
Show TypeLitSort Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Show

data KindRep Source #

The representation produced by GHC for conjuring up the kind of a TypeRep.

Instances

Instances details
Show KindRep Source # 
Instance details

Defined in GHC.Internal.Show

data TyCon Source #

Constructors

TyCon 

Fields

  • Word64#

    Fingerprint (high)

  • Word64#

    Fingerprint (low)

  • Module

    Module in which this is defined

  • TrName

    Type constructor name

  • Int#

    How many kind variables do we accept?

  • KindRep

    A representation of the type's kind

Instances

Instances details
Show TyCon Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq TyCon 
Instance details

Defined in GHC.Classes

Methods

(==) :: TyCon -> TyCon -> Bool Source #

(/=) :: TyCon -> TyCon -> Bool Source #

Ord TyCon 
Instance details

Defined in GHC.Classes

data TrName Source #

Constructors

TrNameS Addr#

Static

TrNameD [Char]

Dynamic

Instances

Instances details
Show TrName Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Eq TrName 
Instance details

Defined in GHC.Classes

data Module Source #

Constructors

Module 

Fields

Instances

Instances details
Show Module Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Show

Eq Module 
Instance details

Defined in GHC.Classes

newtype IO a Source #

A value of type IO a is a computation which, when performed, does some I/O before returning a value of type a.

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.

Constructors

IO (State# RealWorld -> (# State# RealWorld, a #)) 

Instances

Instances details
Alternative IO Source #

Takes the first non-throwing IO action's result. empty throws an exception.

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

empty :: IO a Source #

(<|>) :: IO a -> IO a -> IO a Source #

some :: IO a -> IO [a] Source #

many :: IO a -> IO [a] Source #

Applicative IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> IO a Source #

(<*>) :: IO (a -> b) -> IO a -> IO b Source #

liftA2 :: (a -> b -> c) -> IO a -> IO b -> IO c Source #

(*>) :: IO a -> IO b -> IO b Source #

(<*) :: IO a -> IO b -> IO a Source #

Functor IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> IO a -> IO b Source #

(<$) :: a -> IO b -> IO a Source #

Monad IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b Source #

(>>) :: IO a -> IO b -> IO b Source #

return :: a -> IO a Source #

MonadPlus IO Source #

Takes the first non-throwing IO action's result. mzero throws an exception.

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: IO a Source #

mplus :: IO a -> IO a -> IO a Source #

MonadFail IO Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fail

Methods

fail :: String -> IO a Source #

MonadFix IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> IO a) -> IO a Source #

GHCiSandboxIO IO Source #

@since base-4.4.0.0

Instance details

Defined in GHC.Internal.GHCi

Methods

ghciStepIO :: IO a -> IO a Source #

Monoid a => Monoid (IO a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: IO a Source #

mappend :: IO a -> IO a -> IO a Source #

mconcat :: [IO a] -> IO a Source #

Semigroup a => Semigroup (IO a) Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: IO a -> IO a -> IO a Source #

sconcat :: NonEmpty (IO a) -> IO a Source #

stimes :: Integral b => b -> IO a -> IO a Source #

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 LiftedRep = 'BoxedRep 'Lifted Source #

The runtime representation of lifted 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 Type = TYPE LiftedRep Source #

The kind of types with lifted values. For example Int :: Type.

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 KindBndr = Int Source #

A de Bruijn index for a binder within a KindRep.

type Void# = (# #) Source #

type family MultMul (a :: Multiplicity) (b :: Multiplicity) :: Multiplicity where ... Source #

Equations

MultMul 'One x = x 
MultMul x 'One = x 
MultMul 'Many x = 'Many 
MultMul x 'Many = 'Many 

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 Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #

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 BCO Source #

Primitive bytecode type.

data Weak# (a :: TYPE ('BoxedRep l)) :: UnliftedType Source #

data MutableByteArray# a :: UnliftedType Source #

A mutable ByteAray#. It can be created in three ways:

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 MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #

A shared mutable variable (not the same as a MutVar#!). (Note: in a non-concurrent implementation, (MVar# a) can be represented by (MutVar# (Maybe a)).)

data 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 TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #

data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType Source #

A MutVar# behaves like a single-element mutable array.

data RealWorld Source #

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

data StablePtr# (a :: TYPE ('BoxedRep l)) :: TYPE 'AddrRep Source #

data State# a :: ZeroBitType Source #

State# is the primitive, unlifted type of states. It has one type parameter, thus State# RealWorld, or State# s, where s is a type variable. The only purpose of the type parameter is to keep different state threads separate. It is represented by nothing at all.

data Proxy# (a :: k) :: ZeroBitType Source #

The type constructor Proxy# is used to bear witness to some type variable. It's used when you want to pass around proxy values for doing things like modelling type applications. A Proxy# is not only unboxed, it also has a polymorphic kind, and has no runtime representation, being totally free.

data 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 FUN Source #

The builtin function type, written in infix form as a % m -> b. Values of this type are functions taking inputs of type a and producing outputs of type b. The multiplicity of the input is m.

Note that FUN m a b permits representation polymorphism in both a and b, so that types like Int# -> Int# can still be well-kinded.

Instances

Instances details
Category (->) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: a -> a Source #

(.) :: (b -> c) -> (a -> b) -> a -> c Source #

Monoid b => Monoid (a -> b) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: a -> b Source #

mappend :: (a -> b) -> (a -> b) -> a -> b Source #

mconcat :: [a -> b] -> a -> b Source #

Semigroup b => Semigroup (a -> b) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b Source #

sconcat :: NonEmpty (a -> b) -> a -> b Source #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b Source #

Arrow (->) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

arr :: (b -> c) -> b -> c Source #

first :: (b -> c) -> (b, d) -> (c, d) Source #

second :: (b -> c) -> (d, b) -> (d, c) Source #

(***) :: (b -> c) -> (b' -> c') -> (b, b') -> (c, c') Source #

(&&&) :: (b -> c) -> (b -> c') -> b -> (c, c') Source #

ArrowApply (->) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

app :: (b -> c, b) -> c Source #

ArrowChoice (->) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

left :: (b -> c) -> Either b d -> Either c d Source #

right :: (b -> c) -> Either d b -> Either d c Source #

(+++) :: (b -> c) -> (b' -> c') -> Either b b' -> Either c c' Source #

(|||) :: (b -> d) -> (c -> d) -> Either b c -> d Source #

ArrowLoop (->) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

loop :: ((b, d) -> (c, d)) -> b -> c Source #

Applicative ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> r -> a Source #

(<*>) :: (r -> (a -> b)) -> (r -> a) -> r -> b Source #

liftA2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> c Source #

(*>) :: (r -> a) -> (r -> b) -> r -> b Source #

(<*) :: (r -> a) -> (r -> b) -> r -> a Source #

Functor ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> (r -> a) -> r -> b Source #

(<$) :: a -> (r -> b) -> r -> a Source #

Monad ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b Source #

(>>) :: (r -> a) -> (r -> b) -> r -> b Source #

return :: a -> r -> a Source #

MonadFix ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> r -> a) -> r -> a Source #

data TYPE (a :: RuntimeRep) Source #

Instances

Instances details
Generic1 NonEmpty Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 NonEmpty

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Generic1 Identity Source # 
Instance details

Defined in GHC.Internal.Data.Functor.Identity

Associated Types

type Rep1 Identity

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "GHC.Internal.Data.Functor.Identity" "ghc-internal" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Generic1 First Source # 
Instance details

Defined in GHC.Internal.Data.Monoid

Associated Types

type Rep1 First

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 First = D1 ('MetaData "First" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))

Methods

from1 :: First a -> Rep1 First a Source #

to1 :: Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in GHC.Internal.Data.Monoid

Associated Types

type Rep1 Last

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))

Methods

from1 :: Last a -> Rep1 Last a Source #

to1 :: Rep1 Last a -> Last a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Down

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Down = D1 ('MetaData "Down" "GHC.Internal.Data.Ord" "ghc-internal" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Down a -> Rep1 Down a Source #

to1 :: Rep1 Down a -> Down a Source #

Generic1 Dual Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Dual

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Dual a -> Rep1 Dual a Source #

to1 :: Rep1 Dual a -> Dual a Source #

Generic1 Product Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Product

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
Generic1 Sum Source # 
Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Associated Types

type Rep1 Sum

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Sum a -> Rep1 Sum a Source #

to1 :: Rep1 Sum a -> Sum a Source #

Generic1 ZipList Source # 
Instance details

Defined in GHC.Internal.Functor.ZipList

Associated Types

type Rep1 ZipList

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

type Rep1 ZipList = D1 ('MetaData "ZipList" "GHC.Internal.Functor.ZipList" "ghc-internal" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
Generic1 Par1 Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Par1

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Par1 a -> Rep1 Par1 a Source #

to1 :: Rep1 Par1 a -> Par1 a Source #

Generic1 Maybe Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Maybe

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Maybe a -> Rep1 Maybe a Source #

to1 :: Rep1 Maybe a -> Maybe a Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Solo

@since base-4.15

Instance details

Defined in GHC.Internal.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Solo a -> Rep1 Solo a Source #

to1 :: Rep1 Solo a -> Solo a Source #

Generic1 [] Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 []

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: [a] -> Rep1 [] a Source #

to1 :: Rep1 [] a -> [a] Source #

Monad m => Category (Kleisli m :: Type -> Type -> Type) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

id :: Kleisli m a a Source #

(.) :: Kleisli m b c -> Kleisli m a b -> Kleisli m a c Source #

Generic1 (Either a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Either a :: Type -> Type)

@since base-4.6.0.0

Instance details

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))

Methods

from1 :: Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: Rep1 (Either a) a0 -> Either a a0 Source #

Generic1 ((,) a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,) a :: Type -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, a0) -> Rep1 ((,) a) a0 Source #

to1 :: Rep1 ((,) a) a0 -> (a, a0) Source #

Category (->) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: a -> a Source #

(.) :: (b -> c) -> (a -> b) -> a -> c Source #

Generic1 (Kleisli m a :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Control.Arrow

Associated Types

type Rep1 (Kleisli m a :: Type -> Type)

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "GHC.Internal.Control.Arrow" "ghc-internal" 'True) (C1 ('MetaCons "Kleisli" 'PrefixI 'True) (S1 ('MetaSel ('Just "runKleisli") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ((FUN 'Many a :: Type -> Type) :.: Rec1 m)))

Methods

from1 :: Kleisli m a a0 -> Rep1 (Kleisli m a) a0 Source #

to1 :: Rep1 (Kleisli m a) a0 -> Kleisli m a a0 Source #

Generic1 ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,) a b :: Type -> Type)

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, a0) -> Rep1 ((,,) a b) a0 Source #

to1 :: Rep1 ((,,) a b) a0 -> (a, b, a0) Source #

Generic1 ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, a0) -> Rep1 ((,,,) a b c) a0 Source #

to1 :: Rep1 ((,,,) a b c) a0 -> (a, b, c, a0) Source #

Generic1 ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, a0) -> Rep1 ((,,,,) a b c d) a0 Source #

to1 :: Rep1 ((,,,,) a b c d) a0 -> (a, b, c, d, a0) Source #

Functor f => Generic1 (f :.: g :: k -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (f :.: g :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Comp1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComp1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))

Methods

from1 :: forall (a :: k). (f :.: g) a -> Rep1 (f :.: g) a Source #

to1 :: forall (a :: k). Rep1 (f :.: g) a -> (f :.: g) a Source #

Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, a0) -> Rep1 ((,,,,,) a b c d e) a0 Source #

to1 :: Rep1 ((,,,,,) a b c d e) a0 -> (a, b, c, d, e, a0) Source #

Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, f, a0) -> Rep1 ((,,,,,,) a b c d e f) a0 Source #

to1 :: Rep1 ((,,,,,,) a b c d e f) a0 -> (a, b, c, d, e, f, a0) Source #

Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: (a, b, c, d, e, f, g, a0) -> Rep1 ((,,,,,,,) a b c d e f g) a0 Source #

to1 :: Rep1 ((,,,,,,,) a b c d e f g) a0 -> (a, b, c, d, e, f, g, a0) Source #

Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # 
Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type)

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type)

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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 # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type)

@since base-4.16.0.0

Instance details

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)))))

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

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

empty :: Proxy a Source #

(<|>) :: Proxy a -> Proxy a -> Proxy a Source #

some :: Proxy a -> Proxy [a] Source #

many :: Proxy a -> Proxy [a] Source #

Alternative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: U1 a Source #

(<|>) :: U1 a -> U1 a -> U1 a Source #

some :: U1 a -> U1 [a] Source #

many :: U1 a -> U1 [a] Source #

Applicative (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a Source #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b Source #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

(*>) :: Proxy a -> Proxy b -> Proxy b Source #

(<*) :: Proxy a -> Proxy b -> Proxy a Source #

Applicative (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> U1 a Source #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b Source #

liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c Source #

(*>) :: U1 a -> U1 b -> U1 b Source #

(<*) :: U1 a -> U1 b -> U1 a Source #

Functor (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b Source #

(<$) :: a -> Proxy b -> Proxy a Source #

Functor (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b Source #

(<$) :: a -> U1 b -> U1 a Source #

Functor (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> V1 a -> V1 b Source #

(<$) :: a -> V1 b -> V1 a Source #

Monad (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source #

(>>) :: Proxy a -> Proxy b -> Proxy b Source #

return :: a -> Proxy a Source #

Monad (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: U1 a -> (a -> U1 b) -> U1 b Source #

(>>) :: U1 a -> U1 b -> U1 b Source #

return :: a -> U1 a Source #

MonadPlus (Proxy :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a Source #

mplus :: Proxy a -> Proxy a -> Proxy a Source #

MonadPlus (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: U1 a Source #

mplus :: U1 a -> U1 a -> U1 a Source #

Foldable (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

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 #

sum :: Num a => Proxy a -> a Source #

product :: Num a => Proxy a -> a Source #

Foldable (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

null :: U1 a -> Bool 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 #

sum :: Num a => U1 a -> a Source #

product :: Num a => U1 a -> a Source #

Foldable (UAddr :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Foldable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UChar a -> a Source #

product :: Num a => UChar a -> a Source #

Foldable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UDouble a -> a Source #

product :: Num a => UDouble a -> a Source #

Foldable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UFloat a -> a Source #

product :: Num a => UFloat a -> a Source #

Foldable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UInt a -> a Source #

product :: Num a => UInt a -> a Source #

Foldable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => UWord a -> a Source #

product :: Num a => UWord a -> a Source #

Foldable (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

null :: V1 a -> Bool 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 #

sum :: Num a => V1 a -> a Source #

product :: Num a => V1 a -> a Source #

Traversable (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) Source #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) Source #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) Source #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) Source #

Traversable (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> U1 a -> f (U1 b) Source #

sequenceA :: Applicative f => U1 (f a) -> f (U1 a) Source #

mapM :: Monad m => (a -> m b) -> U1 a -> m (U1 b) Source #

sequence :: Monad m => U1 (m a) -> m (U1 a) Source #

Traversable (UAddr :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Traversable (UChar :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

Traversable (UDouble :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Traversable (UFloat :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Traversable (UInt :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source #

sequence :: Monad m => UInt (m a) -> m (UInt a) Source #

Traversable (UWord :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) Source #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) Source #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) Source #

sequence :: Monad m => UWord (m a) -> m (UWord a) Source #

Traversable (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> V1 a -> f (V1 b) Source #

sequenceA :: Applicative f => V1 (f a) -> f (V1 a) Source #

mapM :: Monad m => (a -> m b) -> V1 a -> m (V1 b) Source #

sequence :: Monad m => V1 (m a) -> m (V1 a) Source #

Alternative f => Alternative (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

empty :: Ap f a Source #

(<|>) :: Ap f a -> Ap f a -> Ap f a Source #

some :: Ap f a -> Ap f [a] Source #

many :: Ap f a -> Ap f [a] Source #

Alternative f => Alternative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

empty :: Alt f a Source #

(<|>) :: Alt f a -> Alt f a -> Alt f a Source #

some :: Alt f a -> Alt f [a] Source #

many :: Alt f a -> Alt f [a] Source #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Alternative f => Alternative (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: Rec1 f a Source #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

some :: Rec1 f a -> Rec1 f [a] Source #

many :: Rec1 f a -> Rec1 f [a] Source #

Monoid m => Applicative (Const m :: Type -> Type) Source #

@since base-2.0.1

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

pure :: a -> Const m a Source #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b Source #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c Source #

(*>) :: Const m a -> Const m b -> Const m b Source #

(<*) :: Const m a -> Const m b -> Const m a Source #

Applicative f => Applicative (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

pure :: a -> Ap f a Source #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b Source #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c Source #

(*>) :: Ap f a -> Ap f b -> Ap f b Source #

(<*) :: Ap f a -> Ap f b -> Ap f a Source #

Applicative f => Applicative (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

pure :: a -> Alt f a Source #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b Source #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source #

(*>) :: Alt f a -> Alt f b -> Alt f b Source #

(<*) :: Alt f a -> Alt f b -> Alt f a Source #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> Rec1 f a Source #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b Source #

liftA2 :: (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c Source #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a Source #

Functor (Const m :: Type -> Type) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source #

(<$) :: a -> Const m b -> Const m a Source #

Functor f => Functor (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b Source #

(<$) :: a -> Ap f b -> Ap f a Source #

Functor f => Functor (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source #

(<$) :: a -> Alt f b -> Alt f a Source #

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source #

@since base-4.17.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> Rec1 f a -> Rec1 f b Source #

(<$) :: a -> Rec1 f b -> Rec1 f a Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Functor (URec Char :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Functor (URec Int :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Functor (URec Word :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Monad f => Monad (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b Source #

(>>) :: Ap f a -> Ap f b -> Ap f b Source #

return :: a -> Ap f a Source #

Monad f => Monad (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b Source #

(>>) :: Alt f a -> Alt f b -> Alt f b Source #

return :: a -> Alt f a Source #

Monad f => Monad (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: Rec1 f a -> (a -> Rec1 f b) -> Rec1 f b Source #

(>>) :: Rec1 f a -> Rec1 f b -> Rec1 f b Source #

return :: a -> Rec1 f a Source #

MonadPlus f => MonadPlus (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mzero :: Ap f a Source #

mplus :: Ap f a -> Ap f a -> Ap f a Source #

MonadPlus f => MonadPlus (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mzero :: Alt f a Source #

mplus :: Alt f a -> Alt f a -> Alt f a Source #

MonadPlus f => MonadPlus (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: Rec1 f a Source #

mplus :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

MonadFail f => MonadFail (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

fail :: String -> Ap f a Source #

MonadFix f => MonadFix (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Ap f a) -> Ap f a Source #

MonadFix f => MonadFix (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Alt f a) -> Alt f a Source #

MonadFix f => MonadFix (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Rec1 f a) -> Rec1 f a Source #

Data t => Data (Proxy t) Source #

@since base-4.7.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => Const m a -> a Source #

product :: Num a => Const m a -> a Source #

Foldable f => Foldable (Ap f) Source #

@since base-4.12.0.0

Instance details

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 #

sum :: Num a => Ap f a -> a Source #

product :: Num a => Ap f a -> a Source #

Foldable f => Foldable (Alt f) Source #

@since base-4.12.0.0

Instance details

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 #

sum :: Num a => Alt f a -> a Source #

product :: Num a => Alt f a -> a Source #

Foldable f => Foldable (Rec1 f) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => Rec1 f a -> a Source #

product :: Num a => Rec1 f a -> a Source #

Traversable (Const m :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Const m a -> f (Const m b) Source #

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) Source #

mapM :: Monad m0 => (a -> m0 b) -> Const m a -> m0 (Const m b) Source #

sequence :: Monad m0 => Const m (m0 a) -> m0 (Const m a) Source #

Traversable f => Traversable (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Ap f a -> f0 (Ap f b) Source #

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) Source #

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) Source #

sequence :: Monad m => Ap f (m a) -> m (Ap f a) Source #

Traversable f => Traversable (Alt f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alt f a -> f0 (Alt f b) Source #

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) Source #

mapM :: Monad m => (a -> m b) -> Alt f a -> m (Alt f b) Source #

sequence :: Monad m => Alt f (m a) -> m (Alt f a) Source #

Traversable f => Traversable (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) Source #

sequenceA :: Applicative f0 => Rec1 f (f0 a) -> f0 (Rec1 f a) Source #

mapM :: Monad m => (a -> m b) -> Rec1 f a -> m (Rec1 f b) Source #

sequence :: Monad m => Rec1 f (m a) -> m (Rec1 f a) Source #

(Alternative f, Alternative g) => Alternative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :*: g) a Source #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

some :: (f :*: g) a -> (f :*: g) [a] Source #

many :: (f :*: g) a -> (f :*: g) [a] Source #

(Applicative f, Applicative g) => Applicative (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :*: g) a Source #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c Source #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a Source #

Monoid c => Applicative (K1 i c :: Type -> Type) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> K1 i c a Source #

(<*>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b Source #

liftA2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 Source #

(*>) :: K1 i c a -> K1 i c b -> K1 i c b Source #

(<*) :: K1 i c a -> K1 i c b -> K1 i c a Source #

(Functor f, Functor g) => Functor (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(<$) :: a -> (f :*: g) b -> (f :*: g) a Source #

(Functor f, Functor g) => Functor (f :+: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(<$) :: a -> (f :+: g) b -> (f :+: g) a Source #

Functor (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b Source #

(<$) :: a -> K1 i c b -> K1 i c a Source #

(Monad f, Monad g) => Monad (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b Source #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

return :: a -> (f :*: g) a Source #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: (f :*: g) a Source #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

(Applicative f, Monoid a) => Monoid (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

mempty :: Ap f a Source #

mappend :: Ap f a -> Ap f a -> Ap f a Source #

mconcat :: [Ap f a] -> Ap f a Source #

Alternative f => Monoid (Alt f a) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

mempty :: Alt f a Source #

mappend :: Alt f a -> Alt f a -> Alt f a Source #

mconcat :: [Alt f a] -> Alt f a Source #

(Applicative f, Semigroup a) => Semigroup (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a Source #

sconcat :: NonEmpty (Ap f a) -> Ap f a Source #

stimes :: Integral b => b -> Ap f a -> Ap f a Source #

Alternative f => Semigroup (Alt f a) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a Source #

sconcat :: NonEmpty (Alt f a) -> Alt f a Source #

stimes :: Integral b => b -> Alt f a -> Alt f a Source #

(MonadFix f, MonadFix g) => MonadFix (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> (f :*: g) a) -> (f :*: g) a Source #

(Data (f a), Data a, Typeable f) => Data (Ap f a) Source #

@since base-4.12.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => (f :*: g) a -> a Source #

product :: Num a => (f :*: g) a -> a Source #

(Foldable f, Foldable g) => Foldable (f :+: g) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => (f :+: g) a -> a Source #

product :: Num a => (f :+: g) a -> a Source #

Foldable (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => K1 i c a -> a Source #

product :: Num a => K1 i c a -> a Source #

(Traversable f, Traversable g) => Traversable (f :*: g) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> K1 i c a -> f (K1 i c b) Source #

sequenceA :: Applicative f => K1 i c (f a) -> f (K1 i c a) Source #

mapM :: Monad m => (a -> m b) -> K1 i c a -> m (K1 i c b) Source #

sequence :: Monad m => K1 i c (m a) -> m (K1 i c a) Source #

(Applicative f, Bounded a) => Bounded (Ap f a) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

minBound :: Ap f a Source #

maxBound :: Ap f a Source #

(Applicative f, Num a) => Num (Ap f a) Source #

Note that even if the underlying Num and Applicative instances are lawful, for most Applicatives, this instance will not be lawful. If you use this instance with the list Applicative, the following customary laws will not hold:

Commutativity:

>>> Ap [10,20] + Ap [1,2]
Ap {getAp = [11,12,21,22]}
>>> Ap [1,2] + Ap [10,20]
Ap {getAp = [11,21,12,22]}

Additive inverse:

>>> Ap [] + negate (Ap [])
Ap {getAp = []}
>>> fromInteger 0 :: Ap [] Int
Ap {getAp = [0]}

Distributivity:

>>> Ap [1,2] * (3 + 4)
Ap {getAp = [7,14]}
>>> (Ap [1,2] * 3) + (Ap [1,2] * 4)
Ap {getAp = [7,11,10,14]}

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a Source #

(-) :: Ap f a -> Ap f a -> Ap f a Source #

(*) :: Ap f a -> Ap f a -> Ap f a Source #

negate :: Ap f a -> Ap f a Source #

abs :: Ap f a -> Ap f a Source #

signum :: Ap f a -> Ap f a Source #

fromInteger :: Integer -> Ap f a Source #

(Alternative f, Applicative g) => Alternative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: (f :.: g) a Source #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

some :: (f :.: g) a -> (f :.: g) [a] Source #

many :: (f :.: g) a -> (f :.: g) [a] Source #

Alternative f => Alternative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

empty :: M1 i c f a Source #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

some :: M1 i c f a -> M1 i c f [a] Source #

many :: M1 i c f a -> M1 i c f [a] Source #

(Applicative f, Applicative g) => Applicative (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> (f :.: g) a Source #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source #

Applicative f => Applicative (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

pure :: a -> M1 i c f a Source #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b Source #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 Source #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a Source #

(Functor f, Functor g) => Functor (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

Functor f => Functor (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b Source #

(<$) :: a -> M1 i c f b -> M1 i c f a Source #

Monad f => Monad (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b Source #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

return :: a -> M1 i c f a Source #

MonadPlus f => MonadPlus (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

mzero :: M1 i c f a Source #

mplus :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

MonadFix f => MonadFix (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> M1 i c f a) -> M1 i c f a Source #

(Typeable f, Typeable g, Data p, Data (f p), Data (g p)) => Data ((f :*: g) p) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

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

Instance details

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 #

sum :: Num a => (f :.: g) a -> a Source #

product :: Num a => (f :.: g) a -> a Source #

Foldable f => Foldable (M1 i c f) Source #

@since base-4.9.0.0

Instance details

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 #

sum :: Num a => M1 i c f a -> a Source #

product :: Num a => M1 i c f a -> a Source #

(Traversable f, Traversable g) => Traversable (f :.: g) Source #

@since base-4.9.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> M1 i c f a -> f0 (M1 i c f b) Source #

sequenceA :: Applicative f0 => M1 i c f (f0 a) -> f0 (M1 i c f a) Source #

mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) Source #

sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) Source #

(Typeable f, Typeable g, Data p, Data (f (g p))) => Data ((f :.: g) p) Source #

@since base-4.9.0.0

Instance details

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

Instance details

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

Instance details

Defined in GHC.Internal.Generics

type Rep1 Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "GHC.Internal.Data.Functor.Identity" "ghc-internal" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 First Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 First = D1 ('MetaData "First" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))
type Rep1 Last Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "GHC.Internal.Data.Monoid" "ghc-internal" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))
type Rep1 Down Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Down = D1 ('MetaData "Down" "GHC.Internal.Data.Ord" "ghc-internal" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Dual Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Product Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Sum Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "GHC.Internal.Data.Semigroup.Internal" "ghc-internal" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 ZipList Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

type Rep1 ZipList = D1 ('MetaData "ZipList" "GHC.Internal.Functor.ZipList" "ghc-internal" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
type Rep1 Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Maybe Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 [] Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Either a :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

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

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Kleisli m a :: Type -> Type) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "GHC.Internal.Control.Arrow" "ghc-internal" 'True) (C1 ('MetaCons "Kleisli" 'PrefixI 'True) (S1 ('MetaSel ('Just "runKleisli") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ((FUN 'Many a :: Type -> Type) :.: Rec1 m)))
type Rep1 ((,,) a b :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,) a b c :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,) a b c d :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Internal.Generics" "ghc-internal" 'True) (C1 ('MetaCons "Comp1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComp1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))
type Rep1 ((,,,,,) a b c d e :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source #

@since base-4.16.0.0

Instance details

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

Instance details

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

Instance details

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 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.

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# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM.

negateDoubleX8# :: DoubleX8# -> DoubleX8# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateFloatX16# :: FloatX16# -> FloatX16# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateDoubleX4# :: DoubleX4# -> DoubleX4# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateFloatX8# :: FloatX8# -> FloatX8# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateDoubleX2# :: DoubleX2# -> DoubleX2# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateFloatX4# :: FloatX4# -> FloatX4# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt64X8# :: Int64X8# -> Int64X8# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt32X16# :: Int32X16# -> Int32X16# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt16X32# :: Int16X32# -> Int16X32# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt8X64# :: Int8X64# -> Int8X64# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt64X4# :: Int64X4# -> Int64X4# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt32X8# :: Int32X8# -> Int32X8# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt16X16# :: Int16X16# -> Int16X16# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt8X32# :: Int8X32# -> Int8X32# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt64X2# :: Int64X2# -> Int64X2# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt32X4# :: Int32X4# -> Int32X4# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt16X8# :: Int16X8# -> Int16X8# Source #

Negate element-wise.

Warning: this is only available on LLVM.

negateInt8X16# :: Int8X16# -> Int8X16# Source #

Negate element-wise.

Warning: this is only available on LLVM.

remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM.

quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM.

divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM.

timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Multiply two vectors element-wise.

Warning: this is only available on LLVM.

minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Subtract two vectors element-wise.

Warning: this is only available on LLVM.

plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Add two vectors element-wise.

Warning: this is only available on LLVM.

insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM.

unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord64X2# :: (# Word64#, Word64# #) -> Word64X2# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt64X2# :: (# Int64#, Int64# #) -> Int64X2# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

broadcastDoubleX8# :: Double# -> DoubleX8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastFloatX16# :: Float# -> FloatX16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastDoubleX4# :: Double# -> DoubleX4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastFloatX8# :: Float# -> FloatX8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastDoubleX2# :: Double# -> DoubleX2# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastFloatX4# :: Float# -> FloatX4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord64X8# :: Word64# -> Word64X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord32X16# :: Word32# -> Word32X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord16X32# :: Word16# -> Word16X32# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X64# :: Word8# -> Word8X64# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord64X4# :: Word64# -> Word64X4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord32X8# :: Word32# -> Word32X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord16X16# :: Word16# -> Word16X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X32# :: Word8# -> Word8X32# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord64X2# :: Word64# -> Word64X2# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord32X4# :: Word32# -> Word32X4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord16X8# :: Word16# -> Word16X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X16# :: Word8# -> Word8X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt64X8# :: Int64# -> Int64X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt32X16# :: Int32# -> Int32X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt16X32# :: Int16# -> Int16X32# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt8X64# :: Int8# -> Int8X64# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt64X4# :: Int64# -> Int64X4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt32X8# :: Int32# -> Int32X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt16X16# :: Int16# -> Int16X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt8X32# :: Int8# -> Int8X32# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt64X2# :: Int64# -> Int64X2# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt32X4# :: Int32# -> Int32X4# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt16X8# :: Int16# -> Int16X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastInt8X16# :: Int8# -> Int8X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld Source #

Sets the allocation counter for the current thread to the given value.

traceMarker# :: Addr# -> State# d -> State# d Source #

Emits a marker event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.

traceBinaryEvent# :: Addr# -> Int# -> State# d -> State# d Source #

Emits an event via the RTS tracing framework. The contents of the event is the binary object passed as the first argument with the given length passed as the second argument. The event will be emitted to the .eventlog file.

traceEvent# :: Addr# -> State# d -> State# d Source #

Emits an event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.

clearCCS# :: (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #) Source #

Run the supplied IO action with an empty CCS. For example, this is used by the interpreter to run an interpreted computation without the call stack showing that it was invoked from GHC.

getCurrentCCS# :: a -> State# d -> (# State# d, Addr# #) Source #

Returns the current CostCentreStack (value is NULL if not profiling). Takes a dummy argument which can be used to avoid the call to getCurrentCCS# being floated out by the simplifier, which would result in an uninformative stack (CAF).

getCCSOf# :: a -> State# d -> (# State# d, Addr# #) Source #

getApStackVal# :: a -> Int# -> (# Int#, b #) Source #

closureSize# :: a -> Int# Source #

closureSize# closure returns the size of the given closure in machine words.

unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #) Source #

unpackClosure# closure copies the closure and pointers in the payload of the given closure into two new arrays, and returns a pointer to the first word of the closure's info table, a non-pointer array for the raw bytes of the closure, and a pointer array for the pointers in the payload.

newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) Source #

newBCO# instrs lits ptrs arity bitmap creates a new bytecode object. The resulting object encodes a function of the given arity with the instructions encoded in instrs, and a static reference table usage bitmap given by bitmap.

mkApUpd0# :: BCO -> (# a #) Source #

Wrap a BCO in a AP_UPD thunk which will be updated with the value of the BCO when evaluated.

anyToAddr# :: a -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #

Retrieve the address of any Haskell value. This is essentially an unsafeCoerce#, but if implemented as such the core lint pass complains and fails to compile. As a primop, it is opaque to core/stg, and only appears in cmm (where the copy propagation pass will get rid of it). Note that "a" must be a value, not a thunk! It's too late for strictness analysis to enforce this, so you're on your own to guarantee this. Also note that Addr# is not a GC pointer - up to you to guarantee that it does not become a dangling pointer immediately after you get it.

addrToAny# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Addr# -> (# a #) Source #

Convert an Addr# to a followable Any type.

keepAlive# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d b. a -> State# d -> (State# d -> b) -> b Source #

keepAlive# x s k keeps the value x alive during the execution of the computation k.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.

numSparks# :: State# d -> (# State# d, Int# #) Source #

Returns the number of sparks in the local spark pool.

getSpark# :: State# d -> (# State# d, Int#, a #) Source #

seq# :: a -> State# d -> (# State# d, a #) Source #

spark# :: a -> State# d -> (# State# d, a #) Source #

par# :: a -> Int# Source #

reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> Int# Source #

Returns 1# if the given pointers are equal and 0# otherwise.

compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) Source #

Return the total capacity (in bytes) of all the compact blocks in the CNF.

compactAddWithSharing# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #

Like compactAdd#, but retains sharing and cycles during compaction.

compactAdd# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) Source #

Recursively add a closure and its transitive closure to a Compact# (a CNF), evaluating any unevaluated components at the same time. Note: compactAdd# is not thread-safe, so only one thread may call compactAdd# with a particular Compact# at any given time. The primop does not enforce any mutual exclusion; the caller is expected to arrange this.

compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) Source #

Given the pointer to the first block of a CNF and the address of the root object in the old address space, fix up the internal pointers inside the CNF to account for a different position in memory than when it was serialized. This method must be called exactly once after importing a serialized CNF. It returns the new CNF and the new adjusted root address.

compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #

Attempt to allocate a compact block with the capacity (in bytes) given by the first argument. The Addr# is a pointer to previous compact block of the CNF or nullAddr# to create a new CNF with a single compact block.

The resulting block is not known to the GC until compactFixupPointers# is called on it, and care must be taken so that the address does not escape or memory will be leaked.

compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #

Given a CNF and the address of one its compact blocks, returns the next compact block and its utilized size, or nullAddr# if the argument was the last compact block in the CNF.

compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #

Returns the address and the utilized size (in bytes) of the first compact block of a CNF.

compactContainsAny# :: a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #

Returns 1# if the object is in any CNF at all, 0# otherwise.

compactContains# :: Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) Source #

Returns 1# if the object is contained in the CNF, 0# otherwise.

compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld Source #

Set the new allocation size of the CNF. This value (in bytes) determines the capacity of each compact block in the CNF. It does not retroactively affect existing compact blocks in the CNF.

compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #) Source #

Create a new CNF with a single compact block. The argument is the capacity of the compact block (in bytes, not words). The capacity is rounded up to a multiple of the allocator block size and is capped to one mega block.

stableNameToInt# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StableName# a -> Int# Source #

makeStableName# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #) Source #

eqStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> StablePtr# a -> Int# Source #

deRefStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) Source #

makeStablePtr# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) Source #

touch# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> State# d Source #

finalizeWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) Source #

Finalize a weak pointer. The return value is an unboxed tuple containing the new state of the world and an "unboxed Maybe", represented by an Int# and a (possibly invalid) finalization action. An Int# of 1 indicates that the finalizer is valid. The return value b from the finalizer should be ignored.

deRefWeak# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) Source #

addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE ('BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) Source #

addCFinalizerToWeak# fptr ptr flag eptr w attaches a C function pointer fptr to a weak pointer w as a finalizer. If flag is zero, fptr will be called with one argument, ptr. Otherwise, it will be called with two arguments, eptr and ptr. addCFinalizerToWeak# returns 1 on success, or 0 if w is already dead.

mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #

mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #

mkWeak# k v finalizer s creates a weak reference to value k, with an associated reference to some value v. If k is still alive then v can be retrieved using deRefWeak#. Note that the type of k must be represented by a pointer (i.e. of kind TYPE 'LiftedRep or TYPE 'UnliftedRep@).

listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #) Source #

Returns an array of the threads started by the program. Note that this threads which have finished execution may or may not be present in this list, depending upon whether they have been collected by the garbage collector.

Since: ghc-prim-0.10

threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) Source #

Get the status of the given thread. Result is (ThreadStatus, Capability, Locked) where ThreadStatus is one of the status constants defined in rts/Constants.h, Capability is the number of the capability which currently owns the thread, and Locked is a boolean indicating whether the thread is bound to that capability.

Since: ghc-prim-0.9

threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #) Source #

Get the label of the given thread. Morally of type ThreadId# -> IO (Maybe ByteArray#), with a 1# tag denoting Just.

Since: ghc-prim-0.10

labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld Source #

Set the label of the given thread. The ByteArray# should contain a UTF-8-encoded string.

waitWrite# :: Int# -> State# d -> State# d Source #

Block until output is possible on specified file descriptor.

waitRead# :: Int# -> State# d -> State# d Source #

Block until input is available on specified file descriptor.

delay# :: Int# -> State# d -> State# d Source #

Sleep specified number of microseconds.

writeIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #) Source #

If IOPort# is full, immediately return with integer 0, throwing an IOPortException. Otherwise, store value arg as 'IOPort#''s new contents, and return with integer 1.

readIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #) Source #

If IOPort# is empty, block until it becomes full. Then remove and return its contents, and set it empty. Throws an IOPortException if another thread is already waiting to read this IOPort#.

newIOPort# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, IOPort# d a #) Source #

Create new IOPort#; initially empty.

isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #) Source #

Return 1 if MVar# is empty; 0 otherwise.

tryReadMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) Source #

If MVar# is empty, immediately return with integer 0 and value undefined. Otherwise, return with integer 1 and contents of MVar#.

readMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #

If MVar# is empty, block until it becomes full. Then read its contents without modifying the MVar, without possibility of intervention from other threads.

tryPutMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #) Source #

If MVar# is full, immediately return with integer 0. Otherwise, store value arg as 'MVar#''s new contents, and return with integer 1.

putMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> a -> State# d -> State# d Source #

If MVar# is full, block until it becomes empty. Then store value arg as its new contents.

tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) Source #

If MVar# is empty, immediately return with integer 0 and value undefined. Otherwise, return with integer 1 and contents of MVar#, and set MVar# empty.

takeMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) Source #

If MVar# is empty, block until it becomes full. Then remove and return its contents, and set it empty.

newMVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). State# d -> (# State# d, MVar# d a #) Source #

Create new MVar#; initially empty.

writeTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> a -> State# d -> State# d Source #

Write contents of TVar#.

readTVarIO# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #

Read contents of TVar# outside an STM transaction. Does not force evaluation of the result.

readTVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) Source #

Read contents of TVar# inside an STM transaction, i.e. within a call to atomically#. Does not force evaluation of the result.

newTVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #) Source #

Create a new TVar# holding a specified initial value.

catchSTM# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

catchRetry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

retry# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #) Source #

atomically# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

control0# :: PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #) Source #

See GHC.Prim.

Warning: this can fail with an unchecked exception.

unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

unmaskAsyncUninterruptible# k s evaluates k s such that asynchronous exceptions are unmasked.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.

maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

maskUninterruptible# k s evaluates k s such that asynchronous exceptions are deferred until after evaluation has finished.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.

maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

maskAsyncExceptions# k s evaluates k s such that asynchronous exceptions are deferred until after evaluation has finished.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.

raiseIO# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> State# RealWorld -> (# State# RealWorld, b #) Source #

raiseDivZero# :: (# #) -> b Source #

raiseOverflow# :: (# #) -> b Source #

raiseUnderflow# :: (# #) -> b Source #

raise# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) b. a -> b Source #

catch# :: forall {k :: Levity} a (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

catch# k handler s evaluates k s, invoking handler on any exceptions thrown.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; see the section "RuntimeRep polymorphism in continuation-style primops" for details.

casMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) Source #

Compare-and-swap: perform a pointer equality test between the first value passed to this function and the value stored inside the MutVar#. If the pointers are equal, replace the stored value with the second value passed to this function, otherwise do nothing. Returns the final value stored inside the MutVar#. The Int# indicates whether a swap took place, with 1# meaning that we didn't swap, and 0# that we did. Implies a full memory barrier. Because the comparison is done on the level of pointers, all of the difficulties of using reallyUnsafePtrEquality# correctly apply to casMutVar# as well.

atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) Source #

Modify the contents of a MutVar#, returning the previous contents and the result of applying the given function to the previous contents.

atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) Source #

Modify the contents of a MutVar#, returning the previous contents x :: a and the result of applying the given function to the previous contents f x :: c.

The data type c (not a newtype!) must be a record whose first field is of lifted type a :: Type and is not unpacked. For example, product types c ~ Solo a or c ~ (a, b) work well. If the record type is both monomorphic and strict in its first field, it's recommended to mark the latter {-# NOUNPACK #-} explicitly.

Under the hood atomicModifyMutVar2# atomically replaces a pointer to an old x :: a with a pointer to a selector thunk fst r, where fst is a selector for the first field of the record and r is a function application thunk r = f x.

atomicModifyIORef2Native from atomic-modify-general package makes an effort to reflect restrictions on c faithfully, providing a well-typed high-level wrapper.

atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) Source #

Atomically exchange the value of a MutVar#.

writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d Source #

Write contents of MutVar#.

readMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) Source #

Read contents of MutVar#. Result is not yet evaluated.

newMutVar# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) Source #

Create MutVar# with specified initial value in specified state thread.

atomicWriteWordAddr# :: Addr# -> Word# -> State# d -> State# d Source #

Given an address, write a machine word. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicReadWordAddr# :: Addr# -> State# d -> (# State# d, Word# #) Source #

Given an address, read a machine word. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchXorWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchOrWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchNandWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchAndWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchSubWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchAddWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

Given an address, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasWord64Addr# :: Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) Source #

Compare and swap on a 64 bit-sized and aligned memory location.

Use as: s -> atomicCasWordAddr64# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasWord32Addr# :: Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) Source #

Compare and swap on a 32 bit-sized and aligned memory location.

Use as: s -> atomicCasWordAddr32# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasWord16Addr# :: Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) Source #

Compare and swap on a 16 bit-sized and aligned memory location.

Use as: s -> atomicCasWordAddr16# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasWord8Addr# :: Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) Source #

Compare and swap on a 8 bit-sized and aligned memory location.

Use as: s -> atomicCasWordAddr8# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) Source #

Compare and swap on a word-sized and aligned memory location.

Use as: s -> atomicCasWordAddr# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #

Compare and swap on a word-sized memory location.

Use as: s -> atomicCasAddrAddr# location expected desired s

This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures).

Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicExchangeWordAddr# :: Addr# -> Word# -> State# d -> (# State# d, Word# #) Source #

The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.

Warning: this can fail with an unchecked exception.

atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# d -> (# State# d, Addr# #) Source #

The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #

Write a 64-bit unsigned integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #

Write a 64-bit signed integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #

Write a 32-bit unsigned integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #

Write a 32-bit signed integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #

Write a 16-bit unsigned integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #

Write a 16-bit signed integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #

Write a StablePtr# value to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #

Write a double-precision floating-point value to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #

Write a single-precision floating-point value to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #

Write a machine address to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsWord# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #

Write a word-sized unsigned integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsInt# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #

Write a word-sized integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Write a 32-bit character to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8OffAddrAsChar# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Write an 8-bit character to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #

Write a 64-bit unsigned integer to mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #

Write a 64-bit signed integer to mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #

Write a 32-bit unsigned integer to mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #

Write a 32-bit signed integer to mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #

Write a 16-bit unsigned integer to mutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #

Write a 16-bit signed integer to mutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d Source #

Write an 8-bit unsigned integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d Source #

Write an 8-bit signed integer to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #

Write a StablePtr# value to mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #

Write a double-precision floating-point value to mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #

Write a single-precision floating-point value to mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #

Write a machine address to mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #

Write a word-sized unsigned integer to mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #

Write a word-sized integer to mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Write a 32-bit character to mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Write an 8-bit character to mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsWord64# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #

Read a 64-bit unsigned integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsInt64# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #

Read a 64-bit signed integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsWord32# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #

Read a 32-bit unsigned integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsInt32# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #

Read a 32-bit signed integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsWord16# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #

Read a 16-bit unsigned integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsInt16# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #

Read a 16-bit signed integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsStablePtr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #

Read a StablePtr# value from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsDouble# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #

Read a double-precision floating-point value from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsFloat# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #

Read a single-precision floating-point value from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #

Read a machine address from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsWord# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #

Read a word-sized unsigned integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsInt# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #

Read a word-sized integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsWideChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 32-bit character from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8OffAddrAsChar# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Read an 8-bit character from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #

Read a 64-bit unsigned integer from mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #

Read a 64-bit signed integer from mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #

Read a 32-bit unsigned integer from mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #

Read a 32-bit signed integer from mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #

Read a 16-bit unsigned integer from mutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #

Read a 16-bit signed integer from mutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) Source #

Read an 8-bit unsigned integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) Source #

Read an 8-bit signed integer from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #

Read a StablePtr# value from mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #

Read a double-precision floating-point value from mutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #

Read a single-precision floating-point value from mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #

Read a machine address from mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #

Read a word-sized unsigned integer from mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #

Read a word-sized integer from mutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 32-bit character from mutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

Warning: this can fail with an unchecked exception.

readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Read an 8-bit character from mutable address; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer from immutable address; offset in bytes.

indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# Source #

Read a 64-bit signed integer from immutable address; offset in bytes.

indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer from immutable address; offset in bytes.

indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# Source #

Read a 32-bit signed integer from immutable address; offset in bytes.

indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer from immutable address; offset in bytes.

indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# Source #

Read a 16-bit signed integer from immutable address; offset in bytes.

indexWord8OffAddrAsStablePtr# :: Addr# -> Int# -> StablePtr# a Source #

Read a StablePtr# value from immutable address; offset in bytes.

indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# Source #

Read a double-precision floating-point value from immutable address; offset in bytes.

indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# Source #

Read a single-precision floating-point value from immutable address; offset in bytes.

indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# Source #

Read a machine address from immutable address; offset in bytes.

indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word# Source #

Read a word-sized unsigned integer from immutable address; offset in bytes.

indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int# Source #

Read a word-sized integer from immutable address; offset in bytes.

indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# Source #

Read a 32-bit character from immutable address; offset in bytes.

indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char# Source #

Read an 8-bit character from immutable address; offset in bytes.

indexWord64OffAddr# :: Addr# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer from immutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexInt64OffAddr# :: Addr# -> Int# -> Int64# Source #

Read a 64-bit signed integer from immutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexWord32OffAddr# :: Addr# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer from immutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexInt32OffAddr# :: Addr# -> Int# -> Int32# Source #

Read a 32-bit signed integer from immutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexWord16OffAddr# :: Addr# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer from immutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexInt16OffAddr# :: Addr# -> Int# -> Int16# Source #

Read a 16-bit signed integer from immutable address; offset in 2-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexWord8OffAddr# :: Addr# -> Int# -> Word8# Source #

Read an 8-bit unsigned integer from immutable address; offset in bytes.

indexInt8OffAddr# :: Addr# -> Int# -> Int8# Source #

Read an 8-bit signed integer from immutable address; offset in bytes.

indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #

Read a StablePtr# value from immutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source #

Read a double-precision floating-point value from immutable address; offset in 8-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexFloatOffAddr# :: Addr# -> Int# -> Float# Source #

Read a single-precision floating-point value from immutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source #

Read a machine address from immutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexWordOffAddr# :: Addr# -> Int# -> Word# Source #

Read a word-sized unsigned integer from immutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexIntOffAddr# :: Addr# -> Int# -> Int# Source #

Read a word-sized integer from immutable address; offset in machine words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #

Read a 32-bit character from immutable address; offset in 4-byte words.

On some platforms, the access may fail for an insufficiently aligned Addr#.

indexCharOffAddr# :: Addr# -> Int# -> Char# Source #

Read an 8-bit character from immutable address; offset in bytes.

int2Addr# :: Int# -> Addr# Source #

Coerce directly from int to address.

addr2Int# :: Addr# -> Int# Source #

Coerce directly from address to int.

remAddr# :: Addr# -> Int# -> Int# Source #

Return the remainder when the Addr# arg, treated like an Int#, is divided by the Int# arg.

minusAddr# :: Addr# -> Addr# -> Int# Source #

Result is meaningless if two Addr#s are so far apart that their difference doesn't fit in an Int#.

fetchXorIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to XOR, atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchOrIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to OR, atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchNandIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to NAND, atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchAndIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to AND, atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchSubIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

fetchAddIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, and offset in machine words, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

casInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) Source #

Given an array, an offset in 64 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

casInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) Source #

Given an array, an offset in 32 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

casInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) Source #

Given an array, an offset in 16 bit units, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

casInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) Source #

Given an array, an offset in bytes, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

casIntArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array, an offset in machine words, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicWriteIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

Given an array and an offset in machine words, write an element. The index is assumed to be in bounds. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

atomicReadIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #

Given an array and an offset in machine words, read an element. The index is assumed to be in bounds. Implies a full memory barrier.

Warning: this can fail with an unchecked exception.

setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld Source #

setAddrRange# dest len c sets all of the bytes in [dest, dest+len) to the value c.

Analogous to the standard C function memset, but with a different argument order.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.11.0

setByteArray# :: MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d Source #

setByteArray# ba off len c sets the byte range [off, off+len) of the MutableByteArray# to the byte c.

Warning: this can fail with an unchecked exception.

copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #

copyAddrToAddrNonOverlapping# src dest len copies len bytes from src to dest. As the name suggests, these two memory ranges must not overlap, although this pre-condition is not checked.

Analogous to the standard C function memcpy, but with a different argument order.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.11.0

copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld Source #

copyAddrToAddr# src dest len copies len bytes from src to dest. These two memory ranges are allowed to overlap.

Analogous to the standard C function memmove, but with a different argument order.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.11.0

copyAddrToByteArray# :: Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

Copy a memory range starting at the Addr# to the specified range in the MutableByteArray#. The memory region at Addr# and the ByteArray# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.

Warning: this can fail with an unchecked exception.

copyMutableByteArrayToAddr# :: MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d Source #

Copy a range of the MutableByteArray# to the memory range starting at the Addr#. The MutableByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the MutableByteArray# (e.g. if the MutableByteArray# were pinned), but this is not checked either.

Warning: this can fail with an unchecked exception.

copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d Source #

Copy a range of the ByteArray# to the memory range starting at the Addr#. The ByteArray# and the memory region at Addr# must fully contain the specified ranges, but this is not checked. The Addr# must not point into the ByteArray# (e.g. if the ByteArray# were pinned), but this is not checked either.

Warning: this can fail with an unchecked exception.

copyMutableByteArrayNonOverlapping# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

copyMutableByteArrayNonOverlapping# src src_ofs dst dst_ofs len copies the range starting at offset src_ofs of length len from the MutableByteArray# src to the MutableByteArray# dst starting at offset dst_ofs. Both arrays must fully contain the specified ranges, but this is not checked. The regions are not allowed to overlap, but this is also not checked.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.11.0

copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

copyMutableByteArray# src src_ofs dst dst_ofs len copies the range starting at offset src_ofs of length len from the MutableByteArray# src to the MutableByteArray# dst starting at offset dst_ofs. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.

Warning: this can fail with an unchecked exception.

copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

copyByteArray# src src_ofs dst dst_ofs len copies the range starting at offset src_ofs of length len from the ByteArray# src to the MutableByteArray# dst starting at offset dst_ofs. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

Warning: this can fail with an unchecked exception.

compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #

compareByteArrays# src1 src1_ofs src2 src2_ofs n compares n bytes starting at offset src1_ofs in the first ByteArray# src1 to the range of n bytes (i.e. same length) starting at offset src2_ofs of the second ByteArray# src2. Both arrays must fully contain the specified ranges, but this is not checked. Returns an Int# less than, equal to, or greater than zero if the range is found, respectively, to be byte-wise lexicographically less than, to match, or be greater than the second range.

Since: ghc-prim-0.5.2.0

writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #

Write a 64-bit unsigned integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #

Write a 64-bit signed integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #

Write a 32-bit unsigned integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #

Write a 32-bit signed integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #

Write a 16-bit unsigned integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #

Write a 16-bit signed integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #

Write a StablePtr# value to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #

Write a double-precision floating-point value to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #

Write a single-precision floating-point value to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #

Write a machine address to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #

Write a word-sized unsigned integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

Write a word-sized integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write a 32-bit character to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write an 8-bit character to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord64Array# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #

Write a 64-bit unsigned integer to mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #

Write a 64-bit signed integer to mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

writeWord32Array# :: MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d Source #

Write a 32-bit unsigned integer to mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

writeInt32Array# :: MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d Source #

Write a 32-bit signed integer to mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

writeWord16Array# :: MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d Source #

Write a 16-bit unsigned integer to mutable array; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

writeInt16Array# :: MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d Source #

Write a 16-bit signed integer to mutable array; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d Source #

Write an 8-bit unsigned integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d Source #

Write an 8-bit signed integer to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

writeStablePtrArray# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d Source #

Write a StablePtr# value to mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

writeDoubleArray# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d Source #

Write a double-precision floating-point value to mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

writeFloatArray# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d Source #

Write a single-precision floating-point value to mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

writeAddrArray# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d Source #

Write a machine address to mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

writeWordArray# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d Source #

Write a word-sized unsigned integer to mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

writeIntArray# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

Write a word-sized integer to mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

writeWideCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write a 32-bit character to mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write an 8-bit character to mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #

Read a 64-bit unsigned integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #

Read a 64-bit signed integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #

Read a 32-bit unsigned integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #

Read a 32-bit signed integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #

Read a 16-bit unsigned integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #

Read a 16-bit signed integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #

Read a StablePtr# value from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #

Read a double-precision floating-point value from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #

Read a single-precision floating-point value from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #

Read a machine address from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #

Read a word-sized unsigned integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #

Read a word-sized integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 32-bit character from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read an 8-bit character from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) Source #

Read a 64-bit unsigned integer from mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #

Read a 64-bit signed integer from mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

readWord32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) Source #

Read a 32-bit unsigned integer from mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readInt32Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) Source #

Read a 32-bit signed integer from mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readWord16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) Source #

Read a 16-bit unsigned integer from mutable array; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

readInt16Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) Source #

Read a 16-bit signed integer from mutable array; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) Source #

Read an 8-bit unsigned integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) Source #

Read an 8-bit signed integer from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

readStablePtrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #

Read a StablePtr# value from mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

readDoubleArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) Source #

Read a double-precision floating-point value from mutable array; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

readFloatArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) Source #

Read a single-precision floating-point value from mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readAddrArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) Source #

Read a machine address from mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

readWordArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) Source #

Read a word-sized unsigned integer from mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

readIntArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) Source #

Read a word-sized integer from mutable array; offset in machine words.

Warning: this can fail with an unchecked exception.

readWideCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 32-bit character from mutable array; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read an 8-bit character from mutable array; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer from immutable array; offset in bytes.

indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# Source #

Read a 64-bit signed integer from immutable array; offset in bytes.

indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer from immutable array; offset in bytes.

indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #

Read a 32-bit signed integer from immutable array; offset in bytes.

indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer from immutable array; offset in bytes.

indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #

Read a 16-bit signed integer from immutable array; offset in bytes.

indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #

Read a StablePtr# value from immutable array; offset in bytes.

indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #

Read a double-precision floating-point value from immutable array; offset in bytes.

indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #

Read a single-precision floating-point value from immutable array; offset in bytes.

indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #

Read a machine address from immutable array; offset in bytes.

indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #

Read a word-sized unsigned integer from immutable array; offset in bytes.

indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #

Read a word-sized integer from immutable array; offset in bytes.

indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #

Read a 32-bit character from immutable array; offset in bytes.

indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #

Read an 8-bit character from immutable array; offset in bytes.

indexWord64Array# :: ByteArray# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer from immutable array; offset in 8-byte words.

indexInt64Array# :: ByteArray# -> Int# -> Int64# Source #

Read a 64-bit signed integer from immutable array; offset in 8-byte words.

indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer from immutable array; offset in 4-byte words.

indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #

Read a 32-bit signed integer from immutable array; offset in 4-byte words.

indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer from immutable array; offset in 2-byte words.

indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #

Read a 16-bit signed integer from immutable array; offset in 2-byte words.

indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #

Read an 8-bit unsigned integer from immutable array; offset in bytes.

indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #

Read an 8-bit signed integer from immutable array; offset in bytes.

indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #

Read a StablePtr# value from immutable array; offset in machine words.

indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #

Read a double-precision floating-point value from immutable array; offset in 8-byte words.

indexFloatArray# :: ByteArray# -> Int# -> Float# Source #

Read a single-precision floating-point value from immutable array; offset in 4-byte words.

indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #

Read a machine address from immutable array; offset in machine words.

indexWordArray# :: ByteArray# -> Int# -> Word# Source #

Read a word-sized unsigned integer from immutable array; offset in machine words.

indexIntArray# :: ByteArray# -> Int# -> Int# Source #

Read a word-sized integer from immutable array; offset in machine words.

indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #

Read a 32-bit character from immutable array; offset in 4-byte words.

indexCharArray# :: ByteArray# -> Int# -> Char# Source #

Read an 8-bit character from immutable array; offset in bytes.

getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) Source #

Return the number of elements in the array, correctly accounting for the effect of shrinkMutableByteArray# and resizeMutableByteArray#.

Since: ghc-prim-0.5.0.0

sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #

Return the size of the array in bytes. Deprecated, it is unsafe in the presence of shrinkMutableByteArray# and resizeMutableByteArray# operations on the same mutable byte array.

sizeofByteArray# :: ByteArray# -> Int# Source #

Return the size of the array in bytes.

unsafeThawByteArray# :: ByteArray# -> State# d -> (# State# d, MutableByteArray# d #) Source #

Make an immutable byte array mutable, without copying.

Since: ghc-prim-0.12.0.0

unsafeFreezeByteArray# :: MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Source #

Make a mutable byte array immutable, without copying.

resizeMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #

Resize mutable byte array to new specified size (in bytes), shrinking or growing it. The returned MutableByteArray# is either the original MutableByteArray# resized in-place or, if not possible, a newly allocated (unpinned) MutableByteArray# (with the original content copied over).

To avoid undefined behaviour, the original MutableByteArray# shall not be accessed anymore after a resizeMutableByteArray# has been performed. Moreover, no reference to the old one should be kept in order to allow garbage collection of the original MutableByteArray# in case a new MutableByteArray# had to be allocated.

Since: ghc-prim-0.4.0.0

shrinkMutableByteArray# :: MutableByteArray# d -> Int# -> State# d -> State# d Source #

Shrink mutable byte array to new specified size (in bytes), in the specified state thread. The new size argument must be less than or equal to the current size as reported by getSizeofMutableByteArray#.

Assuming the non-profiling RTS, this primitive compiles to an O(1) operation in C--, modifying the array in-place. Backends bypassing C-- representation (such as JavaScript) might behave differently.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.4.0.0

mutableByteArrayContents# :: MutableByteArray# d -> Addr# Source #

Intended for use with pinned arrays; otherwise very unsafe!

byteArrayContents# :: ByteArray# -> Addr# Source #

Intended for use with pinned arrays; otherwise very unsafe!

isByteArrayPinned# :: ByteArray# -> Int# Source #

Determine whether a ByteArray# is guaranteed not to move during GC.

isMutableByteArrayPinned# :: MutableByteArray# d -> Int# Source #

Determine whether a MutableByteArray# is guaranteed not to move during GC.

newAlignedPinnedByteArray# :: Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #

Like newPinnedByteArray# but allow specifying an arbitrary alignment, which must be a power of two.

Warning: this can fail with an unchecked exception.

newPinnedByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #

Like newByteArray# but GC guarantees not to move it.

newByteArray# :: Int# -> State# d -> (# State# d, MutableByteArray# d #) Source #

Create a new mutable byte array of specified size (in bytes), in the specified state thread. The size of the memory underlying the array will be rounded up to the platform's word size.

casSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #

Unsafe, machine-level atomic compare and swap on an element within an array. See the documentation of casArray#.

Warning: this can fail with an unchecked exception.

thawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

cloneSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. The source and destination arrays can refer to the same array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.

Warning: this can fail with an unchecked exception.

copySmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

Warning: this can fail with an unchecked exception.

unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #

Make an immutable array mutable, without copying.

unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) Source #

Make a mutable array immutable, without copying.

indexSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# -> (# a #) Source #

Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.

getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) Source #

Return the number of elements in the array, correctly accounting for the effect of shrinkSmallMutableArray# and resizeSmallMutableArray#.

Since: ghc-prim-0.6.1

sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# Source #

Return the number of elements in the array. Deprecated, it is unsafe in the presence of shrinkSmallMutableArray# and resizeSmallMutableArray# operations on the same small mutable array.

sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). SmallArray# a -> Int# Source #

Return the number of elements in the array.

writeSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d Source #

Write to specified index of mutable array.

Warning: this can fail with an unchecked exception.

readSmallArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #

Read from specified index of mutable array. Result is not yet evaluated.

Warning: this can fail with an unchecked exception.

shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d Source #

Shrink mutable array to new specified size, in the specified state thread. The new size argument must be less than or equal to the current size as reported by getSizeofSmallMutableArray#.

Assuming the non-profiling RTS, for the copying garbage collector (default) this primitive compiles to an O(1) operation in C--, modifying the array in-place. For the non-moving garbage collector, however, the time is proportional to the number of elements shrinked out. Backends bypassing C-- representation (such as JavaScript) might behave differently.

Warning: this can fail with an unchecked exception.

Since: ghc-prim-0.6.1

newSmallArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) Source #

Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.

casArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) Source #

Given an array, an offset, the expected old value, and the new value, perform an atomic compare and swap (i.e. write the new value if the current value and the old value are the same pointer). Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns the element at the offset after the operation completes. This means that on a success the new value is returned, and on a failure the actual old value (not the expected one) is returned. Implies a full memory barrier. The use of a pointer equality on a boxed value makes this function harder to use correctly than casIntArray#. All of the difficulties of using reallyUnsafePtrEquality# correctly apply to casArray# as well.

Warning: this can fail with an unchecked exception.

thawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

freezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

cloneArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> Int# -> Array# a Source #

Given a source array, an offset into the source array, and a number of elements to copy, create a new array with the elements from the source array. The provided array must fully contain the specified range, but this is not checked.

Warning: this can fail with an unchecked exception.

copyMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. In the case where the source and destination are the same array the source and destination regions may overlap.

Warning: this can fail with an unchecked exception.

copyArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d Source #

Given a source array, an offset into the source array, a destination array, an offset into the destination array, and a number of elements to copy, copy the elements from the source array to the destination array. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

Warning: this can fail with an unchecked exception.

unsafeThawArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) Source #

Make an immutable array mutable, without copying.

unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) Source #

Make a mutable array immutable, without copying.

indexArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# -> (# a #) Source #

Read from the specified index of an immutable array. The result is packaged into an unboxed unary tuple; the result itself is not yet evaluated. Pattern matching on the tuple forces the indexing of the array to happen but does not evaluate the element itself. Evaluating the thunk prevents additional thunks from building up on the heap. Avoiding these thunks, in turn, reduces references to the argument array, allowing it to be garbage collected more promptly.

sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# Source #

Return the number of elements in the array.

sizeofArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)). Array# a -> Int# Source #

Return the number of elements in the array.

writeArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d Source #

Write to specified index of mutable array.

Warning: this can fail with an unchecked exception.

readArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) Source #

Read from specified index of mutable array. Result is not yet evaluated.

Warning: this can fail with an unchecked exception.

newArray# :: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) Source #

Create a new mutable array with the specified number of elements, in the specified state thread, with each element containing the specified initial value.

fnmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #

Fused negate-multiply-subtract operation -x*y-z. See GHC.Prim.

fnmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #

Fused negate-multiply-add operation -x*y+z. See GHC.Prim.

fmsubDouble# :: Double# -> Double# -> Double# -> Double# Source #

Fused multiply-subtract operation x*y-z. See GHC.Prim.

fmaddDouble# :: Double# -> Double# -> Double# -> Double# Source #

Fused multiply-add operation x*y+z. See GHC.Prim.

fnmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #

Fused negate-multiply-subtract operation -x*y-z. See GHC.Prim.

fnmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #

Fused negate-multiply-add operation -x*y+z. See GHC.Prim.

fmsubFloat# :: Float# -> Float# -> Float# -> Float# Source #

Fused multiply-subtract operation x*y-z. See GHC.Prim.

fmaddFloat# :: Float# -> Float# -> Float# -> Float# Source #

Fused multiply-add operation x*y+z. See GHC.Prim.

decodeFloat_Int# :: Float# -> (# Int#, Int# #) Source #

Convert to integers. First Int# in result is the mantissa; second is the exponent.

float2Int# :: Float# -> Int# Source #

Truncates a Float# value to the nearest Int#. Results are undefined if the truncation if truncation yields a value outside the range of Int#.

decodeDouble_Int64# :: Double# -> (# Int64#, Int# #) Source #

Decode Double# into mantissa and base-2 exponent.

decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) Source #

Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.

(**##) :: Double# -> Double# -> Double# Source #

Exponentiation.

double2Int# :: Double# -> Int# Source #

Truncates a Double# value to the nearest Int#. Results are undefined if the truncation if truncation yields a value outside the range of Int#.

(/##) :: Double# -> Double# -> Double# infixl 7 Source #

(*##) :: Double# -> Double# -> Double# infixl 7 Source #

(-##) :: Double# -> Double# -> Double# infixl 6 Source #

(+##) :: Double# -> Double# -> Double# infixl 6 Source #

(<=##) :: Double# -> Double# -> Int# infix 4 Source #

(<##) :: Double# -> Double# -> Int# infix 4 Source #

(/=##) :: Double# -> Double# -> Int# infix 4 Source #

(==##) :: Double# -> Double# -> Int# infix 4 Source #

(>=##) :: Double# -> Double# -> Int# infix 4 Source #

(>##) :: Double# -> Double# -> Int# infix 4 Source #

bitReverse# :: Word# -> Word# Source #

Reverse the order of the bits in a word.

bitReverse64# :: Word64# -> Word64# Source #

Reverse the order of the bits in a 64-bit word.

bitReverse32# :: Word# -> Word# Source #

Reverse the order of the bits in a 32-bit word.

bitReverse16# :: Word# -> Word# Source #

Reverse the order of the bits in a 16-bit word.

bitReverse8# :: Word# -> Word# Source #

Reverse the order of the bits in a 8-bit word.

byteSwap# :: Word# -> Word# Source #

Swap bytes in a word.

byteSwap64# :: Word64# -> Word64# Source #

Swap bytes in a 64 bits of a word.

byteSwap32# :: Word# -> Word# Source #

Swap bytes in the lower 32 bits of a word. The higher bytes are undefined.

byteSwap16# :: Word# -> Word# Source #

Swap bytes in the lower 16 bits of a word. The higher bytes are undefined.

ctz# :: Word# -> Word# Source #

Count trailing zeros in a word.

ctz64# :: Word64# -> Word# Source #

Count trailing zeros in a 64-bit word.

ctz32# :: Word# -> Word# Source #

Count trailing zeros in the lower 32 bits of a word.

ctz16# :: Word# -> Word# Source #

Count trailing zeros in the lower 16 bits of a word.

ctz8# :: Word# -> Word# Source #

Count trailing zeros in the lower 8 bits of a word.

clz# :: Word# -> Word# Source #

Count leading zeros in a word.

clz64# :: Word64# -> Word# Source #

Count leading zeros in a 64-bit word.

clz32# :: Word# -> Word# Source #

Count leading zeros in the lower 32 bits of a word.

clz16# :: Word# -> Word# Source #

Count leading zeros in the lower 16 bits of a word.

clz8# :: Word# -> Word# Source #

Count leading zeros in the lower 8 bits of a word.

pext# :: Word# -> Word# -> Word# Source #

Extract bits from a word at locations specified by a mask, aka parallel bit extract.

Software emulation:

pext :: Word -> Word -> Word
pext src mask = loop 0 0 0
  where
    loop i count result
      | i >= finiteBitSize (0 :: Word)
      = result
      | testBit mask i
      = loop (i + 1) (count + 1) (if testBit src i then setBit result count else result)
      | otherwise
      = loop (i + 1) count result

Since: ghc-prim-0.5.2.0

pext64# :: Word64# -> Word64# -> Word64# Source #

Extract bits from a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pext32# :: Word# -> Word# -> Word# Source #

Extract bits from lower 32 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pext16# :: Word# -> Word# -> Word# Source #

Extract bits from lower 16 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pext8# :: Word# -> Word# -> Word# Source #

Extract bits from lower 8 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pdep# :: Word# -> Word# -> Word# Source #

Deposit bits to a word at locations specified by a mask, aka parallel bit deposit.

Software emulation:

pdep :: Word -> Word -> Word
pdep src mask = go 0 src mask
  where
    go :: Word -> Word -> Word -> Word
    go result _ 0 = result
    go result src mask = go newResult newSrc newMask
      where
        maskCtz   = countTrailingZeros mask
        newResult = if testBit src 0 then setBit result maskCtz else result
        newSrc    = src `shiftR` 1
        newMask   = clearBit mask maskCtz

Since: ghc-prim-0.5.2.0

pdep64# :: Word64# -> Word64# -> Word64# Source #

Deposit bits to a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pdep32# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 32 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pdep16# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 16 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

pdep8# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 8 bits of a word at locations specified by a mask.

Since: ghc-prim-0.5.2.0

popCnt# :: Word# -> Word# Source #

Count the number of set bits in a word.

popCnt64# :: Word64# -> Word# Source #

Count the number of set bits in a 64-bit word.

popCnt32# :: Word# -> Word# Source #

Count the number of set bits in the lower 32 bits of a word.

popCnt16# :: Word# -> Word# Source #

Count the number of set bits in the lower 16 bits of a word.

popCnt8# :: Word# -> Word# Source #

Count the number of set bits in the lower 8 bits of a word.

uncheckedShiftRL# :: Word# -> Int# -> Word# Source #

Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedShiftL# :: Word# -> Int# -> Word# Source #

Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) Source #

Takes high word of dividend, then low word of dividend, then divisor. Requires that high word < divisor.

plusWord2# :: Word# -> Word# -> (# Word#, Word# #) Source #

Add unsigned integers, with the high part (carry) in the first component of the returned pair and the low part in the second component of the pair. See also addWordC#.

subWordC# :: Word# -> Word# -> (# Word#, Int# #) Source #

Subtract unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow.

addWordC# :: Word# -> Word# -> (# Word#, Int# #) Source #

Add unsigned integers reporting overflow. The first element of the pair is the result. The second element is the carry flag, which is nonzero on overflow. See also plusWord2#.

uncheckedIShiftRL# :: Int# -> Int# -> Int# Source #

Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedIShiftRA# :: Int# -> Int# -> Int# Source #

Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

uncheckedIShiftL# :: Int# -> Int# -> Int# Source #

Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.

word2Double# :: Word# -> Double# Source #

Convert an Word# to the corresponding Double# with the same integral value (up to truncation due to floating-point precision). e.g. word2Double# 1## == 1.0##

word2Float# :: Word# -> Float# Source #

Convert an Word# to the corresponding Float# with the same integral value (up to truncation due to floating-point precision). e.g. word2Float# 1## == 1.0#

int2Double# :: Int# -> Double# Source #

Convert an Int# to the corresponding Double# with the same integral value (up to truncation due to floating-point precision). e.g. int2Double# 1# == 1.0##

int2Float# :: Int# -> Float# Source #

Convert an Int# to the corresponding Float# with the same integral value (up to truncation due to floating-point precision). e.g. int2Float# 1# == 1.0#

(<=#) :: Int# -> Int# -> Int# infix 4 Source #

(<#) :: Int# -> Int# -> Int# infix 4 Source #

(/=#) :: Int# -> Int# -> Int# infix 4 Source #

(==#) :: Int# -> Int# -> Int# infix 4 Source #

(>=#) :: Int# -> Int# -> Int# infix 4 Source #

(>#) :: Int# -> Int# -> Int# infix 4 Source #

subIntC# :: Int# -> Int# -> (# Int#, Int# #) Source #

Subtract signed integers reporting overflow. First member of result is the difference truncated to an Int#; second member is zero if the true difference fits in an Int#, nonzero if overflow occurred (the difference is either too large or too small to fit in an Int#).

addIntC# :: Int# -> Int# -> (# Int#, Int# #) Source #

Add signed integers reporting overflow. First member of result is the sum truncated to an Int#; second member is zero if the true sum fits in an Int#, nonzero if overflow occurred (the sum is either too large or too small to fit in an Int#).

negateInt# :: Int# -> Int# Source #

Unary negation. Since the negative Int# range extends one further than the positive range, negateInt# of the most negative number is an identity operation. This way, negateInt# is always its own inverse.

notI# :: Int# -> Int# Source #

Bitwise "not", also known as the binary complement.

xorI# :: Int# -> Int# -> Int# Source #

Bitwise "xor".

orI# :: Int# -> Int# -> Int# Source #

Bitwise "or".

andI# :: Int# -> Int# -> Int# Source #

Bitwise "and".

quotRemInt# :: Int# -> Int# -> (# Int#, Int# #) Source #

Rounds towards zero.

remInt# :: Int# -> Int# -> Int# Source #

Satisfies (quotInt# x y) *# y +# (remInt# x y) == x. The behavior is undefined if the second argument is zero.

quotInt# :: Int# -> Int# -> Int# Source #

Rounds towards zero. The behavior is undefined if the second argument is zero.

mulIntMayOflo# :: Int# -> Int# -> Int# Source #

Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommended implementation is to do a 32 x 32 -> 64 signed multiply, and subtract result[63:32] from (result[31] >>signed 31). If this is zero, meaning that the upper word is merely a sign extension of the lower one, no overflow can occur.

On a 64-bit platform it is not always possible to acquire the top 64 bits of the result. Therefore, a recommended implementation is to take the absolute value of both operands, and return 0 iff bits[63:31] of them are zero, since that means that their magnitudes fit within 31 bits, so the magnitude of the product must fit into 62 bits.

If in doubt, return non-zero, but do make an effort to create the correct answer for small args, since otherwise the performance of (*) :: Integer -> Integer -> Integer will be poor.

timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) Source #

Return a triple (isHighNeeded,high,low) where high and low are respectively the high and low bits of the double-word result. isHighNeeded is a cheap way to test if the high word is a sign-extension of the low word (isHighNeeded = 0#) or not (isHighNeeded = 1#).

(*#) :: Int# -> Int# -> Int# infixl 7 Source #

Low word of signed integer multiply.

(-#) :: Int# -> Int# -> Int# infixl 6 Source #

(+#) :: Int# -> Int# -> Int# infixl 6 Source #

rightSection :: forall {n :: Multiplicity} {o :: Multiplicity} a b c. (a %n -> b %o -> c) -> b %o -> a %n -> c Source #

leftSection :: forall {n :: Multiplicity} a b. (a %n -> b) -> a %n -> b Source #

proxy# :: forall {k} (a :: k). Proxy# a Source #

Witness for an unboxed Proxy# value, which has no runtime representation.

coerce :: Coercible a b => a -> b Source #

The function coerce allows you to safely convert between values of types that have the same representation with no run-time overhead. In the simplest case you can use it instead of a newtype constructor, to go from the newtype's concrete type to the abstract type. But it also works in more complicated settings, e.g. converting a list of newtypes to a list of concrete types.

When used in conversions involving a newtype wrapper, make sure the newtype constructor is in scope.

This function is representation-polymorphic, but the RuntimeRep type argument is marked as Inferred, meaning that it is not available for visible type application. This means the typechecker will accept coerce @Int @Age 42.

Examples

Expand
>>> newtype TTL = TTL Int deriving (Eq, Ord, Show)
>>> newtype Age = Age Int deriving (Eq, Ord, Show)
>>> coerce (Age 42) :: TTL
TTL 42
>>> coerce (+ (1 :: Int)) (Age 42) :: TTL
TTL 43
>>> coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
[TTL 43,TTL 25]

seq :: a -> b -> b infixr 0 Source #

The value of seq a b is bottom if a is bottom, and otherwise equal to b. In other words, it evaluates the first argument a to weak head normal form (WHNF). seq is usually introduced to improve performance by avoiding unneeded laziness.

A note on evaluation order: the expression seq a b does not guarantee that a will be evaluated before b. The only guarantee given by seq is that the both a and b will be evaluated before seq returns a value. In particular, this means that b may be evaluated before a. If you need to guarantee a specific order of evaluation, you must use the function pseq from the "parallel" package.

nullAddr# :: Addr# Source #

The null address.

void# :: (# #) Source #

This is an alias for the unboxed unit tuple constructor. In earlier versions of GHC, void# was a value of the primitive type Void#, which is now defined to be (# #).

realWorld# :: State# RealWorld Source #

The token used in the implementation of the IO monad as a state monad. It does not pass any information at runtime. See also runRW#.