W3cubDocs

/Haskell 8

GHC.Exts

Copyright (c) The University of Glasgow 2002
License see libraries/base/LICENSE
Maintainer [email protected]
Stability internal
Portability non-portable (GHC Extensions)
Safe Haskell Unsafe
Language Haskell2010

Description

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

Note: no other base module should import this module.

Representations of some basic types

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

Bounded Int

Since: 2.1

Enum Int

Since: 2.1

Eq Int

Methods

(==) :: Int -> Int -> Bool Source

(/=) :: Int -> Int -> Bool Source

Integral Int

Since: 2.0.1

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

Data Int

Since: 4.0.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] Source

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

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int Source

Num Int

Since: 2.1

Methods

(+) :: Int -> Int -> Int Source

(-) :: Int -> Int -> Int Source

(*) :: Int -> Int -> Int Source

negate :: Int -> Int Source

abs :: Int -> Int Source

signum :: Int -> Int Source

fromInteger :: Integer -> Int Source

Ord Int

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

Read Int

Since: 2.1

Real Int

Since: 2.0.1

Methods

toRational :: Int -> Rational Source

Show Int

Since: 2.1

Methods

showsPrec :: Int -> Int -> ShowS Source

show :: Int -> String Source

showList :: [Int] -> ShowS Source

Ix Int

Since: 2.1

Methods

range :: (Int, Int) -> [Int] Source

index :: (Int, Int) -> Int -> Int Source

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool Source

rangeSize :: (Int, Int) -> Int Source

unsafeRangeSize :: (Int, Int) -> Int

FiniteBits Int

Since: 4.6.0.0

Bits Int

Since: 2.1

Storable Int

Since: 2.1

Methods

sizeOf :: Int -> Int Source

alignment :: Int -> Int Source

peekElemOff :: Ptr Int -> Int -> IO Int Source

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

peekByteOff :: Ptr b -> Int -> IO Int Source

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

peek :: Ptr Int -> IO Int Source

poke :: Ptr Int -> Int -> IO () Source

PrintfArg Int

Since: 2.1

Generic1 k (URec k Int)

Associated Types

type Rep1 (URec k Int) (f :: URec k Int -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k Int) f a Source

to1 :: Rep1 (URec k Int) f a -> f a Source

Functor (URec * Int)

Methods

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

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

Foldable (URec * Int)

Methods

fold :: Monoid m => URec * Int m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Int a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Int a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b Source

foldr1 :: (a -> a -> a) -> URec * Int a -> a Source

foldl1 :: (a -> a -> a) -> URec * Int a -> a Source

toList :: URec * Int a -> [a] Source

null :: URec * Int a -> Bool Source

length :: URec * Int a -> Int Source

elem :: Eq a => a -> URec * Int a -> Bool Source

maximum :: Ord a => URec * Int a -> a Source

minimum :: Ord a => URec * Int a -> a Source

sum :: Num a => URec * Int a -> a Source

product :: Num a => URec * Int a -> a Source

Traversable (URec * Int)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) Source

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) Source

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) Source

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) Source

Eq (URec k Int p)

Methods

(==) :: URec k Int p -> URec k Int p -> Bool Source

(/=) :: URec k Int p -> URec k Int p -> Bool Source

Ord (URec k Int p)

Methods

compare :: URec k Int p -> URec k Int p -> Ordering Source

(<) :: URec k Int p -> URec k Int p -> Bool Source

(<=) :: URec k Int p -> URec k Int p -> Bool Source

(>) :: URec k Int p -> URec k Int p -> Bool Source

(>=) :: URec k Int p -> URec k Int p -> Bool Source

max :: URec k Int p -> URec k Int p -> URec k Int p Source

min :: URec k Int p -> URec k Int p -> URec k Int p Source

Show (URec k Int p)

Methods

showsPrec :: Int -> URec k Int p -> ShowS Source

show :: URec k Int p -> String Source

showList :: [URec k Int p] -> ShowS Source

Generic (URec k Int p)

Associated Types

type Rep (URec k Int p) :: * -> * Source

Methods

from :: URec k Int p -> Rep (URec k Int p) x Source

to :: Rep (URec k Int p) x -> URec k Int p Source

data URec k Int

Used for marking occurrences of Int#

Since: 4.9.0.0

data URec k Int = UInt {}
type Rep1 k (URec k Int)
type Rep1 k (URec k Int) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UInt" PrefixI True) (S1 k (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt k)))
type Rep (URec k Int p)
type Rep (URec k Int p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UInt" PrefixI True) (S1 * (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt *)))

data Word :: * Source

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

Constructors

W# Word#

Instances

Bounded Word

Since: 2.1

Enum Word

Since: 2.1

Eq Word

Methods

(==) :: Word -> Word -> Bool Source

(/=) :: Word -> Word -> Bool Source

Integral Word

Since: 2.1

Data Word

Since: 4.0.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source

Num Word

Since: 2.1

Ord Word

Methods

compare :: Word -> Word -> Ordering Source

(<) :: Word -> Word -> Bool Source

(<=) :: Word -> Word -> Bool Source

(>) :: Word -> Word -> Bool Source

(>=) :: Word -> Word -> Bool Source

max :: Word -> Word -> Word Source

min :: Word -> Word -> Word Source

Read Word

Since: 4.5.0.0

Real Word

Since: 2.1

Methods

toRational :: Word -> Rational Source

Show Word

Since: 2.1

Ix Word

Since: 4.6.0.0

Methods

range :: (Word, Word) -> [Word] Source

index :: (Word, Word) -> Word -> Int Source

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool Source

rangeSize :: (Word, Word) -> Int Source

unsafeRangeSize :: (Word, Word) -> Int

FiniteBits Word

Since: 4.6.0.0

Bits Word

Since: 2.1

Storable Word

Since: 2.1

PrintfArg Word

Since: 2.1

Generic1 k (URec k Word)

Associated Types

type Rep1 (URec k Word) (f :: URec k Word -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k Word) f a Source

to1 :: Rep1 (URec k Word) f a -> f a Source

Functor (URec * Word)

Methods

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

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

Foldable (URec * Word)

Methods

fold :: Monoid m => URec * Word m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Word a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Word a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Word a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Word a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Word a -> b Source

foldr1 :: (a -> a -> a) -> URec * Word a -> a Source

foldl1 :: (a -> a -> a) -> URec * Word a -> a Source

toList :: URec * Word a -> [a] Source

null :: URec * Word a -> Bool Source

length :: URec * Word a -> Int Source

elem :: Eq a => a -> URec * Word a -> Bool Source

maximum :: Ord a => URec * Word a -> a Source

minimum :: Ord a => URec * Word a -> a Source

sum :: Num a => URec * Word a -> a Source

product :: Num a => URec * Word a -> a Source

Traversable (URec * Word)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Word a -> f (URec * Word b) Source

sequenceA :: Applicative f => URec * Word (f a) -> f (URec * Word a) Source

mapM :: Monad m => (a -> m b) -> URec * Word a -> m (URec * Word b) Source

sequence :: Monad m => URec * Word (m a) -> m (URec * Word a) Source

Eq (URec k Word p)

Methods

(==) :: URec k Word p -> URec k Word p -> Bool Source

(/=) :: URec k Word p -> URec k Word p -> Bool Source

Ord (URec k Word p)

Methods

compare :: URec k Word p -> URec k Word p -> Ordering Source

(<) :: URec k Word p -> URec k Word p -> Bool Source

(<=) :: URec k Word p -> URec k Word p -> Bool Source

(>) :: URec k Word p -> URec k Word p -> Bool Source

(>=) :: URec k Word p -> URec k Word p -> Bool Source

max :: URec k Word p -> URec k Word p -> URec k Word p Source

min :: URec k Word p -> URec k Word p -> URec k Word p Source

Show (URec k Word p)

Methods

showsPrec :: Int -> URec k Word p -> ShowS Source

show :: URec k Word p -> String Source

showList :: [URec k Word p] -> ShowS Source

Generic (URec k Word p)

Associated Types

type Rep (URec k Word p) :: * -> * Source

Methods

from :: URec k Word p -> Rep (URec k Word p) x Source

to :: Rep (URec k Word p) x -> URec k Word p Source

data URec k Word

Used for marking occurrences of Word#

Since: 4.9.0.0

data URec k Word = UWord {}
type Rep1 k (URec k Word)
type Rep1 k (URec k Word) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UWord" PrefixI True) (S1 k (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UWord k)))
type Rep (URec k Word p)
type Rep (URec k Word p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UWord" PrefixI True) (S1 * (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UWord *)))

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

Eq Float

Methods

(==) :: Float -> Float -> Bool Source

(/=) :: Float -> Float -> Bool Source

Floating Float

Since: 2.1

Data Float

Since: 4.0.0.0

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

Ord Float
Read Float

Since: 2.1

RealFloat Float

Since: 2.1

Storable Float

Since: 2.1

PrintfArg Float

Since: 2.1

Generic1 k (URec k Float)

Associated Types

type Rep1 (URec k Float) (f :: URec k Float -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k Float) f a Source

to1 :: Rep1 (URec k Float) f a -> f a Source

Functor (URec * Float)

Methods

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

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

Foldable (URec * Float)

Methods

fold :: Monoid m => URec * Float m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Float a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Float a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Float a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Float a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Float a -> b Source

foldr1 :: (a -> a -> a) -> URec * Float a -> a Source

foldl1 :: (a -> a -> a) -> URec * Float a -> a Source

toList :: URec * Float a -> [a] Source

null :: URec * Float a -> Bool Source

length :: URec * Float a -> Int Source

elem :: Eq a => a -> URec * Float a -> Bool Source

maximum :: Ord a => URec * Float a -> a Source

minimum :: Ord a => URec * Float a -> a Source

sum :: Num a => URec * Float a -> a Source

product :: Num a => URec * Float a -> a Source

Traversable (URec * Float)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Float a -> f (URec * Float b) Source

sequenceA :: Applicative f => URec * Float (f a) -> f (URec * Float a) Source

mapM :: Monad m => (a -> m b) -> URec * Float a -> m (URec * Float b) Source

sequence :: Monad m => URec * Float (m a) -> m (URec * Float a) Source

Eq (URec k Float p)

Methods

(==) :: URec k Float p -> URec k Float p -> Bool Source

(/=) :: URec k Float p -> URec k Float p -> Bool Source

Ord (URec k Float p)

Methods

compare :: URec k Float p -> URec k Float p -> Ordering Source

(<) :: URec k Float p -> URec k Float p -> Bool Source

(<=) :: URec k Float p -> URec k Float p -> Bool Source

(>) :: URec k Float p -> URec k Float p -> Bool Source

(>=) :: URec k Float p -> URec k Float p -> Bool Source

max :: URec k Float p -> URec k Float p -> URec k Float p Source

min :: URec k Float p -> URec k Float p -> URec k Float p Source

Show (URec k Float p)

Methods

showsPrec :: Int -> URec k Float p -> ShowS Source

show :: URec k Float p -> String Source

showList :: [URec k Float p] -> ShowS Source

Generic (URec k Float p)

Associated Types

type Rep (URec k Float p) :: * -> * Source

Methods

from :: URec k Float p -> Rep (URec k Float p) x Source

to :: Rep (URec k Float p) x -> URec k Float p Source

data URec k Float

Used for marking occurrences of Float#

Since: 4.9.0.0

data URec k Float = UFloat {}
type Rep1 k (URec k Float)
type Rep1 k (URec k Float) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UFloat" PrefixI True) (S1 k (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UFloat k)))
type Rep (URec k Float p)
type Rep (URec k Float p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UFloat" PrefixI True) (S1 * (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UFloat *)))

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

Eq Double

Methods

(==) :: Double -> Double -> Bool Source

(/=) :: Double -> Double -> Bool Source

Floating Double

Since: 2.1

Data Double

Since: 4.0.0.0

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

Ord Double
Read Double

Since: 2.1

RealFloat Double

Since: 2.1

Storable Double

Since: 2.1

PrintfArg Double

Since: 2.1

Generic1 k (URec k Double)

Associated Types

type Rep1 (URec k Double) (f :: URec k Double -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k Double) f a Source

to1 :: Rep1 (URec k Double) f a -> f a Source

Functor (URec * Double)

Methods

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

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

Foldable (URec * Double)

Methods

fold :: Monoid m => URec * Double m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Double a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Double a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Double a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Double a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Double a -> b Source

foldr1 :: (a -> a -> a) -> URec * Double a -> a Source

foldl1 :: (a -> a -> a) -> URec * Double a -> a Source

toList :: URec * Double a -> [a] Source

null :: URec * Double a -> Bool Source

length :: URec * Double a -> Int Source

elem :: Eq a => a -> URec * Double a -> Bool Source

maximum :: Ord a => URec * Double a -> a Source

minimum :: Ord a => URec * Double a -> a Source

sum :: Num a => URec * Double a -> a Source

product :: Num a => URec * Double a -> a Source

Traversable (URec * Double)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Double a -> f (URec * Double b) Source

sequenceA :: Applicative f => URec * Double (f a) -> f (URec * Double a) Source

mapM :: Monad m => (a -> m b) -> URec * Double a -> m (URec * Double b) Source

sequence :: Monad m => URec * Double (m a) -> m (URec * Double a) Source

Eq (URec k Double p)

Methods

(==) :: URec k Double p -> URec k Double p -> Bool Source

(/=) :: URec k Double p -> URec k Double p -> Bool Source

Ord (URec k Double p)

Methods

compare :: URec k Double p -> URec k Double p -> Ordering Source

(<) :: URec k Double p -> URec k Double p -> Bool Source

(<=) :: URec k Double p -> URec k Double p -> Bool Source

(>) :: URec k Double p -> URec k Double p -> Bool Source

(>=) :: URec k Double p -> URec k Double p -> Bool Source

max :: URec k Double p -> URec k Double p -> URec k Double p Source

min :: URec k Double p -> URec k Double p -> URec k Double p Source

Show (URec k Double p)

Methods

showsPrec :: Int -> URec k Double p -> ShowS Source

show :: URec k Double p -> String Source

showList :: [URec k Double p] -> ShowS Source

Generic (URec k Double p)

Associated Types

type Rep (URec k Double p) :: * -> * Source

Methods

from :: URec k Double p -> Rep (URec k Double p) x Source

to :: Rep (URec k Double p) x -> URec k Double p Source

data URec k Double

Used for marking occurrences of Double#

Since: 4.9.0.0

type Rep1 k (URec k Double)
type Rep1 k (URec k Double) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UDouble" PrefixI True) (S1 k (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UDouble k)))
type Rep (URec k Double p)
type Rep (URec k Double p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UDouble" PrefixI True) (S1 * (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UDouble *)))

data Char :: * Source

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) 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

Bounded Char

Since: 2.1

Enum Char

Since: 2.1

Eq Char

Methods

(==) :: Char -> Char -> Bool Source

(/=) :: Char -> Char -> Bool Source

Data Char

Since: 4.0.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char Source

Ord Char

Methods

compare :: Char -> Char -> Ordering Source

(<) :: Char -> Char -> Bool Source

(<=) :: Char -> Char -> Bool Source

(>) :: Char -> Char -> Bool Source

(>=) :: Char -> Char -> Bool Source

max :: Char -> Char -> Char Source

min :: Char -> Char -> Char Source

Read Char

Since: 2.1

Show Char

Since: 2.1

Ix Char

Since: 2.1

Methods

range :: (Char, Char) -> [Char] Source

index :: (Char, Char) -> Char -> Int Source

unsafeIndex :: (Char, Char) -> Char -> Int

inRange :: (Char, Char) -> Char -> Bool Source

rangeSize :: (Char, Char) -> Int Source

unsafeRangeSize :: (Char, Char) -> Int

Storable Char

Since: 2.1

IsChar Char

Since: 2.1

Methods

toChar :: Char -> Char Source

fromChar :: Char -> Char Source

PrintfArg Char

Since: 2.1

Generic1 k (URec k Char)

Associated Types

type Rep1 (URec k Char) (f :: URec k Char -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k Char) f a Source

to1 :: Rep1 (URec k Char) f a -> f a Source

Functor (URec * Char)

Methods

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

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

Foldable (URec * Char)

Methods

fold :: Monoid m => URec * Char m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Char a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Char a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Char a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Char a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Char a -> b Source

foldr1 :: (a -> a -> a) -> URec * Char a -> a Source

foldl1 :: (a -> a -> a) -> URec * Char a -> a Source

toList :: URec * Char a -> [a] Source

null :: URec * Char a -> Bool Source

length :: URec * Char a -> Int Source

elem :: Eq a => a -> URec * Char a -> Bool Source

maximum :: Ord a => URec * Char a -> a Source

minimum :: Ord a => URec * Char a -> a Source

sum :: Num a => URec * Char a -> a Source

product :: Num a => URec * Char a -> a Source

Traversable (URec * Char)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Char a -> f (URec * Char b) Source

sequenceA :: Applicative f => URec * Char (f a) -> f (URec * Char a) Source

mapM :: Monad m => (a -> m b) -> URec * Char a -> m (URec * Char b) Source

sequence :: Monad m => URec * Char (m a) -> m (URec * Char a) Source

Eq (URec k Char p)

Methods

(==) :: URec k Char p -> URec k Char p -> Bool Source

(/=) :: URec k Char p -> URec k Char p -> Bool Source

Ord (URec k Char p)

Methods

compare :: URec k Char p -> URec k Char p -> Ordering Source

(<) :: URec k Char p -> URec k Char p -> Bool Source

(<=) :: URec k Char p -> URec k Char p -> Bool Source

(>) :: URec k Char p -> URec k Char p -> Bool Source

(>=) :: URec k Char p -> URec k Char p -> Bool Source

max :: URec k Char p -> URec k Char p -> URec k Char p Source

min :: URec k Char p -> URec k Char p -> URec k Char p Source

Show (URec k Char p)

Methods

showsPrec :: Int -> URec k Char p -> ShowS Source

show :: URec k Char p -> String Source

showList :: [URec k Char p] -> ShowS Source

Generic (URec k Char p)

Associated Types

type Rep (URec k Char p) :: * -> * Source

Methods

from :: URec k Char p -> Rep (URec k Char p) x Source

to :: Rep (URec k Char p) x -> URec k Char p Source

data URec k Char

Used for marking occurrences of Char#

Since: 4.9.0.0

data URec k Char = UChar {}
type Rep1 k (URec k Char)
type Rep1 k (URec k Char) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UChar" PrefixI True) (S1 k (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UChar k)))
type Rep (URec k Char p)
type Rep (URec k Char p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UChar" PrefixI True) (S1 * (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UChar *)))

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

Generic1 k (URec k (Ptr ()))

Associated Types

type Rep1 (URec k (Ptr ())) (f :: URec k (Ptr ()) -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (URec k (Ptr ())) f a Source

to1 :: Rep1 (URec k (Ptr ())) f a -> f a Source

Eq (Ptr a)

Methods

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

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

Data a => Data (Ptr a)

Since: 4.8.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source

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

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

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

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

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

Ord (Ptr a)

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

Show (Ptr a)

Since: 2.1

Methods

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

show :: Ptr a -> String Source

showList :: [Ptr a] -> ShowS Source

Storable (Ptr a)

Since: 2.1

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

Functor (URec * (Ptr ()))

Methods

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

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

Foldable (URec * (Ptr ()))

Methods

fold :: Monoid m => URec * (Ptr ()) m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * (Ptr ()) a -> m Source

foldr :: (a -> b -> b) -> b -> URec * (Ptr ()) a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * (Ptr ()) a -> b Source

foldl :: (b -> a -> b) -> b -> URec * (Ptr ()) a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * (Ptr ()) a -> b Source

foldr1 :: (a -> a -> a) -> URec * (Ptr ()) a -> a Source

foldl1 :: (a -> a -> a) -> URec * (Ptr ()) a -> a Source

toList :: URec * (Ptr ()) a -> [a] Source

null :: URec * (Ptr ()) a -> Bool Source

length :: URec * (Ptr ()) a -> Int Source

elem :: Eq a => a -> URec * (Ptr ()) a -> Bool Source

maximum :: Ord a => URec * (Ptr ()) a -> a Source

minimum :: Ord a => URec * (Ptr ()) a -> a Source

sum :: Num a => URec * (Ptr ()) a -> a Source

product :: Num a => URec * (Ptr ()) a -> a Source

Traversable (URec * (Ptr ()))

Methods

traverse :: Applicative f => (a -> f b) -> URec * (Ptr ()) a -> f (URec * (Ptr ()) b) Source

sequenceA :: Applicative f => URec * (Ptr ()) (f a) -> f (URec * (Ptr ()) a) Source

mapM :: Monad m => (a -> m b) -> URec * (Ptr ()) a -> m (URec * (Ptr ()) b) Source

sequence :: Monad m => URec * (Ptr ()) (m a) -> m (URec * (Ptr ()) a) Source

Eq (URec k (Ptr ()) p)

Methods

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

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

Ord (URec k (Ptr ()) p)

Methods

compare :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Ordering Source

(<) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool Source

(<=) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool Source

(>) :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> Bool Source

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

max :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> URec k (Ptr ()) p Source

min :: URec k (Ptr ()) p -> URec k (Ptr ()) p -> URec k (Ptr ()) p Source

Generic (URec k (Ptr ()) p)

Associated Types

type Rep (URec k (Ptr ()) p) :: * -> * Source

Methods

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

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

data URec k (Ptr ())

Used for marking occurrences of Addr#

Since: 4.9.0.0

data URec k (Ptr ()) = UAddr {}
type Rep1 k (URec k (Ptr ()))
type Rep1 k (URec k (Ptr ())) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UAddr" PrefixI True) (S1 k (MetaSel (Just Symbol "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UAddr k)))
type Rep (URec k (Ptr ()) p)
type Rep (URec k (Ptr ()) p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UAddr" PrefixI True) (S1 * (MetaSel (Just Symbol "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UAddr *)))

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

Eq (FunPtr a)

Methods

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

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

Ord (FunPtr a)

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

Show (FunPtr a)

Since: 2.1

Methods

showsPrec :: Int -> FunPtr a -> ShowS Source

show :: FunPtr a -> String Source

showList :: [FunPtr a] -> ShowS Source

Storable (FunPtr a)

Since: 2.1

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

The maximum tuple size

maxTupleSize :: Int Source

Primitive operations

module GHC.Prim

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)

uncheckedShiftL64# :: Word# -> Int# -> Word# Source

uncheckedShiftRL64# :: Word# -> Int# -> Word# Source

uncheckedIShiftL64# :: Int# -> Int# -> Int# Source

uncheckedIShiftRA64# :: Int# -> Int# -> Int# Source

isTrue# :: Int# -> Bool Source

Alias for tagToEnum#. Returns True if its parameter is 1# and False if it is 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 string literals

class IsString a where Source

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a Source

Instances

(~) * a Char => IsString [a]

(a ~ Char) context was introduced in 4.9.0.0

Since: 2.1

Methods

fromString :: String -> [a] Source

IsString a => IsString (Identity a)

Methods

fromString :: String -> Identity a Source

IsString a => IsString (Const * a b)

Since: 4.9.0.0

Methods

fromString :: String -> Const * a b Source

Debugging

breakpoint :: a -> a Source

breakpointCond :: Bool -> a -> a Source

Ids with special behaviour

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.

Like seq, the argument of lazy can have an unboxed type.

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.

oneShot :: (a -> b) -> a -> b Source

The oneShot function can be used to give a hint to the compiler that its argument will be called at most once, which may (or may not) enable certain optimizations. It can be useful to improve the performance of code in continuation passing style.

If oneShot is used wrongly, then it may be that computations whose result that would otherwise be shared are re-evaluated every time they are used. Otherwise, the use of oneShot is safe.

oneShot is representation polymorphic: the type variables may refer to lifted or unlifted types.

Running RealWorld state transformers

runRW# :: (State# RealWorld -> a) -> a Source

Apply a function to a 'State# RealWorld' token. When manually applying a function to realWorld#, it is necessary to use NOINLINE to prevent semantically undesirable floating. runRW# is inlined, but only very late in compilation after all floating is complete.

Safe coercions

These are available from the Trustworthy module Data.Coerce as well

Since: 4.7.0.0

coerce :: Coercible * a b => a -> b Source

The function coerce allows you to safely convert between values of types that have the same representation with no run-time overhead. In the simplest case you can use it instead of a newtype constructor, to go from the newtype's concrete type to the abstract type. But it also works in more complicated settings, e.g. converting a list of newtypes to a list of concrete types.

class (~R#) k0 k0 a b => Coercible k0 (a :: k0) (b :: k0) Source

Coercible is a two-parameter class that has instances for types a and b if the compiler can infer that they have the same representation. This class does not have regular instances; instead they are created on-the-fly during type-checking. Trying to manually declare an instance of Coercible is an error.

Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:

instance Coercible a a

Furthermore, for every type constructor there is an instance that allows to coerce under the type constructor. For example, let D be a prototypical type constructor (data or newtype) with three type arguments, which have roles nominal, representational resp. phantom. Then there is an instance of the form

instance Coercible b b' => Coercible (D a b c) (D a b' c')

Note that the nominal type arguments are equal, the representational type arguments can differ, but need to have a Coercible instance themself, and the phantom type arguments can be changed arbitrarily.

The third kind of instance exists for every newtype NT = MkNT T and comes in two variants, namely

instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b

This instance is only usable if the constructor MkNT is in scope.

If, as a library author of a type constructor like Set a, you want to prevent a user of your module to write coerce :: Set T -> Set NT, you need to set the role of Set's type parameter to nominal, by writing

type role Set nominal

For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.

Since: 4.7.0.0

Equality

class (~#) k0 k1 a b => (k0 ~~ k1) (a :: k0) (b :: k1) Source

Lifted, heterogeneous equality. By lifted, we mean that it can be bogus (deferred type error). By heterogeneous, the two types a and b might have different kinds. Because ~~ can appear unexpectedly in error messages to users who do not care about the difference between heterogeneous equality ~~ and homogeneous equality ~, this is printed as ~ unless -fprint-equality-relations is set.

Representation polymorphism

data TYPE (a :: RuntimeRep) :: RuntimeRep -> * Source

Instances

Functor f => Generic1 k ((:.:) * k f g)

Associated Types

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

Methods

from1 :: f a -> Rep1 ((* :.: k) f g) f a Source

to1 :: Rep1 ((* :.: k) f g) f a -> f a Source

Functor f => Generic1 k (Compose * k f g)

Associated Types

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

Methods

from1 :: f a -> Rep1 (Compose * k f g) f a Source

to1 :: Rep1 (Compose * k f g) f a -> f a Source

Monad (U1 *)

Since: 4.9.0.0

Methods

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

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

return :: a -> U1 * a Source

fail :: String -> U1 * a Source

Monad (Proxy *)

Since: 4.7.0.0

Methods

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

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

return :: a -> Proxy * a Source

fail :: String -> Proxy * a Source

Functor (V1 *)

Methods

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

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

Functor (U1 *)

Since: 4.9.0.0

Methods

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

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

Functor (Proxy *)

Since: 4.7.0.0

Methods

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

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

Applicative (U1 *)

Since: 4.9.0.0

Methods

pure :: a -> U1 * a Source

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

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

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

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

Applicative (Proxy *)

Since: 4.7.0.0

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

Foldable (V1 *)

Methods

fold :: Monoid m => V1 * m -> m Source

foldMap :: Monoid m => (a -> m) -> V1 * a -> m Source

foldr :: (a -> b -> b) -> b -> V1 * a -> b Source

foldr' :: (a -> b -> b) -> b -> V1 * a -> b Source

foldl :: (b -> a -> b) -> b -> V1 * a -> b Source

foldl' :: (b -> a -> b) -> b -> V1 * a -> b Source

foldr1 :: (a -> a -> a) -> V1 * a -> a Source

foldl1 :: (a -> a -> a) -> V1 * a -> a Source

toList :: V1 * a -> [a] Source

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

Foldable (U1 *)

Since: 4.9.0.0

Methods

fold :: Monoid m => U1 * m -> m Source

foldMap :: Monoid m => (a -> m) -> U1 * a -> m Source

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

foldr' :: (a -> b -> b) -> b -> U1 * a -> b Source

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

foldl' :: (b -> a -> b) -> b -> U1 * a -> b Source

foldr1 :: (a -> a -> a) -> U1 * a -> a Source

foldl1 :: (a -> a -> a) -> U1 * a -> a Source

toList :: U1 * a -> [a] Source

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 (Proxy *)

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m Source

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m Source

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

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b Source

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

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b Source

foldr1 :: (a -> a -> a) -> Proxy * a -> a Source

foldl1 :: (a -> a -> a) -> Proxy * a -> a Source

toList :: Proxy * a -> [a] Source

null :: Proxy * a -> Bool Source

length :: Proxy * a -> Int Source

elem :: Eq a => a -> Proxy * a -> Bool Source

maximum :: Ord a => Proxy * a -> a Source

minimum :: Ord a => Proxy * a -> a Source

sum :: Num a => Proxy * a -> a Source

product :: Num a => Proxy * a -> a Source

Traversable (V1 *)

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

Traversable (U1 *)

Since: 4.9.0.0

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 (Proxy *)

Since: 4.7.0.0

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

MonadPlus (U1 *)

Since: 4.9.0.0

Methods

mzero :: U1 * a Source

mplus :: U1 * a -> U1 * a -> U1 * a Source

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a Source

mplus :: Proxy * a -> Proxy * a -> Proxy * a Source

Alternative (U1 *)

Since: 4.9.0.0

Methods

empty :: U1 * a Source

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

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

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

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a Source

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

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

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

MonadZip (U1 *)

Since: 4.9.0.0

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

MonadZip (Proxy *)

Since: 4.9.0.0

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

Show2 (Const *)

Since: 4.9.0.0

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

Read2 (Const *)

Since: 4.9.0.0

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

Ord2 (Const *)

Since: 4.9.0.0

Methods

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

Eq2 (Const *)

Since: 4.9.0.0

Methods

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

Show1 (Proxy *)

Since: 4.9.0.0

Methods

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

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

Read1 (Proxy *)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) Source

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] Source

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy * a) Source

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy * a] Source

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

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

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

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

Bifunctor (Const *)

Since: 4.8.0.0

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

Bifoldable (Const *)

Since: 4.10.0.0

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

Bitraversable (Const *)

Since: 4.10.0.0

Methods

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

Generic1 * []

Associated Types

type Rep1 [] (f :: [] -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 [] f a Source

to1 :: Rep1 [] f a -> f a Source

Generic1 * Maybe

Associated Types

type Rep1 Maybe (f :: Maybe -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Maybe f a Source

to1 :: Rep1 Maybe f a -> f a Source

Generic1 * Par1

Associated Types

type Rep1 Par1 (f :: Par1 -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Par1 f a Source

to1 :: Rep1 Par1 f a -> f a Source

Generic1 * Last

Associated Types

type Rep1 Last (f :: Last -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Last f a Source

to1 :: Rep1 Last f a -> f a Source

Generic1 * First

Associated Types

type Rep1 First (f :: First -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 First f a Source

to1 :: Rep1 First f a -> f a Source

Generic1 * Product

Associated Types

type Rep1 Product (f :: Product -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Product f a Source

to1 :: Rep1 Product f a -> f a Source

Generic1 * Sum

Associated Types

type Rep1 Sum (f :: Sum -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Sum f a Source

to1 :: Rep1 Sum f a -> f a Source

Generic1 * Dual

Associated Types

type Rep1 Dual (f :: Dual -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Dual f a Source

to1 :: Rep1 Dual f a -> f a Source

Generic1 * Identity

Associated Types

type Rep1 Identity (f :: Identity -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Identity f a Source

to1 :: Rep1 Identity f a -> f a Source

Generic1 * ZipList

Associated Types

type Rep1 ZipList (f :: ZipList -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 ZipList f a Source

to1 :: Rep1 ZipList f a -> f a Source

Generic1 * NonEmpty

Associated Types

type Rep1 NonEmpty (f :: NonEmpty -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 NonEmpty f a Source

to1 :: Rep1 NonEmpty f a -> f a Source

Generic1 * Option

Associated Types

type Rep1 Option (f :: Option -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Option f a Source

to1 :: Rep1 Option f a -> f a Source

Generic1 * WrappedMonoid

Associated Types

type Rep1 WrappedMonoid (f :: WrappedMonoid -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 WrappedMonoid f a Source

to1 :: Rep1 WrappedMonoid f a -> f a Source

Generic1 * Last

Associated Types

type Rep1 Last (f :: Last -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Last f a Source

to1 :: Rep1 Last f a -> f a Source

Generic1 * First

Associated Types

type Rep1 First (f :: First -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 First f a Source

to1 :: Rep1 First f a -> f a Source

Generic1 * Max

Associated Types

type Rep1 Max (f :: Max -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Max f a Source

to1 :: Rep1 Max f a -> f a Source

Generic1 * Min

Associated Types

type Rep1 Min (f :: Min -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Min f a Source

to1 :: Rep1 Min f a -> f a Source

Generic1 * Complex

Associated Types

type Rep1 Complex (f :: Complex -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 Complex f a Source

to1 :: Rep1 Complex f a -> f a Source

Generic1 * (Either a)

Associated Types

type Rep1 (Either a) (f :: Either a -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (Either a) f a Source

to1 :: Rep1 (Either a) f a -> f a Source

Generic1 * ((,) a)

Associated Types

type Rep1 ((,) a) (f :: (,) a -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 ((,) a) f a Source

to1 :: Rep1 ((,) a) f a -> f a Source

Generic1 * (WrappedMonad m)

Associated Types

type Rep1 (WrappedMonad m) (f :: WrappedMonad m -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (WrappedMonad m) f a Source

to1 :: Rep1 (WrappedMonad m) f a -> f a Source

Generic1 * (Arg a)

Associated Types

type Rep1 (Arg a) (f :: Arg a -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (Arg a) f a Source

to1 :: Rep1 (Arg a) f a -> f a Source

Monad m => Category * (Kleisli m)

Since: 3.0

Methods

id :: cat a a Source

(.) :: cat b c -> cat a b -> cat a c Source

Generic1 * ((,,) a b)

Associated Types

type Rep1 ((,,) a b) (f :: (,,) a b -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 ((,,) a b) f a Source

to1 :: Rep1 ((,,) a b) f a -> f a Source

Generic1 * (WrappedArrow a b)

Associated Types

type Rep1 (WrappedArrow a b) (f :: WrappedArrow a b -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 (WrappedArrow a b) f a Source

to1 :: Rep1 (WrappedArrow a b) f a -> f a Source

Category * ((->) LiftedRep LiftedRep)

Since: 3.0

Methods

id :: cat a a Source

(.) :: cat b c -> cat a b -> cat a c Source

Generic1 * ((,,,) a b c)

Associated Types

type Rep1 ((,,,) a b c) (f :: (,,,) a b c -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 ((,,,) a b c) f a Source

to1 :: Rep1 ((,,,) a b c) f a -> f a Source

Generic1 * ((,,,,) a b c d)

Associated Types

type Rep1 ((,,,,) a b c d) (f :: (,,,,) a b c d -> *) :: k -> * Source

Methods

from1 :: f a -> Rep1 ((,,,,) a b c d) f a Source

to1 :: Rep1 ((,,,,) a b c d) f a -> f a Source

Generic1 * ((,,,,,) a b c d e)

Associated Types

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

Methods

from1 :: f a -> Rep1 ((,,,,,) a b c d e) f a Source

to1 :: Rep1 ((,,,,,) a b c d e) f a -> f a Source

Generic1 * ((,,,,,,) a b c d e f)

Associated Types

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

Methods

from1 :: f a -> Rep1 ((,,,,,,) a b c d e f) f a Source

to1 :: Rep1 ((,,,,,,) a b c d e f) f a -> f a Source

Monad f => Monad (Rec1 * f)

Since: 4.9.0.0

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

fail :: String -> Rec1 * f a Source

Monad f => Monad (Alt * f)

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

fail :: String -> Alt * f a Source

Data p => Data (V1 * p)

Since: 4.9.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 * p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> V1 * p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 * p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 * p -> m (V1 * p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 * p -> m (V1 * p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 * p -> m (V1 * p) Source

Data p => Data (U1 * p)

Since: 4.9.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> U1 * p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> U1 * p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> U1 * p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> U1 * p -> m (U1 * p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 * p -> m (U1 * p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> U1 * p -> m (U1 * p) Source

Data t => Data (Proxy * t)

Since: 4.7.0.0

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Proxy * t)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Proxy * t)) Source

gmapT :: (forall b. Data b => b -> b) -> Proxy * t -> Proxy * t Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Proxy * t -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy * t -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) Source

Functor f => Functor (Rec1 * f)

Methods

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

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

Functor (URec * Char)

Methods

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

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

Functor (URec * Double)

Methods

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

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

Functor (URec * Float)

Methods

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

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

Functor (URec * Int)

Methods

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

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

Functor (URec * Word)

Methods

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

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

Functor (URec * (Ptr ()))

Methods

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

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

Functor f => Functor (Alt * f)

Methods

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

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

Functor (Const * m)

Since: 2.1

Methods

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

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

MonadFix f => MonadFix (Rec1 * f)

Since: 4.9.0.0

Methods

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

MonadFix f => MonadFix (Alt * f)

Since: 4.8.0.0

Methods

mfix :: (a -> Alt * f a) -> Alt * f a Source

Applicative f => Applicative (Rec1 * f)

Since: 4.9.0.0

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

Applicative f => Applicative (Alt * f)

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

Monoid m => Applicative (Const * m)

Since: 2.0.1

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

Foldable f => Foldable (Rec1 * f)

Methods

fold :: Monoid m => Rec1 * f m -> m Source

foldMap :: Monoid m => (a -> m) -> Rec1 * f a -> m Source

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

foldr' :: (a -> b -> b) -> b -> Rec1 * f a -> b Source

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

foldl' :: (b -> a -> b) -> b -> Rec1 * f a -> b Source

foldr1 :: (a -> a -> a) -> Rec1 * f a -> a Source

foldl1 :: (a -> a -> a) -> Rec1 * f a -> a Source

toList :: Rec1 * f a -> [a] Source

null :: Rec1 * f a -> Bool Source

length :: Rec1 * f a -> Int Source

elem :: Eq a => a -> Rec1 * f a -> Bool Source

maximum :: Ord a => Rec1 * f a -> a Source

minimum :: Ord a => Rec1 * f a -> a Source

sum :: Num a => Rec1 * f a -> a Source

product :: Num a => Rec1 * f a -> a Source

Foldable (URec * Char)

Methods

fold :: Monoid m => URec * Char m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Char a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Char a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Char a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Char a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Char a -> b Source

foldr1 :: (a -> a -> a) -> URec * Char a -> a Source

foldl1 :: (a -> a -> a) -> URec * Char a -> a Source

toList :: URec * Char a -> [a] Source

null :: URec * Char a -> Bool Source

length :: URec * Char a -> Int Source

elem :: Eq a => a -> URec * Char a -> Bool Source

maximum :: Ord a => URec * Char a -> a Source

minimum :: Ord a => URec * Char a -> a Source

sum :: Num a => URec * Char a -> a Source

product :: Num a => URec * Char a -> a Source

Foldable (URec * Double)

Methods

fold :: Monoid m => URec * Double m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Double a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Double a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Double a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Double a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Double a -> b Source

foldr1 :: (a -> a -> a) -> URec * Double a -> a Source

foldl1 :: (a -> a -> a) -> URec * Double a -> a Source

toList :: URec * Double a -> [a] Source

null :: URec * Double a -> Bool Source

length :: URec * Double a -> Int Source

elem :: Eq a => a -> URec * Double a -> Bool Source

maximum :: Ord a => URec * Double a -> a Source

minimum :: Ord a => URec * Double a -> a Source

sum :: Num a => URec * Double a -> a Source

product :: Num a => URec * Double a -> a Source

Foldable (URec * Float)

Methods

fold :: Monoid m => URec * Float m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Float a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Float a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Float a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Float a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Float a -> b Source

foldr1 :: (a -> a -> a) -> URec * Float a -> a Source

foldl1 :: (a -> a -> a) -> URec * Float a -> a Source

toList :: URec * Float a -> [a] Source

null :: URec * Float a -> Bool Source

length :: URec * Float a -> Int Source

elem :: Eq a => a -> URec * Float a -> Bool Source

maximum :: Ord a => URec * Float a -> a Source

minimum :: Ord a => URec * Float a -> a Source

sum :: Num a => URec * Float a -> a Source

product :: Num a => URec * Float a -> a Source

Foldable (URec * Int)

Methods

fold :: Monoid m => URec * Int m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Int a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Int a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b Source

foldr1 :: (a -> a -> a) -> URec * Int a -> a Source

foldl1 :: (a -> a -> a) -> URec * Int a -> a Source

toList :: URec * Int a -> [a] Source

null :: URec * Int a -> Bool Source

length :: URec * Int a -> Int Source

elem :: Eq a => a -> URec * Int a -> Bool Source

maximum :: Ord a => URec * Int a -> a Source

minimum :: Ord a => URec * Int a -> a Source

sum :: Num a => URec * Int a -> a Source

product :: Num a => URec * Int a -> a Source

Foldable (URec * Word)

Methods

fold :: Monoid m => URec * Word m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * Word a -> m Source

foldr :: (a -> b -> b) -> b -> URec * Word a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * Word a -> b Source

foldl :: (b -> a -> b) -> b -> URec * Word a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * Word a -> b Source

foldr1 :: (a -> a -> a) -> URec * Word a -> a Source

foldl1 :: (a -> a -> a) -> URec * Word a -> a Source

toList :: URec * Word a -> [a] Source

null :: URec * Word a -> Bool Source

length :: URec * Word a -> Int Source

elem :: Eq a => a -> URec * Word a -> Bool Source

maximum :: Ord a => URec * Word a -> a Source

minimum :: Ord a => URec * Word a -> a Source

sum :: Num a => URec * Word a -> a Source

product :: Num a => URec * Word a -> a Source

Foldable (URec * (Ptr ()))

Methods

fold :: Monoid m => URec * (Ptr ()) m -> m Source

foldMap :: Monoid m => (a -> m) -> URec * (Ptr ()) a -> m Source

foldr :: (a -> b -> b) -> b -> URec * (Ptr ()) a -> b Source

foldr' :: (a -> b -> b) -> b -> URec * (Ptr ()) a -> b Source

foldl :: (b -> a -> b) -> b -> URec * (Ptr ()) a -> b Source

foldl' :: (b -> a -> b) -> b -> URec * (Ptr ()) a -> b Source

foldr1 :: (a -> a -> a) -> URec * (Ptr ()) a -> a Source

foldl1 :: (a -> a -> a) -> URec * (Ptr ()) a -> a Source

toList :: URec * (Ptr ()) a -> [a] Source

null :: URec * (Ptr ()) a -> Bool Source

length :: URec * (Ptr ()) a -> Int Source

elem :: Eq a => a -> URec * (Ptr ()) a -> Bool Source

maximum :: Ord a => URec * (Ptr ()) a -> a Source

minimum :: Ord a => URec * (Ptr ()) a -> a Source

sum :: Num a => URec * (Ptr ()) a -> a Source

product :: Num a => URec * (Ptr ()) a -> a Source

Foldable (Const * m)

Since: 4.7.0.0

Methods

fold :: Monoid m => Const * m m -> m Source

foldMap :: Monoid m => (a -> m) -> Const * m a -> m 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

Traversable f => Traversable (Rec1 * f)

Methods

traverse :: Applicative f => (a -> f b) -> Rec1 * f a -> f (Rec1 * f b) Source

sequenceA :: Applicative f => Rec1 * f (f a) -> f (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

Traversable (URec * Char)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Char a -> f (URec * Char b) Source

sequenceA :: Applicative f => URec * Char (f a) -> f (URec * Char a) Source

mapM :: Monad m => (a -> m b) -> URec * Char a -> m (URec * Char b) Source

sequence :: Monad m => URec * Char (m a) -> m (URec * Char a) Source

Traversable (URec * Double)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Double a -> f (URec * Double b) Source

sequenceA :: Applicative f => URec * Double (f a) -> f (URec * Double a) Source

mapM :: Monad m => (a -> m b) -> URec * Double a -> m (URec * Double b) Source

sequence :: Monad m => URec * Double (m a) -> m (URec * Double a) Source

Traversable (URec * Float)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Float a -> f (URec * Float b) Source

sequenceA :: Applicative f => URec * Float (f a) -> f (URec * Float a) Source

mapM :: Monad m => (a -> m b) -> URec * Float a -> m (URec * Float b) Source

sequence :: Monad m => URec * Float (m a) -> m (URec * Float a) Source

Traversable (URec * Int)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) Source

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) Source

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) Source

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) Source

Traversable (URec * Word)

Methods

traverse :: Applicative f => (a -> f b) -> URec * Word a -> f (URec * Word b) Source

sequenceA :: Applicative f => URec * Word (f a) -> f (URec * Word a) Source

mapM :: Monad m => (a -> m b) -> URec * Word a -> m (URec * Word b) Source

sequence :: Monad m => URec * Word (m a) -> m (URec * Word a) Source

Traversable (URec * (Ptr ()))

Methods

traverse :: Applicative f => (a -> f b) -> URec * (Ptr ()) a -> f (URec * (Ptr ()) b) Source

sequenceA :: Applicative f => URec * (Ptr ()) (f a) -> f (URec * (Ptr ()) a) Source

mapM :: Monad m => (a -> m b) -> URec * (Ptr ()) a -> m (URec * (Ptr ()) b) Source

sequence :: Monad m => URec * (Ptr ()) (m a) -> m (URec * (Ptr ()) a) Source

Traversable (Const * m)

Since: 4.7.0.0

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 m => (a -> m b) -> Const * m a -> m (Const * m b) Source

sequence :: Monad m => Const * m (m a) -> m (Const * m a) Source

MonadPlus f => MonadPlus (Rec1 * f)

Since: 4.9.0.0

Methods

mzero :: Rec1 * f a Source

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

MonadPlus f => MonadPlus (Alt * f)

Methods

mzero :: Alt * f a Source

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

Alternative f => Alternative (Rec1 * f)

Since: 4.9.0.0

Methods

empty :: Rec1 * f a Source

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

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

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

Alternative f => Alternative (Alt * f)

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

MonadZip f => MonadZip (Rec1 * f)

Since: 4.9.0.0

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

MonadZip f => MonadZip (Alt * f)

Since: 4.8.0.0

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

Show a => Show1 (Const * a)

Since: 4.9.0.0

Methods

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

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

Read a => Read1 (Const * a)

Since: 4.9.0.0

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Const * a a] Source

Ord a => Ord1 (Const * a)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Const * a a -> Const * a b -> Ordering Source

Eq a => Eq1 (Const * a)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Const * a a -> Const * a b -> Bool Source

Bifunctor (K1 * i)

Since: 4.9.0.0

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

Bifoldable (K1 * i)

Since: 4.10.0.0

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

Bitraversable (K1 * i)

Since: 4.10.0.0

Methods

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

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

Since: 4.9.0.0

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

fail :: String -> (* :*: f) g a Source

(Monad f, Monad g) => Monad (Product * f g)

Since: 4.9.0.0

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

fail :: String -> Product * f g a Source

(Data (f p), Typeable (* -> *) f, Data p) => Data (Rec1 * f p)

Since: 4.9.0.0

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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rec1 * f p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Rec1 * f p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rec1 * f p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rec1 * f p -> m (Rec1 * f p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 * f p -> m (Rec1 * f p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rec1 * f p -> m (Rec1 * f p) Source

((~) * a b, Data a) => Data ((:~:) * a b)

Since: 4.7.0.0

Methods

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

gunfold :: (forall c r. Data c => c (c -> 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 c. Data c => c -> c) -> (* :~: a) b -> (* :~: a) b Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (* :~: a) b -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (* :~: a) b -> r Source

gmapQ :: (forall d. Data d => d -> u) -> (* :~: a) b -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> (* :~: a) b -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) Source

(Coercible * a b, Data a, Data b) => Data (Coercion * a b)

Since: 4.7.0.0

Methods

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

gunfold :: (forall c r. Data c => c (c -> 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 c. Data c => c -> c) -> Coercion * a b -> Coercion * a b Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion * a b -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion * a b -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Coercion * a b -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion * a b -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

(Data (f a), Data a, Typeable (* -> *) f) => Data (Alt * f a)

Since: 4.8.0.0

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

Functor (K1 * i c)

Methods

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

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

(Functor g, Functor f) => Functor ((:+:) * f g)

Methods

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

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

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

Methods

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

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

(Functor f, Functor g) => Functor (Sum * f g)

Since: 4.9.0.0

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 (Product * f g)

Since: 4.9.0.0

Methods

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

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

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

Since: 4.9.0.0

Methods

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

(MonadFix f, MonadFix g) => MonadFix (Product * f g)

Since: 4.9.0.0

Methods

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

IsString a => IsString (Const * a b)

Since: 4.9.0.0

Methods

fromString :: String -> Const * a b Source

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

Since: 4.9.0.0

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 g) => Applicative (Product * f g)

Since: 4.9.0.0

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

Foldable (K1 * i c)

Methods

fold :: Monoid m => K1 * i c m -> m Source

foldMap :: Monoid m => (a -> m) -> K1 * i c a -> m Source

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

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

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

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

foldr1 :: (a -> a -> a) -> K1 * i c a -> a Source

foldl1 :: (a -> a -> a) -> K1 * i c a -> a Source

toList :: K1 * i c a -> [a] Source

null :: K1 * i c a -> Bool Source

length :: K1 * i c a -> Int Source

elem :: Eq a => a -> K1 * i c a -> Bool Source

maximum :: Ord a => K1 * i c a -> a Source

minimum :: Ord a => K1 * i c a -> a Source

sum :: Num a => K1 * i c a -> a Source

product :: Num a => K1 * i c a -> a Source

(Foldable f, Foldable g) => Foldable ((:+:) * f g)

Methods

fold :: Monoid m => (* :+: f) g m -> m Source

foldMap :: Monoid m => (a -> m) -> (* :+: f) g a -> m Source

foldr :: (a -> b -> b) -> b -> (* :+: f) g a -> b Source

foldr' :: (a -> b -> b) -> b -> (* :+: f) g a -> b Source

foldl :: (b -> a -> b) -> b -> (* :+: f) g a -> b Source

foldl' :: (b -> a -> b) -> b -> (* :+: f) g a -> b Source

foldr1 :: (a -> a -> a) -> (* :+: f) g a -> a Source

foldl1 :: (a -> a -> a) -> (* :+: f) g a -> a Source

toList :: (* :+: f) g a -> [a] Source

null :: (* :+: f) g a -> Bool Source

length :: (* :+: f) g a -> Int Source

elem :: Eq a => a -> (* :+: f) g a -> Bool Source

maximum :: Ord a => (* :+: f) g a -> a Source

minimum :: Ord a => (* :+: f) g a -> a Source

sum :: Num a => (* :+: f) g a -> a Source

product :: Num a => (* :+: f) g a -> a Source

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

Methods

fold :: Monoid m => (* :*: f) g m -> m Source

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

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

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

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

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

foldr1 :: (a -> a -> a) -> (* :*: f) g a -> a Source

foldl1 :: (a -> a -> a) -> (* :*: f) g a -> a Source

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

null :: (* :*: f) g a -> Bool Source

length :: (* :*: f) g a -> Int Source

elem :: Eq a => a -> (* :*: f) g a -> Bool Source

maximum :: Ord a => (* :*: f) g a -> a Source

minimum :: Ord a => (* :*: f) g a -> a Source

sum :: Num a => (* :*: f) g a -> a Source

product :: Num a => (* :*: f) g a -> a Source

(Foldable f, Foldable g) => Foldable (Sum * f g)

Since: 4.9.0.0

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Foldable f, Foldable g) => Foldable (Product * f g)

Since: 4.9.0.0

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Traversable (K1 * i c)

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

(Traversable f, Traversable g) => Traversable ((:+:) * f g)

Methods

traverse :: Applicative f => (a -> f b) -> (* :+: f) g a -> f ((* :+: f) g b) Source

sequenceA :: Applicative f => (* :+: f) g (f a) -> f ((* :+: 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)

Methods

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

sequenceA :: Applicative f => (* :*: f) g (f a) -> f ((* :*: 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 (Sum * f g)

Since: 4.9.0.0

Methods

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

sequenceA :: Applicative f => Sum * f g (f a) -> f (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 (Product * f g)

Since: 4.9.0.0

Methods

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

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

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

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

Alternative f => Semigroup (Alt * f a)

Since: 4.9.0.0

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

Alternative f => Monoid (Alt * f a)

Since: 4.8.0.0

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

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

Since: 4.9.0.0

Methods

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

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

(MonadPlus f, MonadPlus g) => MonadPlus (Product * f g)

Since: 4.9.0.0

Methods

mzero :: Product * f g a Source

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

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

Since: 4.9.0.0

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 g) => Alternative (Product * f g)

Since: 4.9.0.0

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

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

Since: 4.9.0.0

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

(MonadZip f, MonadZip g) => MonadZip (Product * f g)

Since: 4.9.0.0

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

(Show1 f, Show1 g) => Show1 (Sum * f g)

Since: 4.9.0.0

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

(Show1 f, Show1 g) => Show1 (Product * f g)

Since: 4.9.0.0

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

(Read1 f, Read1 g) => Read1 (Sum * f g)

Since: 4.9.0.0

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

(Read1 f, Read1 g) => Read1 (Product * f g)

Since: 4.9.0.0

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

(Ord1 f, Ord1 g) => Ord1 (Sum * f g)

Since: 4.9.0.0

Methods

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

(Ord1 f, Ord1 g) => Ord1 (Product * f g)

Since: 4.9.0.0

Methods

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

(Eq1 f, Eq1 g) => Eq1 (Sum * f g)

Since: 4.9.0.0

Methods

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

(Eq1 f, Eq1 g) => Eq1 (Product * f g)

Since: 4.9.0.0

Methods

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

(Eq1 f, Eq1 g, Eq a) => Eq (Sum * f g a)

Since: 4.9.0.0

Methods

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

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

(Eq1 f, Eq1 g, Eq a) => Eq (Product * f g a)

Since: 4.9.0.0

Methods

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

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

Monad f => Monad (M1 * i c f)

Since: 4.9.0.0

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

fail :: String -> M1 * i c f a Source

(Typeable * i, Data p, Data c) => Data (K1 * i c p)

Since: 4.9.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> K1 * i c p -> c (K1 * i c p) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (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 => c (t d)) -> Maybe (c (K1 * i c p)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (K1 * i c p)) Source

gmapT :: (forall b. Data b => b -> b) -> K1 * i c p -> K1 * i c p Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> K1 * i c p -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> K1 * i c p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> K1 * i c p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> K1 * i c p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> K1 * i c p -> m (K1 * i c p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 * i c p -> m (K1 * i c p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> K1 * i c p -> m (K1 * i c p) Source

(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:+:) * f g p)

Since: 4.9.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall a. a -> c a) -> (* :+: f) g p -> c ((* :+: f) g p) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((* :+: f) g p) Source

toConstr :: (* :+: f) g p -> Constr Source

dataTypeOf :: (* :+: f) g p -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ((* :+: f) g p)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((* :+: f) g p)) Source

gmapT :: (forall b. Data b => b -> b) -> (* :+: f) g p -> (* :+: f) g p Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (* :+: f) g p -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (* :+: f) g p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> (* :+: f) g p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> (* :+: f) g p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (* :+: f) g p -> m ((* :+: f) g p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :+: f) g p -> m ((* :+: f) g p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :+: f) g p -> m ((* :+: f) g p) Source

(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f p), Data (g p)) => Data ((:*:) * f g p)

Since: 4.9.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall a. a -> c a) -> (* :*: f) g p -> c ((* :*: f) g p) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((* :*: f) g p) Source

toConstr :: (* :*: f) g p -> Constr Source

dataTypeOf :: (* :*: f) g p -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ((* :*: f) g p)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((* :*: f) g p)) Source

gmapT :: (forall b. Data b => b -> b) -> (* :*: f) g p -> (* :*: f) g p Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (* :*: f) g p -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (* :*: f) g p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> (* :*: f) g p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> (* :*: f) g p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (* :*: f) g p -> m ((* :*: f) g p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :*: f) g p -> m ((* :*: f) g p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :*: f) g p -> m ((* :*: f) g p) Source

Functor f => Functor (M1 * i c f)

Methods

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

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

(Functor g, Functor f) => Functor ((:.:) * * f g)

Methods

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

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

(Functor f, Functor g) => Functor (Compose * * f g)

Since: 4.9.0.0

Methods

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

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

(Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a)

Since: 4.9.0.0

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

(Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a)

Since: 4.9.0.0

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

(Read1 f, Read1 g, Read a) => Read (Sum * f g a)

Since: 4.9.0.0

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

(Read1 f, Read1 g, Read a) => Read (Product * f g a)

Since: 4.9.0.0

(Show1 f, Show1 g, Show a) => Show (Sum * f g a)

Since: 4.9.0.0

Methods

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

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

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

(Show1 f, Show1 g, Show a) => Show (Product * f g a)

Since: 4.9.0.0

Methods

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

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

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

MonadFix f => MonadFix (M1 * i c f)

Since: 4.9.0.0

Methods

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

Applicative f => Applicative (M1 * i c f)

Since: 4.9.0.0

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 -> c) -> M1 * i c f a -> M1 * i c f b -> M1 * i c f c 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

(Applicative f, Applicative g) => Applicative ((:.:) * * f g)

Since: 4.9.0.0

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 g) => Applicative (Compose * * f g)

Since: 4.9.0.0

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

Foldable f => Foldable (M1 * i c f)

Methods

fold :: Monoid m => M1 * i c f m -> m Source

foldMap :: Monoid m => (a -> m) -> M1 * i c f a -> m Source

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

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

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

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

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

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

toList :: M1 * i c f a -> [a] Source

null :: M1 * i c f a -> Bool Source

length :: M1 * i c f a -> Int Source

elem :: Eq a => a -> M1 * i c f a -> Bool Source

maximum :: Ord a => M1 * i c f a -> a Source

minimum :: Ord a => M1 * i c f a -> a Source

sum :: Num a => M1 * i c f a -> a Source

product :: Num a => M1 * i c f a -> a Source

(Foldable f, Foldable g) => Foldable ((:.:) * * f g)

Methods

fold :: Monoid m => (* :.: *) f g m -> m Source

foldMap :: Monoid m => (a -> m) -> (* :.: *) f g a -> m Source

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

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

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

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

foldr1 :: (a -> a -> a) -> (* :.: *) f g a -> a Source

foldl1 :: (a -> a -> a) -> (* :.: *) f g a -> a Source

toList :: (* :.: *) f g a -> [a] Source

null :: (* :.: *) f g a -> Bool Source

length :: (* :.: *) f g a -> Int Source

elem :: Eq a => a -> (* :.: *) f g a -> Bool Source

maximum :: Ord a => (* :.: *) f g a -> a Source

minimum :: Ord a => (* :.: *) f g a -> a Source

sum :: Num a => (* :.: *) f g a -> a Source

product :: Num a => (* :.: *) f g a -> a Source

(Foldable f, Foldable g) => Foldable (Compose * * f g)

Since: 4.9.0.0

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Traversable f => Traversable (M1 * i c f)

Methods

traverse :: Applicative f => (a -> f b) -> M1 * i c f a -> f (M1 * i c f b) Source

sequenceA :: Applicative f => M1 * i c f (f a) -> f (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

(Traversable f, Traversable g) => Traversable ((:.:) * * f g)

Methods

traverse :: Applicative f => (a -> f b) -> (* :.: *) f g a -> f ((* :.: *) f g b) Source

sequenceA :: Applicative f => (* :.: *) f g (f a) -> f ((* :.: *) 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 (Compose * * f g)

Since: 4.9.0.0

Methods

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

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

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

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

MonadPlus f => MonadPlus (M1 * i c f)

Since: 4.9.0.0

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

Alternative f => Alternative (M1 * i c f)

Since: 4.9.0.0

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

(Alternative f, Applicative g) => Alternative ((:.:) * * f g)

Since: 4.9.0.0

Methods

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

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

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

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

(Alternative f, Applicative g) => Alternative (Compose * * f g)

Since: 4.9.0.0

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

MonadZip f => MonadZip (M1 * i c f)

Since: 4.9.0.0

Methods

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

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

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

(Show1 f, Show1 g) => Show1 (Compose * * f g)

Since: 4.9.0.0

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

(Read1 f, Read1 g) => Read1 (Compose * * f g)

Since: 4.9.0.0

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

(Ord1 f, Ord1 g) => Ord1 (Compose * * f g)

Since: 4.9.0.0

Methods

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

(Eq1 f, Eq1 g) => Eq1 (Compose * * f g)

Since: 4.9.0.0

Methods

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

(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a)

Since: 4.9.0.0

Methods

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

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

(Data p, Data (f p), Typeable Meta c, Typeable * i, Typeable (* -> *) f) => Data (M1 * i c f p)

Since: 4.9.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> M1 * i c f p -> c (M1 * i c f p) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (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 => c (t d)) -> Maybe (c (M1 * i c f p)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (M1 * i c f p)) Source

gmapT :: (forall b. Data b => b -> b) -> M1 * i c f p -> M1 * i c f p Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> M1 * i c f p -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> M1 * i c f p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> M1 * i c f p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> M1 * i c f p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> M1 * i c f p -> m (M1 * i c f p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 * i c f p -> m (M1 * i c f p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> M1 * i c f p -> m (M1 * i c f p) Source

(Typeable (* -> *) f, Typeable (* -> *) g, Data p, Data (f (g p))) => Data ((:.:) * * f g p)

Since: 4.9.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall a. a -> c a) -> (* :.: *) f g p -> c ((* :.: *) f g p) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((* :.: *) f g p) Source

toConstr :: (* :.: *) f g p -> Constr Source

dataTypeOf :: (* :.: *) f g p -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ((* :.: *) f g p)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((* :.: *) f g p)) Source

gmapT :: (forall b. Data b => b -> b) -> (* :.: *) f g p -> (* :.: *) f g p Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (* :.: *) f g p -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (* :.: *) f g p -> r Source

gmapQ :: (forall d. Data d => d -> u) -> (* :.: *) f g p -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> (* :.: *) f g p -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (* :.: *) f g p -> m ((* :.: *) f g p) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :.: *) f g p -> m ((* :.: *) f g p) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :.: *) f g p -> m ((* :.: *) f g p) Source

(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a)

Since: 4.9.0.0

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

(Read1 f, Read1 g, Read a) => Read (Compose * * f g a)

Since: 4.9.0.0

(Show1 f, Show1 g, Show a) => Show (Compose * * f g a)

Since: 4.9.0.0

Methods

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

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

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

type (==) * a b
type (==) * a b
type Rep1 k ((:.:) * k f g)
type Rep1 k ((:.:) * k f g) = D1 k (MetaData ":.:" "GHC.Generics" "base" True) (C1 k (MetaCons "Comp1" PrefixI True) (S1 k (MetaSel (Just Symbol "unComp1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) * k f (Rec1 k g))))
type Rep1 k (Compose * k f g)
type Rep1 k (Compose * k f g) = D1 k (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 k (MetaCons "Compose" PrefixI True) (S1 k (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) * k f (Rec1 k g))))
type Rep1 * []
type Rep1 * Maybe
type Rep1 * Par1
type Rep1 * Par1 = D1 * (MetaData "Par1" "GHC.Generics" "base" True) (C1 * (MetaCons "Par1" PrefixI True) (S1 * (MetaSel (Just Symbol "unPar1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Last
type Rep1 * Last = D1 * (MetaData "Last" "Data.Monoid" "base" True) (C1 * (MetaCons "Last" PrefixI True) (S1 * (MetaSel (Just Symbol "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * Maybe)))
type Rep1 * First
type Rep1 * First = D1 * (MetaData "First" "Data.Monoid" "base" True) (C1 * (MetaCons "First" PrefixI True) (S1 * (MetaSel (Just Symbol "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * Maybe)))
type Rep1 * Product
type Rep1 * Product = D1 * (MetaData "Product" "Data.Monoid" "base" True) (C1 * (MetaCons "Product" PrefixI True) (S1 * (MetaSel (Just Symbol "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Sum
type Rep1 * Sum = D1 * (MetaData "Sum" "Data.Monoid" "base" True) (C1 * (MetaCons "Sum" PrefixI True) (S1 * (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Dual
type Rep1 * Dual = D1 * (MetaData "Dual" "Data.Monoid" "base" True) (C1 * (MetaCons "Dual" PrefixI True) (S1 * (MetaSel (Just Symbol "getDual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Identity
type Rep1 * Identity = D1 * (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 * (MetaCons "Identity" PrefixI True) (S1 * (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * ZipList
type Rep1 * ZipList = D1 * (MetaData "ZipList" "Control.Applicative" "base" True) (C1 * (MetaCons "ZipList" PrefixI True) (S1 * (MetaSel (Just Symbol "getZipList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * [])))
type Rep1 * NonEmpty
type Rep1 * Option
type Rep1 * Option = D1 * (MetaData "Option" "Data.Semigroup" "base" True) (C1 * (MetaCons "Option" PrefixI True) (S1 * (MetaSel (Just Symbol "getOption") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * Maybe)))
type Rep1 * WrappedMonoid
type Rep1 * WrappedMonoid = D1 * (MetaData "WrappedMonoid" "Data.Semigroup" "base" True) (C1 * (MetaCons "WrapMonoid" PrefixI True) (S1 * (MetaSel (Just Symbol "unwrapMonoid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Last
type Rep1 * Last = D1 * (MetaData "Last" "Data.Semigroup" "base" True) (C1 * (MetaCons "Last" PrefixI True) (S1 * (MetaSel (Just Symbol "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * First
type Rep1 * First = D1 * (MetaData "First" "Data.Semigroup" "base" True) (C1 * (MetaCons "First" PrefixI True) (S1 * (MetaSel (Just Symbol "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Max
type Rep1 * Max = D1 * (MetaData "Max" "Data.Semigroup" "base" True) (C1 * (MetaCons "Max" PrefixI True) (S1 * (MetaSel (Just Symbol "getMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Min
type Rep1 * Min = D1 * (MetaData "Min" "Data.Semigroup" "base" True) (C1 * (MetaCons "Min" PrefixI True) (S1 * (MetaSel (Just Symbol "getMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep1 * Complex
type Rep1 * (Either a)
type Rep1 * ((,) a)
type Rep1 * (WrappedMonad m)
type Rep1 * (WrappedMonad m) = D1 * (MetaData "WrappedMonad" "Control.Applicative" "base" True) (C1 * (MetaCons "WrapMonad" PrefixI True) (S1 * (MetaSel (Just Symbol "unwrapMonad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * m)))
type Rep1 * (Arg a)
type Rep1 * ((,,) a b)
type Rep1 * (WrappedArrow a b)
type Rep1 * (WrappedArrow a b) = D1 * (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 * (MetaCons "WrapArrow" PrefixI True) (S1 * (MetaSel (Just Symbol "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * (a b))))
type Rep1 * ((,,,) a b c)
type Rep1 * ((,,,,) a b c d)
type Rep1 * ((,,,,,) a b c d e)
type Rep1 * ((,,,,,,) a b c d e f)

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

LiftedRep

lifted; represented by a pointer

UnliftedRep

unlifted; represented by a pointer

IntRep

signed, word-sized value

WordRep

unsigned, word-sized value

Int64Rep

signed, 64-bit value (on 32-bit only)

Word64Rep

unsigned, 64-bit value (on 32-bit only)

AddrRep

A pointer, but not to a Haskell value

FloatRep

a 32-bit floating point number

DoubleRep

a 64-bit floating point number

data VecCount :: * Source

Length of a SIMD vector type

Constructors

Vec2
Vec4
Vec8
Vec16
Vec32
Vec64

data VecElem :: * Source

Element of a SIMD vector type

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

Provides Show and Read instances (since: 4.7.0.0).

Since: 4.6.0.0

Constructors

Down a

Instances

Eq a => Eq (Down a)

Methods

(==) :: Down a -> Down a -> Bool Source

(/=) :: Down a -> Down a -> Bool Source

Ord a => Ord (Down a)

Since: 4.6.0.0

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

Read a => Read (Down a)
Show a => Show (Down a)

Methods

showsPrec :: Int -> Down a -> ShowS Source

show :: Down a -> String Source

showList :: [Down a] -> ShowS Source

groupWith :: Ord b => (a -> b) -> [a] -> [[a]] Source

The groupWith function uses the user supplied function which projects an element out of every list element in order to first sort the input list and then to form groups by equality on these projected elements

sortWith :: Ord b => (a -> b) -> [a] -> [a] Source

The sortWith function sorts a list of elements using the user supplied function to project something out of each element

the :: Eq a => [a] -> a Source

the ensures that all the elements of the list are identical and then returns that unique element

Event logging

traceEvent :: String -> IO () Source

Deprecated: Use traceEvent or traceEventIO

SpecConstr annotations

data SpecConstrAnnotation Source

Instances

Eq SpecConstrAnnotation
Data SpecConstrAnnotation

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

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

The Constraint kind

data Constraint :: * Source

The kind of constraints, like Show a

The Any type

type family Any k0 :: k0 where ... Source

The type constructor Any is type to which you can unsafely coerce any lifted type, and back. More concretely, for a lifted type t and value x :: t, -- unsafeCoerce (unsafeCoerce x :: Any) :: t is equivalent to x.

Overloaded lists

class IsList l where Source

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: 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 as a hint. Its behaviour should be equivalent to fromList. The hint can be used to construct the structure l more efficiently compared to fromList. If the given hint does not equal to the input list's length the behaviour of fromListN is not specified.

toList :: l -> [Item l] Source

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

Instances

IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: 4.9.0.0

IsList Version

Since: 4.8.0.0

Associated Types

type Item Version :: * Source

IsList [a]

Since: 4.7.0.0

Associated Types

type Item [a] :: * Source

Methods

fromList :: [Item [a]] -> [a] Source

fromListN :: Int -> [Item [a]] -> [a] Source

toList :: [a] -> [Item [a]] Source

IsList (NonEmpty a)

Since: 4.9.0.0

Associated Types

type Item (NonEmpty a) :: * Source

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a Source

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a Source

toList :: NonEmpty a -> [Item (NonEmpty a)] Source

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.2.1/docs/html/libraries/base-4.10.0.0/GHC-Exts.html