base-4.17.0.0: Basic libraries
Copyright(c) The University of Glasgow 2002
Licensesee libraries/base/LICENSE
Maintainercvs-ghc@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellUnsafe
LanguageHaskell2010

GHC.Exts

Description

GHC Extensions: this is the Approved Way to get at GHC-specific extensions.

Note: no other base module should import this module.

Synopsis

Pointer types

data Ptr a Source #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Constructors

Ptr Addr# 

Instances

Instances details
Generic1 (URec (Ptr ()) :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a Source #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a Source #

Data a => Data (Ptr a) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Ptr a -> Constr Source #

dataTypeOf :: Ptr a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Foldable (UAddr :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 #

Traversable (UAddr :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 #

Storable (Ptr a) Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int Source #

alignment :: Ptr a -> Int Source #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source #

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

Show (Ptr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS Source #

show :: Ptr a -> String Source #

showList :: [Ptr a] -> ShowS Source #

Eq (Ptr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

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

Ord (Ptr a) Source #

Since: base-2.1

Instance details

Defined in GHC.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 #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

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

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

Generic (URec (Ptr ()) p) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Eq (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

Ord (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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 #

data URec (Ptr ()) (p :: k) Source #

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

data FunPtr a Source #

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

foreign import ccall "stdlib.h &free"
  p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

type Compare = Int -> Int -> Bool
foreign import ccall "wrapper"
  mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

type IntFunction = CInt -> IO ()
foreign import ccall "dynamic"
  mkFun :: FunPtr IntFunction -> IntFunction

Constructors

FunPtr Addr# 

Instances

Instances details
Storable (FunPtr a) Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int Source #

alignment :: FunPtr a -> Int Source #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) Source #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) Source #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () Source #

Show (FunPtr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Ptr

Eq (FunPtr a) Source # 
Instance details

Defined in GHC.Ptr

Methods

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

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

Ord (FunPtr a) Source # 
Instance details

Defined in GHC.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 #

Other primitive types

data Word Source #

A Word is an unsigned integral type, with the same size as Int.

Constructors

W# Word# 

Instances

Instances details
Data Word Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Storable Word Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word Source #

Since: base-2.1

Instance details

Defined in GHC.Bits

FiniteBits Word Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

Bounded Word Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Word Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

Num Word Source #

Since: base-2.1

Instance details

Defined in GHC.Num

Read Word Source #

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Integral Word Source #

Since: base-2.1

Instance details

Defined in GHC.Real

Real Word Source #

Since: base-2.1

Instance details

Defined in GHC.Real

Show Word Source #

Since: base-2.1

Instance details

Defined in GHC.Show

PrintfArg Word Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

Associated Types

type Rep1 (URec Word) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Word a -> Rep1 (URec Word) a Source #

to1 :: forall (a :: k0). Rep1 (URec Word) a -> URec Word a Source #

Foldable (UWord :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 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.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.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type Source #

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

Eq (URec Word p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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.Generics

type Rep1 (URec Word :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" '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 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 #

Storable Float Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Enum Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Floating Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Num Float Source #

Note that due to the presence of NaN, not all elements of Float have an additive inverse.

>>> 0/0 + (negate 0/0 :: Float)
NaN

Also note that due to the presence of -0, Float's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Float)
0.0

Since: base-2.1

Instance details

Defined in GHC.Float

Read Float Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Fractional Float Source #

Note that due to the presence of NaN, not all elements of Float have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Float)
NaN

Since: base-2.1

Instance details

Defined in GHC.Float

Real Float Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFrac Float Source #

Since: base-2.1

Instance details

Defined in GHC.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.1

Instance details

Defined in GHC.Float

PrintfArg Float Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

Note that due to the presence of NaN, Float's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord's operator interactions are not respected by Float's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Generic1 (URec Float :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Float) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Float a -> Rep1 (URec Float) a Source #

to1 :: forall (a :: k0). Rep1 (URec Float) a -> URec Float a Source #

Foldable (UFloat :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 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.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.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type Source #

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

Eq (URec Float p) Source # 
Instance details

Defined in GHC.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.Generics

data URec Float (p :: k) Source #

Used for marking occurrences of Float#

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" '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
Data Int Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Storable Int Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int Source #

Since: base-2.1

Instance details

Defined in GHC.Bits

FiniteBits Int Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

Bounded Int Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Int Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Int Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Num Int Source #

Since: base-2.1

Instance details

Defined in GHC.Num

Read Int Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Int Source #

Since: base-2.0.1

Instance details

Defined in GHC.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.Real

Show Int Source #

Since: base-2.1

Instance details

Defined in GHC.Show

PrintfArg Int Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

Associated Types

type Rep1 (URec Int) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Int a -> Rep1 (URec Int) a Source #

to1 :: forall (a :: k0). Rep1 (URec Int) a -> URec Int a Source #

Foldable (UInt :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 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.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.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type Source #

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

Eq (URec Int p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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.Generics

type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

data TYPE (a :: RuntimeRep) Source #

Instances

Instances details
Category Op Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

id :: forall (a :: k). Op a a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). Op b c -> Op a b -> Op a c Source #

HasResolution E0 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E0 -> Integer Source #

HasResolution E1 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E1 -> Integer Source #

HasResolution E12 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E12 -> Integer Source #

HasResolution E2 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E2 -> Integer Source #

HasResolution E3 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E3 -> Integer Source #

HasResolution E6 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E6 -> Integer Source #

HasResolution E9 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E9 -> Integer Source #

Generic1 ZipList Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 ZipList :: k -> Type Source #

Methods

from1 :: forall (a :: k). ZipList a -> Rep1 ZipList a Source #

to1 :: forall (a :: k). Rep1 ZipList a -> ZipList a Source #

Generic1 Complex Source # 
Instance details

Defined in Data.Complex

Associated Types

type Rep1 Complex :: k -> Type Source #

Methods

from1 :: forall (a :: k). Complex a -> Rep1 Complex a Source #

to1 :: forall (a :: k). Rep1 Complex a -> Complex a Source #

Generic1 Identity Source # 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity :: k -> Type Source #

Methods

from1 :: forall (a :: k). Identity a -> Rep1 Identity a Source #

to1 :: forall (a :: k). Rep1 Identity a -> Identity a Source #

Generic1 First Source # 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 First :: k -> Type Source #

Methods

from1 :: forall (a :: k). First a -> Rep1 First a Source #

to1 :: forall (a :: k). Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 Last :: k -> Type Source #

Methods

from1 :: forall (a :: k). Last a -> Rep1 Last a Source #

to1 :: forall (a :: k). Rep1 Last a -> Last a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down :: k -> Type Source #

Methods

from1 :: forall (a :: k). Down a -> Rep1 Down a Source #

to1 :: forall (a :: k). Rep1 Down a -> Down a Source #

Generic1 First Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 First :: k -> Type Source #

Methods

from1 :: forall (a :: k). First a -> Rep1 First a Source #

to1 :: forall (a :: k). Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Last :: k -> Type Source #

Methods

from1 :: forall (a :: k). Last a -> Rep1 Last a Source #

to1 :: forall (a :: k). Rep1 Last a -> Last a Source #

Generic1 Max Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Max :: k -> Type Source #

Methods

from1 :: forall (a :: k). Max a -> Rep1 Max a Source #

to1 :: forall (a :: k). Rep1 Max a -> Max a Source #

Generic1 Min Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Min :: k -> Type Source #

Methods

from1 :: forall (a :: k). Min a -> Rep1 Min a Source #

to1 :: forall (a :: k). Rep1 Min a -> Min a Source #

Generic1 WrappedMonoid Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 WrappedMonoid :: k -> Type Source #

Methods

from1 :: forall (a :: k). WrappedMonoid a -> Rep1 WrappedMonoid a Source #

to1 :: forall (a :: k). Rep1 WrappedMonoid a -> WrappedMonoid a Source #

Generic1 Dual Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Dual :: k -> Type Source #

Methods

from1 :: forall (a :: k). Dual a -> Rep1 Dual a Source #

to1 :: forall (a :: k). Rep1 Dual a -> Dual a Source #

Generic1 Product Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type Source #

Methods

from1 :: forall (a :: k). Product a -> Rep1 Product a Source #

to1 :: forall (a :: k). Rep1 Product a -> Product a Source #

Generic1 Sum Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type Source #

Methods

from1 :: forall (a :: k). Sum a -> Rep1 Sum a Source #

to1 :: forall (a :: k). Rep1 Sum a -> Sum a Source #

Generic1 Par1 Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Par1 :: k -> Type Source #

Methods

from1 :: forall (a :: k). Par1 a -> Rep1 Par1 a Source #

to1 :: forall (a :: k). Rep1 Par1 a -> Par1 a Source #

Generic1 NonEmpty Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type Source #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a Source #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a Source #

Generic1 Maybe Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type Source #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a Source #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Solo :: k -> Type Source #

Methods

from1 :: forall (a :: k). Solo a -> Rep1 Solo a Source #

to1 :: forall (a :: k). Rep1 Solo a -> Solo a Source #

Generic1 [] Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 [] :: k -> Type Source #

Methods

from1 :: forall (a :: k). [a] -> Rep1 [] a Source #

to1 :: forall (a :: k). Rep1 [] a -> [a] Source #

Monad m => Category (Kleisli m :: Type -> Type -> Type) Source #

Since: base-3.0

Instance details

Defined in Control.Arrow

Methods

id :: forall (a :: k). Kleisli m a a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). Kleisli m b c -> Kleisli m a b -> Kleisli m a c Source #

Generic1 (WrappedMonad m :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 (WrappedMonad m) :: k -> Type Source #

Methods

from1 :: forall (a :: k). WrappedMonad m a -> Rep1 (WrappedMonad m) a Source #

to1 :: forall (a :: k). Rep1 (WrappedMonad m) a -> WrappedMonad m a Source #

Generic1 (Either a :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Either a) a0 -> Either a a0 Source #

Generic1 (Arg a :: Type -> Type) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 (Arg a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Arg a a0 -> Rep1 (Arg a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Arg a) a0 -> Arg a a0 Source #

Generic1 ((,) a :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,) a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, a0) -> Rep1 ((,) a) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,) a) a0 -> (a, a0) Source #

Category (->) Source #

Since: base-3.0

Instance details

Defined in Control.Category

Methods

id :: forall (a :: k). a -> a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). (b -> c) -> (a -> b) -> a -> c Source #

Generic1 (WrappedArrow a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 (WrappedArrow a b) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source #

to1 :: forall (a0 :: k). Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source #

Generic1 (Kleisli m a :: Type -> Type) Source # 
Instance details

Defined in Control.Arrow

Associated Types

type Rep1 (Kleisli m a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Kleisli m a a0 -> Rep1 (Kleisli m a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Kleisli m a) a0 -> Kleisli m a a0 Source #

Generic1 ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,) a b) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, a0) -> Rep1 ((,,) a b) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,) a b) a0 -> (a, b, a0) Source #

Generic1 ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,) a b c) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, a0) -> Rep1 ((,,,) a b c) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,,) a b c) a0 -> (a, b, c, a0) Source #

Generic1 ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,,) a b c d) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, a0) -> Rep1 ((,,,,) a b c d) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,,,) a b c d) a0 -> (a, b, c, d, a0) Source #

Functor f => Generic1 (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep1 (Compose f g) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). Compose f g a -> Rep1 (Compose f g) a Source #

to1 :: forall (a :: k0). Rep1 (Compose f g) a -> Compose f g a Source #

Functor f => Generic1 (f :.: g :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :.: g) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). (f :.: g) a -> Rep1 (f :.: g) a Source #

to1 :: forall (a :: k0). Rep1 (f :.: g) a -> (f :.: g) a Source #

Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,,,) a b c d e) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, a0) -> Rep1 ((,,,,,) a b c d e) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,) a b c d e f) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, a0) -> Rep1 ((,,,,,,) a b c d e f) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,) a b c d e f g) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, a0) -> Rep1 ((,,,,,,,) a b c d e f g) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,) a b c d e f g h) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,) a b c d e f g h i) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (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 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Bifoldable (Const :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => Const m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Const a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Const a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Const a b -> c Source #

Bifunctor (Const :: Type -> Type -> Type) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d Source #

first :: (a -> b) -> Const a c -> Const b c Source #

second :: (b -> c) -> Const a b -> Const a c Source #

Bitraversable (Const :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source #

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 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 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const a c -> Const b d -> Bool Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) Source #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] Source #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) Source #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS Source #

Show2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS Source #

Contravariant (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' Source #

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

Contravariant (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> U1 a -> U1 a' Source #

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

Contravariant (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> V1 a -> V1 a' Source #

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

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 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 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 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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.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 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.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 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.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.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 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.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 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.Generics

Methods

mzero :: U1 a Source #

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

MonadFail f => MonadFail (Ap f) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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 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 Control.Monad.Fix

Methods

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

MonadZip f => MonadZip (Alt f) Source #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

MonadZip f => MonadZip (Rec1 f) Source #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Bifoldable (K1 i :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => K1 i m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> K1 i a b -> m Source #

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

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

Bifunctor (K1 i :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

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

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

Bitraversable (K1 i :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) Source #

Data t => Data (Proxy t) Source #

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 #

Eq a => Eq1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool Source #

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

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source #

Ord a => Ord1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering Source #

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

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source #

Read a => Read1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source #

Show a => Show1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS Source #

Contravariant (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a0) -> Const a a0 -> Const a a' Source #

(>$) :: b -> Const a b -> Const a a0 Source #

Contravariant f => Contravariant (Alt f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Alt f a -> Alt f a' Source #

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

Contravariant f => Contravariant (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Rec1 f a -> Rec1 f a' Source #

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

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 (Ap f) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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.Generics

Alternative f => Alternative (Rec1 f) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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 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 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 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.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.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.1

Instance details

Defined in 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 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 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.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.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.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.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.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.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.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.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 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 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.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 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 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.Generics

Methods

mzero :: Rec1 f a Source #

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

(MonadFix f, MonadFix g) => MonadFix (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mfix :: (a -> Product f g a) -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

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

(MonadZip f, MonadZip g) => MonadZip (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzip :: Product f g a -> Product f g b -> Product f g (a, b) Source #

mzipWith :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c Source #

munzip :: Product f g (a, b) -> (Product f g a, Product f g b) Source #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

(Data (f a), Data a, Typeable f) => Data (Ap f a) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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 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 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 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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

fold :: Monoid m => Product f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Product f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Product f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Product f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Product f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Product f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Product f g a -> b Source #

foldr1 :: (a -> a -> a) -> Product f g a -> a Source #

foldl1 :: (a -> a -> a) -> Product f g a -> a Source #

toList :: Product f g a -> [a] Source #

null :: Product f g a -> Bool Source #

length :: Product f g a -> Int Source #

elem :: Eq a => a -> Product f g a -> Bool Source #

maximum :: Ord a => Product f g a -> a Source #

minimum :: Ord a => Product f g a -> a Source #

sum :: Num a => Product f g a -> a Source #

product :: Num a => Product f g a -> a Source #

(Foldable f, Foldable g) => Foldable (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

fold :: Monoid m => Sum f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Sum f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Sum f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Sum f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Sum f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Sum f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Sum f g a -> b Source #

foldr1 :: (a -> a -> a) -> Sum f g a -> a Source #

foldl1 :: (a -> a -> a) -> Sum f g a -> a Source #

toList :: Sum f g a -> [a] Source #

null :: Sum f g a -> Bool Source #

length :: Sum f g a -> Int Source #

elem :: Eq a => a -> Sum f g a -> Bool Source #

maximum :: Ord a => Sum f g a -> a Source #

minimum :: Ord a => Sum f g a -> a Source #

sum :: Num a => Sum f g a -> a Source #

product :: Num a => Sum f g a -> a Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 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 #

(Eq1 f, Eq1 g) => Eq1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftEq :: (a -> b -> Bool) -> Product f g a -> Product f g b -> Bool Source #

(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftEq :: (a -> b -> Bool) -> Sum f g a -> Sum f g b -> Bool Source #

(Ord1 f, Ord1 g) => Ord1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftCompare :: (a -> b -> Ordering) -> Product f g a -> Product f g b -> Ordering Source #

(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftCompare :: (a -> b -> Ordering) -> Sum f g a -> Sum f g b -> Ordering Source #

(Read1 f, Read1 g) => Read1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] Source #

(Read1 f, Read1 g) => Read1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Sum f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] Source #

(Show1 f, Show1 g) => Show1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product f g a] -> ShowS Source #

(Show1 f, Show1 g) => Show1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Sum f g a] -> ShowS Source #

(Contravariant f, Contravariant g) => Contravariant (Product f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Product f g a -> Product f g a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (Sum f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Sum f g a -> Sum f g a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (f :*: g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :*: g) a -> (f :*: g) a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (f :+: g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :+: g) a -> (f :+: g) a' Source #

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

Contravariant (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> K1 i c a -> K1 i c a' Source #

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

(Traversable f, Traversable g) => Traversable (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) Source #

sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) Source #

mapM :: Monad m => (a -> m b) -> Product f g a -> m (Product f g b) Source #

sequence :: Monad m => Product f g (m a) -> m (Product f g a) Source #

(Traversable f, Traversable g) => Traversable (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Sum f g a -> f0 (Sum f g b) Source #

sequenceA :: Applicative f0 => Sum f g (f0 a) -> f0 (Sum f g a) Source #

mapM :: Monad m => (a -> m b) -> Sum f g a -> m (Sum f g b) Source #

sequence :: Monad m => Sum f g (m a) -> m (Sum f g a) Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 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 #

(Alternative f, Alternative g) => Alternative (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

empty :: Product f g a Source #

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

pure :: a -> Product f g a Source #

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

(Functor f, Functor g) => Functor (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

return :: a -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzero :: Product f g a Source #

mplus :: Product f g a -> Product f g a -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 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 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 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 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 #

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

Since: base-4.12.0.0

Instance details

Defined in 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 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

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

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

munzip :: M1 i c f (a, b) -> (M1 i c f a, M1 i c f b) 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 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 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 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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

fold :: Monoid m => Compose f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Compose f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Compose f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Compose f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Compose f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Compose f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Compose f g a -> b Source #

foldr1 :: (a -> a -> a) -> Compose f g a -> a Source #

foldl1 :: (a -> a -> a) -> Compose f g a -> a Source #

toList :: Compose f g a -> [a] Source #

null :: Compose f g a -> Bool Source #

length :: Compose f g a -> Int Source #

elem :: Eq a => a -> Compose f g a -> Bool Source #

maximum :: Ord a => Compose f g a -> a Source #

minimum :: Ord a => Compose f g a -> a Source #

sum :: Num a => Compose f g a -> a Source #

product :: Num a => Compose f g a -> a Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 #

(Eq1 f, Eq1 g) => Eq1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftEq :: (a -> b -> Bool) -> Compose f g a -> Compose f g b -> Bool Source #

(Ord1 f, Ord1 g) => Ord1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftCompare :: (a -> b -> Ordering) -> Compose f g a -> Compose f g b -> Ordering Source #

(Read1 f, Read1 g) => Read1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] Source #

(Show1 f, Show1 g) => Show1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose f g a] -> ShowS Source #

(Functor f, Contravariant g) => Contravariant (Compose f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Compose f g a -> Compose f g a' Source #

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

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

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :.: g) a -> (f :.: g) a' Source #

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

Contravariant f => Contravariant (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

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

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

(Traversable f, Traversable g) => Traversable (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source #

sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 (Compose f g a) Source #

mapM :: Monad m => (a -> m b) -> Compose f g a -> m (Compose f g b) Source #

sequence :: Monad m => Compose f g (m a) -> m (Compose f g a) Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 #

(Alternative f, Applicative g) => Alternative (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

empty :: Compose f g a Source #

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

pure :: a -> Compose f g a Source #

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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.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 #

(Read1 f, Read1 g, Read a) => Read (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

(Read1 f, Read1 g, Read a) => Read (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

readsPrec :: Int -> ReadS (Sum f g a) Source #

readList :: ReadS [Sum f g a] Source #

readPrec :: ReadPrec (Sum f g a) Source #

readListPrec :: ReadPrec [Sum f g a] Source #

(Show1 f, Show1 g, Show a) => Show (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS Source #

show :: Product f g a -> String Source #

showList :: [Product f g a] -> ShowS Source #

(Show1 f, Show1 g, Show a) => Show (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS Source #

show :: Sum f g a -> String Source #

showList :: [Sum f g a] -> ShowS Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

(==) :: Product f g a -> Product f g a -> Bool Source #

(/=) :: Product f g a -> Product f g a -> Bool Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

(==) :: Sum f g a -> Sum f g a -> Bool Source #

(/=) :: Sum f g a -> Sum f g a -> Bool Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

compare :: Product f g a -> Product f g a -> Ordering Source #

(<) :: Product f g a -> Product f g a -> Bool Source #

(<=) :: Product f g a -> Product f g a -> Bool Source #

(>) :: Product f g a -> Product f g a -> Bool Source #

(>=) :: Product f g a -> Product f g a -> Bool Source #

max :: Product f g a -> Product f g a -> Product f g a Source #

min :: Product f g a -> Product f g a -> Product f g a Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

compare :: Sum f g a -> Sum f g a -> Ordering Source #

(<) :: Sum f g a -> Sum f g a -> Bool Source #

(<=) :: Sum f g a -> Sum f g a -> Bool Source #

(>) :: Sum f g a -> Sum f g a -> Bool Source #

(>=) :: Sum f g a -> Sum f g a -> Bool Source #

max :: Sum f g a -> Sum f g a -> Sum f g a Source #

min :: Sum f g a -> Sum f g a -> Sum f g 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 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 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 #

(Read1 f, Read1 g, Read a) => Read (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

(Show1 f, Show1 g, Show a) => Show (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS Source #

show :: Compose f g a -> String Source #

showList :: [Compose f g a] -> ShowS Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(==) :: Compose f g a -> Compose f g a -> Bool Source #

(/=) :: Compose f g a -> Compose f g a -> Bool Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

compare :: Compose f g a -> Compose f g a -> Ordering Source #

(<) :: Compose f g a -> Compose f g a -> Bool Source #

(<=) :: Compose f g a -> Compose f g a -> Bool Source #

(>) :: Compose f g a -> Compose f g a -> Bool Source #

(>=) :: Compose f g a -> Compose f g a -> Bool Source #

max :: Compose f g a -> Compose f g a -> Compose f g a Source #

min :: Compose f g a -> Compose f g a -> Compose f g a Source #

type Rep1 ZipList Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 ZipList = D1 ('MetaData "ZipList" "Control.Applicative" "base" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
type Rep1 Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

type Rep1 Identity Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" '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 Data.Monoid

type Rep1 First = D1 ('MetaData "First" "Data.Monoid" "base" '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 Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "Data.Monoid" "base" '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.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 First = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Last = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Max = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Min = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 WrappedMonoid Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 WrappedMonoid = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Dual Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" '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 Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" '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 Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Par1 Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 NonEmpty Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 Maybe Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" '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.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "Solo" '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.Generics

type Rep1 (WrappedMonad m :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m)))
type Rep1 (Either a :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Arg a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 ((,) a :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (WrappedArrow a b :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b))))
type Rep1 (Kleisli m a :: Type -> Type) Source #

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "Control.Arrow" "base" '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.Generics

type Rep1 ((,,,) a b c :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 ((,,,,) a b c d :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Compose f g :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

type Rep1 (Compose f g :: k -> Type) = D1 ('MetaData "Compose" "Data.Functor.Compose" "base" 'True) (C1 ('MetaCons "Compose" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))
type Rep1 (f :.: g :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Generics" "base" '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.Generics

type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.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.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.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.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.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.Generics

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.Generics

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.Generics

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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 Bool Source #

Constructors

False 
True 

Instances

Instances details
Data Bool Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Storable Bool Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Bool Source #

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in GHC.Bits

FiniteBits Bool Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Bits

Bounded Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Generic Bool Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type Source #

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

Ix Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Read Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show Bool Source #

Since: base-2.1

Instance details

Defined in GHC.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.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 is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

Constructors

C# Char# 

Instances

Instances details
Data Char Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Storable Char Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bounded Char Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Char Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Char Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Read Char Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show Char Source #

Since: base-2.1

Instance details

Defined in GHC.Show

IsChar Char Source #

Since: base-2.1

Instance details

Defined in Text.Printf

PrintfArg Char Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

Generic1 (URec Char :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Char) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Char a -> Rep1 (URec Char) a Source #

to1 :: forall (a :: k0). Rep1 (URec Char) a -> URec Char a Source #

Foldable (UChar :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 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.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.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type Source #

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

Eq (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.Generics

data URec Char (p :: k) = UChar {}
type Compare (a :: Char) (b :: Char) Source # 
Instance details

Defined in 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.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Generics" "base" '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 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 #

Storable Double Source #

Since: base-2.1

Instance details

Defined in Foreign.Storable

Enum Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Floating Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFloat Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Num Double Source #

Note that due to the presence of NaN, not all elements of Double have an additive inverse.

>>> 0/0 + (negate 0/0 :: Double)
NaN

Also note that due to the presence of -0, Double's Num instance doesn't have an additive identity

>>> 0 + (-0 :: Double)
0.0

Since: base-2.1

Instance details

Defined in GHC.Float

Read Double Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Fractional Double Source #

Note that due to the presence of NaN, not all elements of Double have an multiplicative inverse.

>>> 0/0 * (recip 0/0 :: Double)
NaN

Since: base-2.1

Instance details

Defined in GHC.Float

Real Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

RealFrac Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

Show Double Source #

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Double Source #

Since: base-2.1

Instance details

Defined in Text.Printf

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

Note that due to the presence of NaN, Double's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord's operator interactions are not respected by Double's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Generic1 (URec Double :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Double) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec Double a -> Rep1 (URec Double) a Source #

to1 :: forall (a :: k0). Rep1 (URec Double) a -> URec Double a Source #

Foldable (UDouble :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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 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.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.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type Source #

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

Eq (URec Double p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

data URec Double (p :: k) Source #

Used for marking occurrences of Double#

Since: base-4.9.0.0

Instance details

Defined in GHC.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.Generics

type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" '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.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

data Ordering Source #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Data Ordering Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Monoid Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Semigroup Ordering Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Bounded Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Generic Ordering Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type Source #

Ix Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Read Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.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.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-4.7.0.0

data Symbol Source #

(Kind) This is the kind of type-level symbols. Declared here because class IP needs it

Instances

Instances details
type Compare (a :: Symbol) (b :: Symbol) Source # 
Instance details

Defined in 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.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.Enum

Enum Levity Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Enum

Show Levity Source #

Since: base-4.15.0.0

Instance details

Defined in GHC.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.Enum

Enum VecCount Source #

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Show VecCount Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.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.Enum

Enum VecElem Source #

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Show VecElem Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

data Constraint Source #

The kind of constraints, like Show a

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.

Constructors

SPEC 
SPEC2 

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

pattern TrNameD :: [Char] -> TrName Source #

Dynamic

pattern TrNameS :: Addr# -> TrName Source #

Static

isTrue# :: Int# -> Bool Source #

Alias for tagToEnum#. Returns True if its parameter is 1# and False if it is 0#.

Legacy interface for arrays of arrays

Primitive operations

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:

  • 'newByteArray#': Create an unpinned array.
  • 'newPinnedByteArray#': This will create a pinned array,
  • 'newAlignedPinnedByteArray#': This will create a pinned array, with a custom alignment.

Unpinned arrays can be moved around during garbage collection, so you must not store or pass pointers to these values if there is a chance for the garbage collector to kick in. That said, even unpinned arrays can be passed to unsafe FFI calls, because no garbage collection happens during these unsafe calls (see Guaranteed Call Safety in the GHC Manual). For safe FFI calls, byte arrays must be not only pinned, but also kept alive by means of the keepAlive# function for the duration of a call (that's because garbage collection cannot move a pinned array, but is free to scrap it altogether).

data 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 a 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 this module for more detailed explanations.

data TYPE (a :: RuntimeRep) Source #

Instances

Instances details
Category Op Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

id :: forall (a :: k). Op a a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). Op b c -> Op a b -> Op a c Source #

HasResolution E0 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E0 -> Integer Source #

HasResolution E1 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E1 -> Integer Source #

HasResolution E12 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E12 -> Integer Source #

HasResolution E2 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E2 -> Integer Source #

HasResolution E3 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E3 -> Integer Source #

HasResolution E6 Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

resolution :: p E6 -> Integer Source #

HasResolution E9 Source #

Since: base-4.1.0.0

Instance details

Defined in Data.Fixed

Methods

resolution :: p E9 -> Integer Source #

Generic1 ZipList Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 ZipList :: k -> Type Source #

Methods

from1 :: forall (a :: k). ZipList a -> Rep1 ZipList a Source #

to1 :: forall (a :: k). Rep1 ZipList a -> ZipList a Source #

Generic1 Complex Source # 
Instance details

Defined in Data.Complex

Associated Types

type Rep1 Complex :: k -> Type Source #

Methods

from1 :: forall (a :: k). Complex a -> Rep1 Complex a Source #

to1 :: forall (a :: k). Rep1 Complex a -> Complex a Source #

Generic1 Identity Source # 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity :: k -> Type Source #

Methods

from1 :: forall (a :: k). Identity a -> Rep1 Identity a Source #

to1 :: forall (a :: k). Rep1 Identity a -> Identity a Source #

Generic1 First Source # 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 First :: k -> Type Source #

Methods

from1 :: forall (a :: k). First a -> Rep1 First a Source #

to1 :: forall (a :: k). Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 Last :: k -> Type Source #

Methods

from1 :: forall (a :: k). Last a -> Rep1 Last a Source #

to1 :: forall (a :: k). Rep1 Last a -> Last a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down :: k -> Type Source #

Methods

from1 :: forall (a :: k). Down a -> Rep1 Down a Source #

to1 :: forall (a :: k). Rep1 Down a -> Down a Source #

Generic1 First Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 First :: k -> Type Source #

Methods

from1 :: forall (a :: k). First a -> Rep1 First a Source #

to1 :: forall (a :: k). Rep1 First a -> First a Source #

Generic1 Last Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Last :: k -> Type Source #

Methods

from1 :: forall (a :: k). Last a -> Rep1 Last a Source #

to1 :: forall (a :: k). Rep1 Last a -> Last a Source #

Generic1 Max Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Max :: k -> Type Source #

Methods

from1 :: forall (a :: k). Max a -> Rep1 Max a Source #

to1 :: forall (a :: k). Rep1 Max a -> Max a Source #

Generic1 Min Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 Min :: k -> Type Source #

Methods

from1 :: forall (a :: k). Min a -> Rep1 Min a Source #

to1 :: forall (a :: k). Rep1 Min a -> Min a Source #

Generic1 WrappedMonoid Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 WrappedMonoid :: k -> Type Source #

Methods

from1 :: forall (a :: k). WrappedMonoid a -> Rep1 WrappedMonoid a Source #

to1 :: forall (a :: k). Rep1 WrappedMonoid a -> WrappedMonoid a Source #

Generic1 Dual Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Dual :: k -> Type Source #

Methods

from1 :: forall (a :: k). Dual a -> Rep1 Dual a Source #

to1 :: forall (a :: k). Rep1 Dual a -> Dual a Source #

Generic1 Product Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type Source #

Methods

from1 :: forall (a :: k). Product a -> Rep1 Product a Source #

to1 :: forall (a :: k). Rep1 Product a -> Product a Source #

Generic1 Sum Source # 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type Source #

Methods

from1 :: forall (a :: k). Sum a -> Rep1 Sum a Source #

to1 :: forall (a :: k). Rep1 Sum a -> Sum a Source #

Generic1 Par1 Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Par1 :: k -> Type Source #

Methods

from1 :: forall (a :: k). Par1 a -> Rep1 Par1 a Source #

to1 :: forall (a :: k). Rep1 Par1 a -> Par1 a Source #

Generic1 NonEmpty Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type Source #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a Source #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a Source #

Generic1 Maybe Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type Source #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a Source #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Solo :: k -> Type Source #

Methods

from1 :: forall (a :: k). Solo a -> Rep1 Solo a Source #

to1 :: forall (a :: k). Rep1 Solo a -> Solo a Source #

Generic1 [] Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 [] :: k -> Type Source #

Methods

from1 :: forall (a :: k). [a] -> Rep1 [] a Source #

to1 :: forall (a :: k). Rep1 [] a -> [a] Source #

Monad m => Category (Kleisli m :: Type -> Type -> Type) Source #

Since: base-3.0

Instance details

Defined in Control.Arrow

Methods

id :: forall (a :: k). Kleisli m a a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). Kleisli m b c -> Kleisli m a b -> Kleisli m a c Source #

Generic1 (WrappedMonad m :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 (WrappedMonad m) :: k -> Type Source #

Methods

from1 :: forall (a :: k). WrappedMonad m a -> Rep1 (WrappedMonad m) a Source #

to1 :: forall (a :: k). Rep1 (WrappedMonad m) a -> WrappedMonad m a Source #

Generic1 (Either a :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Either a) a0 -> Either a a0 Source #

Generic1 (Arg a :: Type -> Type) Source # 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep1 (Arg a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Arg a a0 -> Rep1 (Arg a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Arg a) a0 -> Arg a a0 Source #

Generic1 ((,) a :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,) a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, a0) -> Rep1 ((,) a) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,) a) a0 -> (a, a0) Source #

Category (->) Source #

Since: base-3.0

Instance details

Defined in Control.Category

Methods

id :: forall (a :: k). a -> a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). (b -> c) -> (a -> b) -> a -> c Source #

Generic1 (WrappedArrow a b :: Type -> Type) Source # 
Instance details

Defined in Control.Applicative

Associated Types

type Rep1 (WrappedArrow a b) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source #

to1 :: forall (a0 :: k). Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source #

Generic1 (Kleisli m a :: Type -> Type) Source # 
Instance details

Defined in Control.Arrow

Associated Types

type Rep1 (Kleisli m a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Kleisli m a a0 -> Rep1 (Kleisli m a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Kleisli m a) a0 -> Kleisli m a a0 Source #

Generic1 ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,) a b) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, a0) -> Rep1 ((,,) a b) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,) a b) a0 -> (a, b, a0) Source #

Generic1 ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,) a b c) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, a0) -> Rep1 ((,,,) a b c) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,,) a b c) a0 -> (a, b, c, a0) Source #

Generic1 ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,,) a b c d) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, a0) -> Rep1 ((,,,,) a b c d) a0 Source #

to1 :: forall (a0 :: k). Rep1 ((,,,,) a b c d) a0 -> (a, b, c, d, a0) Source #

Functor f => Generic1 (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep1 (Compose f g) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). Compose f g a -> Rep1 (Compose f g) a Source #

to1 :: forall (a :: k0). Rep1 (Compose f g) a -> Compose f g a Source #

Functor f => Generic1 (f :.: g :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :.: g) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). (f :.: g) a -> Rep1 (f :.: g) a Source #

to1 :: forall (a :: k0). Rep1 (f :.: g) a -> (f :.: g) a Source #

Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ((,,,,,) a b c d e) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, a0) -> Rep1 ((,,,,,) a b c d e) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,) a b c d e f) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, a0) -> Rep1 ((,,,,,,) a b c d e f) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,) a b c d e f g) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, a0) -> Rep1 ((,,,,,,,) a b c d e f g) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,) a b c d e f g h) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, h, a0) -> Rep1 ((,,,,,,,,) a b c d e f g h) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,) a b c d e f g h i) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (a, b, c, d, e, f, g, h, i, a0) -> Rep1 ((,,,,,,,,,) a b c d e f g h i) a0 Source #

to1 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). (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 :: forall (a0 :: k). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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.Generics

Associated Types

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k0). (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 :: forall (a0 :: k0). 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Bifoldable (Const :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => Const m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Const a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Const a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Const a b -> c Source #

Bifunctor (Const :: Type -> Type -> Type) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d Source #

first :: (a -> b) -> Const a c -> Const b c Source #

second :: (b -> c) -> Const a b -> Const a c Source #

Bitraversable (Const :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source #

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 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 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Eq2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const a c -> Const b d -> Bool Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) Source #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] Source #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) Source #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS Source #

Show2 (Const :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS Source #

Contravariant (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' Source #

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

Contravariant (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> U1 a -> U1 a' Source #

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

Contravariant (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> V1 a -> V1 a' Source #

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

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 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 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 (Proxy :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in 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.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 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.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 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.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.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 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.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 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.Generics

Methods

mzero :: U1 a Source #

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

MonadFail f => MonadFail (Ap f) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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 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 Control.Monad.Fix

Methods

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

MonadZip f => MonadZip (Alt f) Source #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

MonadZip f => MonadZip (Rec1 f) Source #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Bifoldable (K1 i :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => K1 i m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> K1 i a b -> m Source #

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

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

Bifunctor (K1 i :: Type -> Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

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

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

Bitraversable (K1 i :: Type -> Type -> Type) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) Source #

Data t => Data (Proxy t) Source #

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 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 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 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 #

Eq a => Eq1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool Source #

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

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool Source #

Ord a => Ord1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering Source #

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

Since: base-4.17.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering Source #

Read a => Read1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source #

Show a => Show1 (Const a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS Source #

Contravariant (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a0) -> Const a a0 -> Const a a' Source #

(>$) :: b -> Const a b -> Const a a0 Source #

Contravariant f => Contravariant (Alt f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Alt f a -> Alt f a' Source #

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

Contravariant f => Contravariant (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Rec1 f a -> Rec1 f a' Source #

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

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

Since: base-4.7.0.0

Instance details

Defined in 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 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 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 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 (Ap f) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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.Generics

Alternative f => Alternative (Rec1 f) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.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 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 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 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.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.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.1

Instance details

Defined in 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 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 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.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.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.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.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.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.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.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.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 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 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.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 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 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.Generics

Methods

mzero :: Rec1 f a Source #

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

(MonadFix f, MonadFix g) => MonadFix (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mfix :: (a -> Product f g a) -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

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

(MonadZip f, MonadZip g) => MonadZip (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzip :: Product f g a -> Product f g b -> Product f g (a, b) Source #

mzipWith :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c Source #

munzip :: Product f g (a, b) -> (Product f g a, Product f g b) Source #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

(Data (f a), Data a, Typeable f) => Data (Ap f a) Source #

Since: base-4.12.0.0

Instance details

Defined in 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 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 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 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 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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

fold :: Monoid m => Product f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Product f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Product f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Product f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Product f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Product f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Product f g a -> b Source #

foldr1 :: (a -> a -> a) -> Product f g a -> a Source #

foldl1 :: (a -> a -> a) -> Product f g a -> a Source #

toList :: Product f g a -> [a] Source #

null :: Product f g a -> Bool Source #

length :: Product f g a -> Int Source #

elem :: Eq a => a -> Product f g a -> Bool Source #

maximum :: Ord a => Product f g a -> a Source #

minimum :: Ord a => Product f g a -> a Source #

sum :: Num a => Product f g a -> a Source #

product :: Num a => Product f g a -> a Source #

(Foldable f, Foldable g) => Foldable (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

fold :: Monoid m => Sum f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Sum f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Sum f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Sum f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Sum f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Sum f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Sum f g a -> b Source #

foldr1 :: (a -> a -> a) -> Sum f g a -> a Source #

foldl1 :: (a -> a -> a) -> Sum f g a -> a Source #

toList :: Sum f g a -> [a] Source #

null :: Sum f g a -> Bool Source #

length :: Sum f g a -> Int Source #

elem :: Eq a => a -> Sum f g a -> Bool Source #

maximum :: Ord a => Sum f g a -> a Source #

minimum :: Ord a => Sum f g a -> a Source #

sum :: Num a => Sum f g a -> a Source #

product :: Num a => Sum f g a -> a Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 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 #

(Eq1 f, Eq1 g) => Eq1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftEq :: (a -> b -> Bool) -> Product f g a -> Product f g b -> Bool Source #

(Eq1 f, Eq1 g) => Eq1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftEq :: (a -> b -> Bool) -> Sum f g a -> Sum f g b -> Bool Source #

(Ord1 f, Ord1 g) => Ord1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftCompare :: (a -> b -> Ordering) -> Product f g a -> Product f g b -> Ordering Source #

(Ord1 f, Ord1 g) => Ord1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftCompare :: (a -> b -> Ordering) -> Sum f g a -> Sum f g b -> Ordering Source #

(Read1 f, Read1 g) => Read1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] Source #

(Read1 f, Read1 g) => Read1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Sum f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] Source #

(Show1 f, Show1 g) => Show1 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product f g a] -> ShowS Source #

(Show1 f, Show1 g) => Show1 (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Sum f g a] -> ShowS Source #

(Contravariant f, Contravariant g) => Contravariant (Product f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Product f g a -> Product f g a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (Sum f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Sum f g a -> Sum f g a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (f :*: g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :*: g) a -> (f :*: g) a' Source #

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

(Contravariant f, Contravariant g) => Contravariant (f :+: g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :+: g) a -> (f :+: g) a' Source #

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

Contravariant (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> K1 i c a -> K1 i c a' Source #

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

(Traversable f, Traversable g) => Traversable (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) Source #

sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) Source #

mapM :: Monad m => (a -> m b) -> Product f g a -> m (Product f g b) Source #

sequence :: Monad m => Product f g (m a) -> m (Product f g a) Source #

(Traversable f, Traversable g) => Traversable (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Sum f g a -> f0 (Sum f g b) Source #

sequenceA :: Applicative f0 => Sum f g (f0 a) -> f0 (Sum f g a) Source #

mapM :: Monad m => (a -> m b) -> Sum f g a -> m (Sum f g b) Source #

sequence :: Monad m => Sum f g (m a) -> m (Sum f g a) Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 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 #

(Alternative f, Alternative g) => Alternative (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

empty :: Product f g a Source #

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

pure :: a -> Product f g a Source #

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

(Functor f, Functor g) => Functor (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

return :: a -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzero :: Product f g a Source #

mplus :: Product f g a -> Product f g a -> Product f g a Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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 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 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 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 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 #

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

Since: base-4.12.0.0

Instance details

Defined in 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 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 #

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

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

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

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

munzip :: M1 i c f (a, b) -> (M1 i c f a, M1 i c f b) 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 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 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 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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

fold :: Monoid m => Compose f g m -> m Source #

foldMap :: Monoid m => (a -> m) -> Compose f g a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Compose f g a -> m Source #

foldr :: (a -> b -> b) -> b -> Compose f g a -> b Source #

foldr' :: (a -> b -> b) -> b -> Compose f g a -> b Source #

foldl :: (b -> a -> b) -> b -> Compose f g a -> b Source #

foldl' :: (b -> a -> b) -> b -> Compose f g a -> b Source #

foldr1 :: (a -> a -> a) -> Compose f g a -> a Source #

foldl1 :: (a -> a -> a) -> Compose f g a -> a Source #

toList :: Compose f g a -> [a] Source #

null :: Compose f g a -> Bool Source #

length :: Compose f g a -> Int Source #

elem :: Eq a => a -> Compose f g a -> Bool Source #

maximum :: Ord a => Compose f g a -> a Source #

minimum :: Ord a => Compose f g a -> a Source #

sum :: Num a => Compose f g a -> a Source #

product :: Num a => Compose f g a -> a Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 #

(Eq1 f, Eq1 g) => Eq1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftEq :: (a -> b -> Bool) -> Compose f g a -> Compose f g b -> Bool Source #

(Ord1 f, Ord1 g) => Ord1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftCompare :: (a -> b -> Ordering) -> Compose f g a -> Compose f g b -> Ordering Source #

(Read1 f, Read1 g) => Read1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose f g a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose f g a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] Source #

(Show1 f, Show1 g) => Show1 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose f g a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose f g a] -> ShowS Source #

(Functor f, Contravariant g) => Contravariant (Compose f g) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Compose f g a -> Compose f g a' Source #

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

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

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> (f :.: g) a -> (f :.: g) a' Source #

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

Contravariant f => Contravariant (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

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

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

(Traversable f, Traversable g) => Traversable (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source #

sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 (Compose f g a) Source #

mapM :: Monad m => (a -> m b) -> Compose f g a -> m (Compose f g b) Source #

sequence :: Monad m => Compose f g (m a) -> m (Compose f g a) Source #

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

Since: base-4.9.0.0

Instance details

Defined in 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 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 #

(Alternative f, Applicative g) => Alternative (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

empty :: Compose f g a Source #

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

pure :: a -> Compose f g a Source #

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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 (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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.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.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 #

(Read1 f, Read1 g, Read a) => Read (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

(Read1 f, Read1 g, Read a) => Read (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

readsPrec :: Int -> ReadS (Sum f g a) Source #

readList :: ReadS [Sum f g a] Source #

readPrec :: ReadPrec (Sum f g a) Source #

readListPrec :: ReadPrec [Sum f g a] Source #

(Show1 f, Show1 g, Show a) => Show (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS Source #

show :: Product f g a -> String Source #

showList :: [Product f g a] -> ShowS Source #

(Show1 f, Show1 g, Show a) => Show (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS Source #

show :: Sum f g a -> String Source #

showList :: [Sum f g a] -> ShowS Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

(==) :: Product f g a -> Product f g a -> Bool Source #

(/=) :: Product f g a -> Product f g a -> Bool Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

(==) :: Sum f g a -> Sum f g a -> Bool Source #

(/=) :: Sum f g a -> Sum f g a -> Bool Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

compare :: Product f g a -> Product f g a -> Ordering Source #

(<) :: Product f g a -> Product f g a -> Bool Source #

(<=) :: Product f g a -> Product f g a -> Bool Source #

(>) :: Product f g a -> Product f g a -> Bool Source #

(>=) :: Product f g a -> Product f g a -> Bool Source #

max :: Product f g a -> Product f g a -> Product f g a Source #

min :: Product f g a -> Product f g a -> Product f g a Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

compare :: Sum f g a -> Sum f g a -> Ordering Source #

(<) :: Sum f g a -> Sum f g a -> Bool Source #

(<=) :: Sum f g a -> Sum f g a -> Bool Source #

(>) :: Sum f g a -> Sum f g a -> Bool Source #

(>=) :: Sum f g a -> Sum f g a -> Bool Source #

max :: Sum f g a -> Sum f g a -> Sum f g a Source #

min :: Sum f g a -> Sum f g a -> Sum f g 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 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 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 #

(Read1 f, Read1 g, Read a) => Read (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

(Show1 f, Show1 g, Show a) => Show (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS Source #

show :: Compose f g a -> String Source #

showList :: [Compose f g a] -> ShowS Source #

(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(==) :: Compose f g a -> Compose f g a -> Bool Source #

(/=) :: Compose f g a -> Compose f g a -> Bool Source #

(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

compare :: Compose f g a -> Compose f g a -> Ordering Source #

(<) :: Compose f g a -> Compose f g a -> Bool Source #

(<=) :: Compose f g a -> Compose f g a -> Bool Source #

(>) :: Compose f g a -> Compose f g a -> Bool Source #

(>=) :: Compose f g a -> Compose f g a -> Bool Source #

max :: Compose f g a -> Compose f g a -> Compose f g a Source #

min :: Compose f g a -> Compose f g a -> Compose f g a Source #

type Rep1 ZipList Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 ZipList = D1 ('MetaData "ZipList" "Control.Applicative" "base" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 [])))
type Rep1 Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

type Rep1 Identity Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" '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 Data.Monoid

type Rep1 First = D1 ('MetaData "First" "Data.Monoid" "base" '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 Data.Monoid

type Rep1 Last = D1 ('MetaData "Last" "Data.Monoid" "base" '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.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 First = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Last = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Max = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 Min = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 WrappedMonoid Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 WrappedMonoid = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Dual Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" '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 Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" '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 Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 Par1 Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 Par1 = D1 ('MetaData "Par1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep1 NonEmpty Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 Maybe Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" '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.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "Solo" '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.Generics

type Rep1 (WrappedMonad m :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m)))
type Rep1 (Either a :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Arg a :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep1 ((,) a :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (WrappedArrow a b :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b))))
type Rep1 (Kleisli m a :: Type -> Type) Source #

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

type Rep1 (Kleisli m a :: Type -> Type) = D1 ('MetaData "Kleisli" "Control.Arrow" "base" '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.Generics

type Rep1 ((,,,) a b c :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 ((,,,,) a b c d :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Compose f g :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

type Rep1 (Compose f g :: k -> Type) = D1 ('MetaData "Compose" "Data.Functor.Compose" "base" 'True) (C1 ('MetaCons "Compose" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 g)))
type Rep1 (f :.: g :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (f :.: g :: k -> Type) = D1 ('MetaData ":.:" "GHC.Generics" "base" '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.Generics

type Rep1 ((,,,,,,) a b c d e f :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.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.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.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.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.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.Generics

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.Generics

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.Generics

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "(,,,,,,,,,,,,,,)" "GHC.Tuple" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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 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 Control.Category

Methods

id :: forall (a :: k). a -> a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). (b -> c) -> (a -> b) -> a -> c Source #

Arrow (->) Source #

Since: base-2.1

Instance details

Defined in 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.1

Instance details

Defined in Control.Arrow

Methods

app :: (b -> c, b) -> c Source #

ArrowChoice (->) Source #

Since: base-2.1

Instance details

Defined in 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.1

Instance details

Defined in Control.Arrow

Methods

loop :: ((b, d) -> (c, d)) -> b -> c Source #

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

Since: base-2.1

Instance details

Defined in GHC.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.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 #

Show (a -> b) Source #

Since: base-2.1

Instance details

Defined in Text.Show.Functions

Methods

showsPrec :: Int -> (a -> b) -> ShowS Source #

show :: (a -> b) -> String Source #

showList :: [a -> b] -> ShowS Source #

(PrintfArg a, HPrintfType r) => HPrintfType (a -> r) Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Methods

hspr :: Handle -> String -> [UPrintf] -> a -> r

(PrintfArg a, PrintfType r) => PrintfType (a -> r) Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Methods

spr :: String -> [UPrintf] -> a -> r

MonadFix ((->) r) Source #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

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

Applicative ((->) r) Source #

Since: base-2.1

Instance details

Defined in GHC.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.1

Instance details

Defined in GHC.Base

Methods

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

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

Monad ((->) r) Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

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

data Int8X16# :: TYPE ('VecRep 'Vec16 'Int8ElemRep) Source #

Warning: this is only available on LLVM.

data Int16X8# :: TYPE ('VecRep 'Vec8 'Int16ElemRep) Source #

Warning: this is only available on LLVM.

data Int32X4# :: TYPE ('VecRep 'Vec4 'Int32ElemRep) Source #

Warning: this is only available on LLVM.

data Int64X2# :: TYPE ('VecRep 'Vec2 'Int64ElemRep) Source #

Warning: this is only available on LLVM.

data Int8X32# :: TYPE ('VecRep 'Vec32 'Int8ElemRep) Source #

Warning: this is only available on LLVM.

data Int16X16# :: TYPE ('VecRep 'Vec16 'Int16ElemRep) Source #

Warning: this is only available on LLVM.

data Int32X8# :: TYPE ('VecRep 'Vec8 'Int32ElemRep) Source #

Warning: this is only available on LLVM.

data Int64X4# :: TYPE ('VecRep 'Vec4 'Int64ElemRep) Source #

Warning: this is only available on LLVM.

data Int8X64# :: TYPE ('VecRep 'Vec64 'Int8ElemRep) Source #

Warning: this is only available on LLVM.

data Int16X32# :: TYPE ('VecRep 'Vec32 'Int16ElemRep) Source #

Warning: this is only available on LLVM.

data Int32X16# :: TYPE ('VecRep 'Vec16 'Int32ElemRep) Source #

Warning: this is only available on LLVM.

data Int64X8# :: TYPE ('VecRep 'Vec8 'Int64ElemRep) Source #

Warning: this is only available on LLVM.

data Word8X16# :: TYPE ('VecRep 'Vec16 'Word8ElemRep) Source #

Warning: this is only available on LLVM.

data Word16X8# :: TYPE ('VecRep 'Vec8 'Word16ElemRep) Source #

Warning: this is only available on LLVM.

data Word32X4# :: TYPE ('VecRep 'Vec4 'Word32ElemRep) Source #

Warning: this is only available on LLVM.

data Word64X2# :: TYPE ('VecRep 'Vec2 'Word64ElemRep) Source #

Warning: this is only available on LLVM.

data Word8X32# :: TYPE ('VecRep 'Vec32 'Word8ElemRep) Source #

Warning: this is only available on LLVM.

data Word16X16# :: TYPE ('VecRep 'Vec16 'Word16ElemRep) Source #

Warning: this is only available on LLVM.

data Word32X8# :: TYPE ('VecRep 'Vec8 'Word32ElemRep) Source #

Warning: this is only available on LLVM.

data Word64X4# :: TYPE ('VecRep 'Vec4 'Word64ElemRep) Source #

Warning: this is only available on LLVM.

data Word8X64# :: TYPE ('VecRep 'Vec64 'Word8ElemRep) Source #

Warning: this is only available on LLVM.

data Word16X32# :: TYPE ('VecRep 'Vec32 'Word16ElemRep) Source #

Warning: this is only available on LLVM.

data Word32X16# :: TYPE ('VecRep 'Vec16 'Word32ElemRep) Source #

Warning: this is only available on LLVM.

data Word64X8# :: TYPE ('VecRep 'Vec8 'Word64ElemRep) Source #

Warning: this is only available on LLVM.

data FloatX4# :: TYPE ('VecRep 'Vec4 'FloatElemRep) Source #

Warning: this is only available on LLVM.

data DoubleX2# :: TYPE ('VecRep 'Vec2 'DoubleElemRep) Source #

Warning: this is only available on LLVM.

data FloatX8# :: TYPE ('VecRep 'Vec8 'FloatElemRep) Source #

Warning: this is only available on LLVM.

data DoubleX4# :: TYPE ('VecRep 'Vec4 'DoubleElemRep) Source #

Warning: this is only available on LLVM.

data FloatX16# :: TYPE ('VecRep 'Vec16 'FloatElemRep) Source #

Warning: this is only available on LLVM.

data DoubleX8# :: TYPE ('VecRep 'Vec8 'DoubleElemRep) Source #

Warning: this is only available on LLVM.

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 and can fail with an unchecked exception.

indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# Source #

Reads vector; offset in scalar elements.

Warning: this is only available on LLVM and can fail with an unchecked exception.

writeDoubleArrayAsDoubleX8# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #

Write a vector to specified index of mutable array of scalars; offset is in scalar elements.

Warning: this 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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# Source #

Reads vector; offset in bytes.

Warning: this is only available on LLVM and can fail with an unchecked exception.

writeDoubleX8Array# :: MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d Source #

Write a vector to specified index of mutable array.

Warning: this 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 and can fail with an unchecked exception.

indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# Source #

Read a vector from specified index of immutable array.

Warning: this is only available on LLVM and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Satisfies (quot# x y) times# y plus# (rem# x y) == x.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# Source #

Rounds towards zero element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# Source #

Divide two vectors element-wise.

Warning: this is only available on LLVM and can fail with an unchecked exception.

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 and can fail with an unchecked exception.

insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# Source #

Insert a scalar at the given position in a vector.

Warning: this is only available on LLVM and can fail with an unchecked exception.

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# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord8X64# :: Word8X64# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

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# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord8X32# :: Word8X32# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

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# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

Warning: this is only available on LLVM.

unpackWord8X16# :: Word8X16# -> (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) Source #

Unpack the elements of a vector into an unboxed tuple. #

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# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X32# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord8X64# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X64# Source #

Pack the elements of an unboxed tuple into a vector.

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# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X16# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord8X32# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X32# Source #

Pack the elements of an unboxed tuple into a vector.

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# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word16X8# Source #

Pack the elements of an unboxed tuple into a vector.

Warning: this is only available on LLVM.

packWord8X16# :: (# Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word#, Word# #) -> Word8X16# Source #

Pack the elements of an unboxed tuple into a vector.

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# :: Word# -> Word16X32# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X64# :: Word# -> 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# :: Word# -> Word16X16# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X32# :: Word# -> 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# :: Word# -> Word16X8# Source #

Broadcast a scalar to all elements of a vector.

Warning: this is only available on LLVM.

broadcastWord8X16# :: Word# -> 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.

whereFrom# :: a -> State# d -> (# State# d, Addr# #) Source #

Returns the InfoProvEnt for the info table of the given object (value is NULL if the table does not exist or there is no information about the closure).

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# :: Addr# -> (# a #) Source #

Convert an Addr# to a followable Any type.

keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (State# RealWorld -> b) -> b Source #

tt{keepAlive# x s k} keeps the value tt{x} alive during the execution of the computation tt{k}.

Note that the result type here isn't quite as unrestricted as the polymorphic type might suggest; ticket #21868 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.

Warning: this can fail with an unchecked exception.

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)). a -> State# RealWorld -> State# RealWorld 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).

forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #

fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) Source #

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 #

maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #) Source #

raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE ('BoxedRep l)) (b :: TYPE r). a -> b Source #

Warning: this can fail with an unchecked exception.

catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE ('BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #

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.

Warning: this can fail with an unchecked exception.

atomicModifyMutVar2# :: MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) Source #

Modify the contents of a MutVar#, returning the previous contents and the result of applying the given function to the previous contents. Note that this isn't strictly speaking the correct type for this function; it should really be MutVar# s a -> (a -> (a,b)) -> State# s -> (# State# s, a, (a, b) #), but we don't know about pairs here.

Warning: this can fail with an unchecked exception.

writeMutVar# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). MutVar# d a -> a -> State# d -> State# d Source #

Write contents of MutVar#.

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.

writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeWord32OffAddr# :: Addr# -> Int# -> Word32# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeWord16OffAddr# :: Addr# -> Int# -> Word16# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeWord8OffAddr# :: Addr# -> Int# -> Word8# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeInt32OffAddr# :: Addr# -> Int# -> Int32# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeInt16OffAddr# :: Addr# -> Int# -> Int16# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeInt8OffAddr# :: Addr# -> Int# -> Int8# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# d -> State# d Source #

Warning: this can fail with an unchecked exception.

readWord64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word64# #) Source #

Warning: this can fail with an unchecked exception.

readWord32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word32# #) Source #

Warning: this can fail with an unchecked exception.

readWord16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word16# #) Source #

Warning: this can fail with an unchecked exception.

readWord8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word8# #) Source #

Warning: this can fail with an unchecked exception.

readInt64OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int64# #) Source #

Warning: this can fail with an unchecked exception.

readInt32OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int32# #) Source #

Warning: this can fail with an unchecked exception.

readInt16OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int16# #) Source #

Warning: this can fail with an unchecked exception.

readInt8OffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int8# #) Source #

Warning: this can fail with an unchecked exception.

readStablePtrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) Source #

Warning: this can fail with an unchecked exception.

readDoubleOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Double# #) Source #

Warning: this can fail with an unchecked exception.

readFloatOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Float# #) Source #

Warning: this can fail with an unchecked exception.

readAddrOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Addr# #) Source #

Warning: this can fail with an unchecked exception.

readWordOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Word# #) Source #

Warning: this can fail with an unchecked exception.

readIntOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Int# #) Source #

Warning: this can fail with an unchecked exception.

readWideCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Reads 31-bit character; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readCharOffAddr# :: Addr# -> Int# -> State# d -> (# State# d, Char# #) Source #

Reads 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord64OffAddr# :: Addr# -> Int# -> Word64# Source #

Warning: this can fail with an unchecked exception.

indexWord32OffAddr# :: Addr# -> Int# -> Word32# Source #

Warning: this can fail with an unchecked exception.

indexWord16OffAddr# :: Addr# -> Int# -> Word16# Source #

Warning: this can fail with an unchecked exception.

indexWord8OffAddr# :: Addr# -> Int# -> Word8# Source #

Warning: this can fail with an unchecked exception.

indexInt64OffAddr# :: Addr# -> Int# -> Int64# Source #

Warning: this can fail with an unchecked exception.

indexInt32OffAddr# :: Addr# -> Int# -> Int32# Source #

Warning: this can fail with an unchecked exception.

indexInt16OffAddr# :: Addr# -> Int# -> Int16# Source #

Warning: this can fail with an unchecked exception.

indexInt8OffAddr# :: Addr# -> Int# -> Int8# Source #

Warning: this can fail with an unchecked exception.

indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #

Warning: this can fail with an unchecked exception.

indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source #

Warning: this can fail with an unchecked exception.

indexFloatOffAddr# :: Addr# -> Int# -> Float# Source #

Warning: this can fail with an unchecked exception.

indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source #

Warning: this can fail with an unchecked exception.

indexWordOffAddr# :: Addr# -> Int# -> Word# Source #

Warning: this can fail with an unchecked exception.

indexIntOffAddr# :: Addr# -> Int# -> Int# Source #

Warning: this can fail with an unchecked exception.

indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source #

Reads 31-bit character; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

indexCharOffAddr# :: Addr# -> Int# -> Char# Source #

Reads 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

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.

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.

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.

copyMutableByteArray# :: MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d Source #

Copy a range of the first MutableByteArray# to the specified region in the second MutableByteArray#. 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 n copies the range starting at offset src_ofs of length n from the ByteArray# src to the MutableByteArray# dst starting at offset dst_ofs. Both arrays must fully contain the specified ranges, but this is not checked. The two arrays must not be the same array in different states, but this is not checked either.

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.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d Source #

Write a 64-bit unsigned integer; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; offset in bytes.

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write a 8-bit character; 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; 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; 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; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

writeWord8Array# :: MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d Source #

Write a 8-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

writeInt64Array# :: MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d Source #

Write a 64-bit signed integer; offset in 8-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; offset in 4-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; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

writeInt8Array# :: MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d Source #

Write a 8-bit signed integer; 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; 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; 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; 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; 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; 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; 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; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

writeCharArray# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d Source #

Write a 8-bit character; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; 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; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 8-bit character; 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; 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; 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; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

readWord8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) Source #

Read a 8-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

readInt64Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) Source #

Read a 64-bit signed integer; offset in 8-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; offset in 4-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; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

readInt8Array# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) Source #

Read a 8-bit signed integer; 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; 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; 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; 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; 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; 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; 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; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

readCharArray# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) Source #

Read a 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# Source #

Read a 64-bit signed integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #

Read a 32-bit signed integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #

Read a 16-bit signed integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #

Read a StablePtr# value; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #

Read a double-precision floating-point value; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #

Read a single-precision floating-point value; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #

Read a machine address; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #

Read a word-sized unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #

Read a word-sized integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #

Read a 32-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #

Read a 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

indexWord64Array# :: ByteArray# -> Int# -> Word64# Source #

Read a 64-bit unsigned integer; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #

Read a 32-bit unsigned integer; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #

Read a 16-bit unsigned integer; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #

Read a 8-bit unsigned integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexInt64Array# :: ByteArray# -> Int# -> Int64# Source #

Read a 64-bit signed integer; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #

Read a 32-bit signed integer; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #

Read a 16-bit signed integer; offset in 2-byte words.

Warning: this can fail with an unchecked exception.

indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #

Read a 8-bit signed integer; offset in bytes.

Warning: this can fail with an unchecked exception.

indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #

Read a StablePtr# value; offset in machine words.

Warning: this can fail with an unchecked exception.

indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #

Read a double-precision floating-point value; offset in 8-byte words.

Warning: this can fail with an unchecked exception.

indexFloatArray# :: ByteArray# -> Int# -> Float# Source #

Read a single-precision floating-point value; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #

Read a machine address; offset in machine words.

Warning: this can fail with an unchecked exception.

indexWordArray# :: ByteArray# -> Int# -> Word# Source #

Read a word-sized unsigned integer; offset in machine words.

Warning: this can fail with an unchecked exception.

indexIntArray# :: ByteArray# -> Int# -> Int# Source #

Read a word-sized integer; offset in machine words.

Warning: this can fail with an unchecked exception.

indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #

Read a 32-bit character; offset in 4-byte words.

Warning: this can fail with an unchecked exception.

indexCharArray# :: ByteArray# -> Int# -> Char# Source #

Read a 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (# State# d, Int# #) Source #

Return the number of elements in the array.

sizeofMutableByteArray# :: MutableByteArray# d -> Int# Source #

Return the size of the array in bytes. Note that this is deprecated as it is unsafe in the presence of shrink and resize operations on the same mutable byte array.

sizeofByteArray# :: ByteArray# -> Int# Source #

Return the size of the array in bytes.

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 (unpinned) mutable byte array to new specified size (in bytes). The returned MutableByteArray# is either the original MutableByteArray# resized in-place or, if not possible, a newly allocated (unpinned) MutableByteArray# (with the original content copied over).

To avoid undefined behaviour, the original MutableByteArray# shall not be accessed anymore after a resizeMutableByteArray# has been performed. Moreover, no reference to the old one should be kept in order to allow garbage collection of the original MutableByteArray# in case a new MutableByteArray# had to be allocated.

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

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.

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.

Warning: this can fail with an unchecked exception.

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.

sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE ('BoxedRep l)). SmallMutableArray# d a -> Int# Source #

Return the number of elements in the array. Note that this is deprecated as it is unsafe in the presence of shrink and resize 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#.

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.

Warning: this can fail with an unchecked exception.

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.

decodeFloat_Int# :: Float# -> (# Int#, Int# #) Source #

Convert to integers. First Int# in result is the mantissa; second is the exponent.

acosFloat# :: Float# -> Float# Source #

Warning: this can fail with an unchecked exception.

asinFloat# :: Float# -> Float# Source #

Warning: this can fail with an unchecked exception.

log1pFloat# :: Float# -> Float# Source #

Warning: this can fail with an unchecked exception.

logFloat# :: Float# -> Float# Source #

Warning: this can fail with an unchecked exception.

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

divideFloat# :: Float# -> Float# -> Float# Source #

Warning: this can fail with an unchecked exception.

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.

acosDouble# :: Double# -> Double# Source #

Warning: this can fail with an unchecked exception.

asinDouble# :: Double# -> Double# Source #

Warning: this can fail with an unchecked exception.

log1pDouble# :: Double# -> Double# Source #

Warning: this can fail with an unchecked exception.

logDouble# :: Double# -> Double# Source #

Warning: this can fail with an unchecked exception.

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 #

Warning: this can fail with an unchecked exception.

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

pext64# :: Word64# -> Word64# -> Word64# Source #

Extract bits from a word at locations specified by a mask.

pext32# :: Word# -> Word# -> Word# Source #

Extract bits from lower 32 bits of a word at locations specified by a mask.

pext16# :: Word# -> Word# -> Word# Source #

Extract bits from lower 16 bits of a word at locations specified by a mask.

pext8# :: Word# -> Word# -> Word# Source #

Extract bits from lower 8 bits of a word at locations specified by a mask.

pdep# :: Word# -> Word# -> Word# Source #

Deposit bits to a word at locations specified by a mask.

pdep64# :: Word64# -> Word64# -> Word64# Source #

Deposit bits to a word at locations specified by a mask.

pdep32# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 32 bits of a word at locations specified by a mask.

pdep16# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 16 bits of a word at locations specified by a mask.

pdep8# :: Word# -> Word# -> Word# Source #

Deposit bits to lower 8 bits of a word at locations specified by a mask.

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.

Warning: this can fail with an unchecked exception.

quotRemWord# :: Word# -> Word# -> (# Word#, Word# #) Source #

Warning: this can fail with an unchecked exception.

remWord# :: Word# -> Word# -> Word# Source #

Warning: this can fail with an unchecked exception.

quotWord# :: Word# -> Word# -> Word# Source #

Warning: this can fail with an unchecked exception.

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.

Warning: this can fail with an unchecked exception.

remInt# :: Int# -> Int# -> Int# Source #

Satisfies (quotInt# x y) *# y +# (remInt# x y) == x. The behavior is undefined if the second argument is zero.

Warning: this can fail with an unchecked exception.

quotInt# :: Int# -> Int# -> Int# Source #

Rounds towards zero. The behavior is undefined if the second argument is zero.

Warning: this can fail with an unchecked exception.

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 #

remWord64# :: Word64# -> Word64# -> Word64# Source #

Warning: this can fail with an unchecked exception.

quotWord64# :: Word64# -> Word64# -> Word64# Source #

Warning: this can fail with an unchecked exception.

remInt64# :: Int64# -> Int64# -> Int64# Source #

Warning: this can fail with an unchecked exception.

quotInt64# :: Int64# -> Int64# -> Int64# Source #

Warning: this can fail with an unchecked exception.

quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #) Source #

Warning: this can fail with an unchecked exception.

remWord32# :: Word32# -> Word32# -> Word32# Source #

Warning: this can fail with an unchecked exception.

quotWord32# :: Word32# -> Word32# -> Word32# Source #

Warning: this can fail with an unchecked exception.

quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #) Source #

Warning: this can fail with an unchecked exception.

remInt32# :: Int32# -> Int32# -> Int32# Source #

Warning: this can fail with an unchecked exception.

quotInt32# :: Int32# -> Int32# -> Int32# Source #

Warning: this can fail with an unchecked exception.

quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #) Source #

Warning: this can fail with an unchecked exception.

remWord16# :: Word16# -> Word16# -> Word16# Source #

Warning: this can fail with an unchecked exception.

quotWord16# :: Word16# -> Word16# -> Word16# Source #

Warning: this can fail with an unchecked exception.

quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #) Source #

Warning: this can fail with an unchecked exception.

remInt16# :: Int16# -> Int16# -> Int16# Source #

Warning: this can fail with an unchecked exception.

quotInt16# :: Int16# -> Int16# -> Int16# Source #

Warning: this can fail with an unchecked exception.

quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #) Source #

Warning: this can fail with an unchecked exception.

remWord8# :: Word8# -> Word8# -> Word8# Source #

Warning: this can fail with an unchecked exception.

quotWord8# :: Word8# -> Word8# -> Word8# Source #

Warning: this can fail with an unchecked exception.

quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #) Source #

Warning: this can fail with an unchecked exception.

remInt8# :: Int8# -> Int8# -> Int8# Source #

Warning: this can fail with an unchecked exception.

quotInt8# :: Int8# -> Int8# -> Int8# Source #

Warning: this can fail with an unchecked exception.

rightSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {s :: RuntimeRep} {n :: Multiplicity} {o :: Multiplicity} (a :: TYPE q) (b :: TYPE r) (c :: TYPE s). (a %n -> b %o -> c) -> b %o -> a %n -> c Source #

leftSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {n :: Multiplicity} (a :: TYPE q) (b :: TYPE r). (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.

seq :: forall {r :: RuntimeRep} a (b :: TYPE r). 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 GHC.Magic.runRW#.

Running RealWorld state thread

runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o Source #

Apply a function to a State# RealWorld token. When manually applying a function to realWorld#, it is necessary to use NOINLINE to prevent semantically undesirable floating. runRW# is inlined, but only very late in compilation after all floating is complete.

Bit shift operations

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)

Pointer comparison operations

reallyUnsafePtrEquality :: a -> a -> Int# Source #

Compare the underlying pointers of two values for equality.

Returns 1 if the pointers are equal and 0 otherwise.

The two values must be of the same type, of kind Type. See also reallyUnsafePtrEquality#, which doesn't have such restrictions.

eqStableName# :: StableName# a -> StableName# b -> Int# Source #

Compare two stable names for equality.

sameArray# :: Array# a -> Array# a -> Int# Source #

Compare the underlying pointers of two arrays.

sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int# Source #

Compare the underlying pointers of two mutable arrays.

sameSmallArray# :: SmallArray# a -> SmallArray# a -> Int# Source #

Compare the underlying pointers of two small arrays.

sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int# Source #

Compare the underlying pointers of two small mutable arrays.

sameByteArray# :: ByteArray# -> ByteArray# -> Int# Source #

Compare the pointers of two byte arrays.

sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# Source #

Compare the underlying pointers of two mutable byte arrays.

sameMVar# :: MVar# s a -> MVar# s a -> Int# Source #

Compare the underlying pointers of two MVar#s.

sameMutVar# :: MutVar# s a -> MutVar# s a -> Int# Source #

Compare the underlying pointers of two MutVar#s.

sameTVar# :: TVar# s a -> TVar# s a -> Int# Source #

Compare the underlying pointers of two TVar#s.

sameIOPort# :: IOPort# s a -> IOPort# s a -> Int# Source #

Compare the underlying pointers of two IOPort#s.

Compat wrapper

atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #) Source #

An implementation of the old atomicModifyMutVar# primop in terms of the new atomicModifyMutVar2# primop, for backwards compatibility. The type of this function is a bit bogus. It's best to think of it as having type

atomicModifyMutVar#
  :: MutVar# s a
  -> (a -> (a, b))
  -> State# s
  -> (# State# s, b #)

but there may be code that uses this with other two-field record types.

Resize functions

Resizing arrays of boxed elements is currently handled in library space (rather than being a primop) since there is not an efficient way to grow arrays. However, resize operations may become primops in a future release of GHC.

resizeSmallMutableArray# Source #

Arguments

:: SmallMutableArray# s a

Array to resize

-> Int#

New size of array

-> a

Newly created slots initialized to this element. Only used when array is grown.

-> State# s 
-> (# State# s, SmallMutableArray# s a #) 

Resize a mutable array to new specified size. The returned SmallMutableArray# is either the original SmallMutableArray# resized in-place or, if not possible, a newly allocated SmallMutableArray# with the original content copied over.

To avoid undefined behaviour, the original SmallMutableArray# shall not be accessed anymore after a resizeSmallMutableArray# has been performed. Moreover, no reference to the old one should be kept in order to allow garbage collection of the original SmallMutableArray# in case a new SmallMutableArray# had to be allocated.

Since: base-4.14.0.0

Fusion

build :: forall a. (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 a. (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.

Overloaded lists

class IsList l where Source #

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: base-4.7.0.0

Minimal complete definition

fromList, toList

Associated Types

type Item l Source #

The Item type function returns the type of items of the structure l.

Methods

fromList :: [Item l] -> l Source #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [Item l] -> l Source #

The fromListN function takes the input list's length and potentially uses it to construct the structure l more efficiently compared to fromList. If the given number does not equal to the input list's length the behaviour of fromListN is not specified.

fromListN (length xs) xs == fromList xs

toList :: l -> [Item l] Source #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

Instances

Instances details
IsList ByteArray Source #

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Associated Types

type Item ByteArray Source #

IsList Version Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item Version Source #

IsList CallStack Source #

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item CallStack Source #

IsList (ZipList a) Source #

Since: base-4.15.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item (ZipList a) Source #

Methods

fromList :: [Item (ZipList a)] -> ZipList a Source #

fromListN :: Int -> [Item (ZipList a)] -> ZipList a Source #

toList :: ZipList a -> [Item (ZipList a)] Source #

IsList (NonEmpty a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item (NonEmpty a) Source #

IsList [a] Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item [a] Source #

Methods

fromList :: [Item [a]] -> [a] Source #

fromListN :: Int -> [Item [a]] -> [a] Source #

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

Transform comprehensions

newtype Down a Source #

The Down type allows you to reverse sort order conveniently. A value of type Down a contains a value of type a (represented as Down a).

If a has an Ord instance associated with it then comparing two values thus wrapped will give you the opposite of their normal sort order. This is particularly useful when sorting in generalised list comprehensions, as in: then sortWith by Down x.

>>> compare True False
GT
>>> compare (Down True) (Down False)
LT

If a has a Bounded instance then the wrapped instance also respects the reversed ordering by exchanging the values of minBound and maxBound.

>>> minBound :: Int
-9223372036854775808
>>> minBound :: Down Int
Down 9223372036854775807

All other instances of Down a behave as they do for a.

Since: base-4.6.0.0

Constructors

Down 

Fields

Instances

Instances details
MonadFix Down Source #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Fix

Methods

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

MonadZip Down Source #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Foldable Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

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

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

null :: Down a -> Bool Source #

length :: Down a -> Int Source #

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

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

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

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

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

Eq1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] Source #

Show1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Down a] -> ShowS Source #

Traversable Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Applicative Down Source #

Since: base-4.11.0.0

Instance details

Defined in 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 #

Functor Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

Monad Down Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

return :: a -> Down a Source #

Generic1 Down Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down :: k -> Type Source #

Methods

from1 :: forall (a :: k). Down a -> Rep1 Down a Source #

to1 :: forall (a :: k). Rep1 Down a -> Down a Source #

Data a => Data (Down a) Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Down a -> Constr Source #

dataTypeOf :: Down a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable a => Storable (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int Source #

alignment :: Down a -> Int Source #

peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) Source #

pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Down a) Source #

pokeByteOff :: Ptr b -> Int -> Down a -> IO () Source #

peek :: Ptr (Down a) -> IO (Down a) Source #

poke :: Ptr (Down a) -> Down a -> IO () Source #

Monoid a => Monoid (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a Source #

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

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

Semigroup a => Semigroup (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in 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 #

Bits a => Bits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(.&.) :: Down a -> Down a -> Down a Source #

(.|.) :: Down a -> Down a -> Down a Source #

xor :: Down a -> Down a -> Down a Source #

complement :: Down a -> Down a Source #

shift :: Down a -> Int -> Down a Source #

rotate :: Down a -> Int -> Down a Source #

zeroBits :: Down a Source #

bit :: Int -> Down a Source #

setBit :: Down a -> Int -> Down a Source #

clearBit :: Down a -> Int -> Down a Source #

complementBit :: Down a -> Int -> Down a Source #

testBit :: Down a -> Int -> Bool Source #

bitSizeMaybe :: Down a -> Maybe Int Source #

bitSize :: Down a -> Int Source #

isSigned :: Down a -> Bool Source #

shiftL :: Down a -> Int -> Down a Source #

unsafeShiftL :: Down a -> Int -> Down a Source #

shiftR :: Down a -> Int -> Down a Source #

unsafeShiftR :: Down a -> Int -> Down a Source #

rotateL :: Down a -> Int -> Down a Source #

rotateR :: Down a -> Int -> Down a Source #

popCount :: Down a -> Int Source #

FiniteBits a => FiniteBits (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Bounded a => Bounded (Down a) Source #

Swaps minBound and maxBound of the underlying type.

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Floating a => Floating (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

pi :: Down a Source #

exp :: Down a -> Down a Source #

log :: Down a -> Down a Source #

sqrt :: Down a -> Down a Source #

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

logBase :: Down a -> Down a -> Down a Source #

sin :: Down a -> Down a Source #

cos :: Down a -> Down a Source #

tan :: Down a -> Down a Source #

asin :: Down a -> Down a Source #

acos :: Down a -> Down a Source #

atan :: Down a -> Down a Source #

sinh :: Down a -> Down a Source #

cosh :: Down a -> Down a Source #

tanh :: Down a -> Down a Source #

asinh :: Down a -> Down a Source #

acosh :: Down a -> Down a Source #

atanh :: Down a -> Down a Source #

log1p :: Down a -> Down a Source #

expm1 :: Down a -> Down a Source #

log1pexp :: Down a -> Down a Source #

log1mexp :: Down a -> Down a Source #

RealFloat a => RealFloat (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Generic (Down a) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type Source #

Methods

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

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

Ix a => Ix (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

range :: (Down a, Down a) -> [Down a] Source #

index :: (Down a, Down a) -> Down a -> Int Source #

unsafeIndex :: (Down a, Down a) -> Down a -> Int Source #

inRange :: (Down a, Down a) -> Down a -> Bool Source #

rangeSize :: (Down a, Down a) -> Int Source #

unsafeRangeSize :: (Down a, Down a) -> Int Source #

Num a => Num (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

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

negate :: Down a -> Down a Source #

abs :: Down a -> Down a Source #

signum :: Down a -> Down a Source #

fromInteger :: Integer -> Down a Source #

Read a => Read (Down a) Source #

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Fractional a => Fractional (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

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

recip :: Down a -> Down a Source #

fromRational :: Rational -> Down a Source #

Real a => Real (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

RealFrac a => RealFrac (Down a) Source #

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

properFraction :: Integral b => Down a -> (b, Down a) Source #

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

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

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

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

Show a => Show (Down a) Source #

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS Source #

show :: Down a -> String Source #

showList :: [Down a] -> ShowS Source #

Eq a => Eq (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

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

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

Ord a => Ord (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in 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 #

type Rep1 Down Source #

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Down a) Source #

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep (Down a) = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

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

The groupWith function uses the user supplied function which projects an element out of every list element in order to first sort the input list and then to form groups by equality on these projected elements

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

The sortWith function sorts a list of elements using the user supplied function to project something out of each element

In general if the user supplied function is expensive to compute then you should probably be using sortOn, as it only needs to compute it once for each element. sortWith, on the other hand must compute the mapping function for every comparison that it performs.

the :: Eq a => [a] -> a Source #

the ensures that all the elements of the list are identical and then returns that unique element

Strings

Overloaded string literals

class IsString a where Source #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a Source #

Instances

Instances details
IsString a => IsString (Identity a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.String

a ~ Char => IsString [a] Source #

(a ~ Char) context was introduced in 4.9.0.0

Since: base-2.1

Instance details

Defined in Data.String

Methods

fromString :: String -> [a] Source #

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

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b Source #

CString

unpackFoldrCString# :: Addr# -> (Char -> a -> a) -> a -> a Source #

cstringLength# :: Addr# -> Int# Source #

Compute the length of a NUL-terminated string. This address must refer to immutable memory. GHC includes a built-in rule for constant folding when the argument is a statically-known literal. That is, a core-to-core pass reduces the expression cstringLength# "hello"# to the constant 5#.

Debugging

Breakpoints

breakpoint :: a -> a Source #

Event logging

traceEvent :: String -> IO () Source #

Deprecated: Use traceEvent or traceEventIO

The call stack

currentCallStack :: IO [String] Source #

Returns a [String] representing the current call stack. This can be useful for debugging.

The implementation uses the call-stack simulation maintained by the profiler, so it only works if the program was compiled with -prof and contains suitable SCC annotations (e.g. by using -fprof-auto). Otherwise, the list returned is likely to be empty or uninformative.

Since: base-4.5.0.0

Ids with special behaviour

inline :: a -> a Source #

The call inline f arranges that f is inlined, regardless of its size. More precisely, the call inline f rewrites to the right-hand side of f's definition. This allows the programmer to control inlining from a particular call site rather than the definition site of the function (c.f. INLINE pragmas).

This inlining occurs regardless of the argument to the call or the size of f's definition; it is unconditional. The main caveat is that f's definition must be visible to the compiler; it is therefore recommended to mark the function with an INLINABLE pragma at its definition so that GHC guarantees to record its unfolding regardless of size.

If no inlining takes place, the inline function expands to the identity function in Phase zero, so its use imposes no overhead.

noinline :: a -> a Source #

The call noinline f arranges that f will not be inlined. It is removed during CorePrep so that its use imposes no overhead (besides the fact that it blocks inlining.)

lazy :: a -> a Source #

The lazy function restrains strictness analysis a little. The call lazy e means the same as e, but lazy has a magical property so far as strictness analysis is concerned: it is lazy in its first argument, even though its semantics is strict. After strictness analysis has run, calls to lazy are inlined to be the identity function.

This behaviour is occasionally useful when controlling evaluation order. Notably, lazy is used in the library definition of par:

par :: a -> b -> b
par x y = case (par# x) of _ -> lazy y

If lazy were not lazy, par would look strict in y which would defeat the whole purpose of par.

oneShot :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b Source #

The oneShot function can be used to give a hint to the compiler that its argument will be called at most once, which may (or may not) enable certain optimizations. It can be useful to improve the performance of code in continuation passing style.

If oneShot is used wrongly, then it may be that computations whose result that would otherwise be shared are re-evaluated every time they are used. Otherwise, the use of oneShot is safe.

oneShot is representation-polymorphic: the type variables may refer to lifted or unlifted types.

considerAccessible :: Bool Source #

Semantically, considerAccessible = True. But it has special meaning to the pattern-match checker, which will never flag the clause in which considerAccessible occurs as a guard as redundant or inaccessible. Example:

case (x, x) of
  (True,  True)  -> 1
  (False, False) -> 2
  (True,  False) -> 3 -- Warning: redundant

The pattern-match checker will warn here that the third clause is redundant. It will stop doing so if the clause is adorned with considerAccessible:

case (x, x) of
  (True,  True)  -> 1
  (False, False) -> 2
  (True,  False) | considerAccessible -> 3 -- No warning

Put considerAccessible as the last statement of the guard to avoid get confusing results from the pattern-match checker, which takes "consider accessible" by word.

SpecConstr annotations

data SpecConstrAnnotation Source #

Instances

Instances details
Data SpecConstrAnnotation Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Exts

Methods

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

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

toConstr :: SpecConstrAnnotation -> Constr Source #

dataTypeOf :: SpecConstrAnnotation -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Eq SpecConstrAnnotation Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Exts

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.

Constructors

SPEC 
SPEC2 

Coercions

Safe coercions

These are available from the Trustworthy module Data.Coerce as well.

Since: base-4.7.0.0

coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). 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.

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.

Very unsafe coercion

unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b Source #

Highly, terribly dangerous coercion from one representation type to another. Misuse of this function can invite the garbage collector to trounce upon your data and then laugh in your face. You don't want this function. Really.

Casting class dictionaries with single methods

class WithDict cls meth where Source #

withDict d f provides a way to call a type-class–overloaded function f by applying it to the supplied dictionary d.

withDict can only be used if the type class has a single method with no superclasses. For more (important) details on how this works, see Note [withDict] in GHC.Tc.Instance.Class in GHC.

Methods

withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r Source #

The maximum tuple size