base-4.9.0.0: Basic libraries

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

GHC.Exts

Contents

Description

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

Note: no other base module should import this module.

Synopsis

Representations of some basic types

data Int :: * #

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 Source # 
Enum Int Source # 
Eq Int 

Methods

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

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

Integral Int Source # 

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

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 Source # 
Ord Int 

Methods

compare :: Int -> Int -> Ordering #

(<) :: Int -> Int -> Bool #

(<=) :: Int -> Int -> Bool #

(>) :: Int -> Int -> Bool #

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

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int Source # 
Real Int Source # 
Show Int Source # 
Ix Int Source # 

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 Source # 
Bits Int Source # 
Storable Int Source # 
PrintfArg Int Source # 
Functor (URec Int) Source # 

Methods

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

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

Foldable (URec Int) Source # 

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) Source # 

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 #

Generic1 (URec Int) Source # 

Associated Types

type Rep1 (URec Int :: * -> *) :: * -> * Source #

Methods

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

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

Eq (URec Int p) # 

Methods

(==) :: URec Int p -> URec Int p -> Bool #

(/=) :: URec Int p -> URec Int p -> Bool #

Ord (URec Int p) # 

Methods

compare :: URec Int p -> URec Int p -> Ordering #

(<) :: URec Int p -> URec Int p -> Bool #

(<=) :: URec Int p -> URec Int p -> Bool #

(>) :: URec Int p -> URec Int p -> Bool #

(>=) :: URec Int p -> URec Int p -> Bool #

max :: URec Int p -> URec Int p -> URec Int p #

min :: URec Int p -> URec Int p -> URec Int p #

Show (URec Int p) Source # 
Generic (URec Int p) Source # 

Associated Types

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

Methods

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

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

data URec Int Source #

Used for marking occurrences of Int#

data URec Int = UInt {}
type Rep1 (URec Int) Source # 
type Rep1 (URec Int) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UInt" PrefixI True) (S1 (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UInt))
type Rep (URec Int p) Source # 
type Rep (URec 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 :: * #

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

Constructors

W# Word# 

Instances

Bounded Word Source # 
Enum Word Source # 
Eq Word 

Methods

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

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

Integral Word Source # 
Data Word Source # 

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 Source # 
Ord Word 

Methods

compare :: Word -> Word -> Ordering #

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

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

(>) :: Word -> Word -> Bool #

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

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word Source # 
Real Word Source # 
Show Word Source # 
Ix Word Source # 
FiniteBits Word Source # 
Bits Word Source # 
Storable Word Source # 
PrintfArg Word Source # 
Functor (URec Word) Source # 

Methods

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

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

Foldable (URec Word) Source # 

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) Source # 

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 #

Generic1 (URec Word) Source # 

Associated Types

type Rep1 (URec Word :: * -> *) :: * -> * Source #

Methods

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

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

Eq (URec Word p) # 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) # 

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p) Source # 
Generic (URec Word p) Source # 

Associated Types

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

Methods

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

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

data URec Word Source #

Used for marking occurrences of Word#

data URec Word = UWord {}
type Rep1 (URec Word) Source # 
type Rep1 (URec Word) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))
type Rep (URec Word p) Source # 
type Rep (URec 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 :: * #

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 #

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

Floating Float Source # 
Data Float Source # 

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 

Methods

compare :: Float -> Float -> Ordering #

(<) :: Float -> Float -> Bool #

(<=) :: Float -> Float -> Bool #

(>) :: Float -> Float -> Bool #

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

max :: Float -> Float -> Float #

min :: Float -> Float -> Float #

Read Float Source # 
RealFloat Float Source # 
Storable Float Source # 
PrintfArg Float Source # 
Functor (URec Float) Source # 

Methods

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

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

Foldable (URec Float) Source # 

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) Source # 

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 #

Generic1 (URec Float) Source # 

Associated Types

type Rep1 (URec Float :: * -> *) :: * -> * Source #

Methods

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

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

Eq (URec Float p) # 

Methods

(==) :: URec Float p -> URec Float p -> Bool #

(/=) :: URec Float p -> URec Float p -> Bool #

Ord (URec Float p) # 

Methods

compare :: URec Float p -> URec Float p -> Ordering #

(<) :: URec Float p -> URec Float p -> Bool #

(<=) :: URec Float p -> URec Float p -> Bool #

(>) :: URec Float p -> URec Float p -> Bool #

(>=) :: URec Float p -> URec Float p -> Bool #

max :: URec Float p -> URec Float p -> URec Float p #

min :: URec Float p -> URec Float p -> URec Float p #

Show (URec Float p) Source # 
Generic (URec Float p) Source # 

Associated Types

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

Methods

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

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

data URec Float Source #

Used for marking occurrences of Float#

type Rep1 (URec Float) Source # 
type Rep1 (URec Float) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UFloat" PrefixI True) (S1 (MetaSel (Just Symbol "uFloat#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UFloat))
type Rep (URec Float p) Source # 
type Rep (URec 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 :: * #

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 #

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

Floating Double Source # 
Data Double Source # 

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 Source # 
RealFloat Double Source # 
Storable Double Source # 
PrintfArg Double Source # 
Functor (URec Double) Source # 

Methods

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

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

Foldable (URec Double) Source # 

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) Source # 

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 #

Generic1 (URec Double) Source # 

Associated Types

type Rep1 (URec Double :: * -> *) :: * -> * Source #

Eq (URec Double p) # 

Methods

(==) :: URec Double p -> URec Double p -> Bool #

(/=) :: URec Double p -> URec Double p -> Bool #

Ord (URec Double p) # 

Methods

compare :: URec Double p -> URec Double p -> Ordering #

(<) :: URec Double p -> URec Double p -> Bool #

(<=) :: URec Double p -> URec Double p -> Bool #

(>) :: URec Double p -> URec Double p -> Bool #

(>=) :: URec Double p -> URec Double p -> Bool #

max :: URec Double p -> URec Double p -> URec Double p #

min :: URec Double p -> URec Double p -> URec Double p #

Show (URec Double p) Source # 
Generic (URec Double p) Source # 

Associated Types

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

Methods

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

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

data URec Double Source #

Used for marking occurrences of Double#

type Rep1 (URec Double) Source # 
type Rep1 (URec Double) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UDouble" PrefixI True) (S1 (MetaSel (Just Symbol "uDouble#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UDouble))
type Rep (URec Double p) Source # 
type Rep (URec 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 :: * #

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 Source # 
Enum Char Source # 
Eq Char 

Methods

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

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

Data Char Source # 

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 #

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

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

(>) :: Char -> Char -> Bool #

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

max :: Char -> Char -> Char #

min :: Char -> Char -> Char #

Read Char Source # 
Show Char Source # 
Ix Char Source # 
Storable Char Source # 
IsChar Char Source # 
PrintfArg Char Source # 
Functor (URec Char) Source # 

Methods

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

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

Foldable (URec Char) Source # 

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) Source # 

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 #

Generic1 (URec Char) Source # 

Associated Types

type Rep1 (URec Char :: * -> *) :: * -> * Source #

Methods

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

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

Eq (URec Char p) # 

Methods

(==) :: URec Char p -> URec Char p -> Bool #

(/=) :: URec Char p -> URec Char p -> Bool #

Ord (URec Char p) # 

Methods

compare :: URec Char p -> URec Char p -> Ordering #

(<) :: URec Char p -> URec Char p -> Bool #

(<=) :: URec Char p -> URec Char p -> Bool #

(>) :: URec Char p -> URec Char p -> Bool #

(>=) :: URec Char p -> URec Char p -> Bool #

max :: URec Char p -> URec Char p -> URec Char p #

min :: URec Char p -> URec Char p -> URec Char p #

Show (URec Char p) Source # 
Generic (URec Char p) Source # 

Associated Types

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

Methods

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

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

data URec Char Source #

Used for marking occurrences of Char#

data URec Char = UChar {}
type Rep1 (URec Char) Source # 
type Rep1 (URec Char) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UChar" PrefixI True) (S1 (MetaSel (Just Symbol "uChar#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UChar))
type Rep (URec Char p) Source # 
type Rep (URec 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

Eq (Ptr a) Source # 

Methods

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

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

Data a => Data (Ptr a) Source # 

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 #

Functor (URec (Ptr ())) Source # 

Methods

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

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

Ord (Ptr a) Source # 

Methods

compare :: Ptr a -> Ptr a -> Ordering #

(<) :: Ptr a -> Ptr a -> Bool #

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

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

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

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a) Source # 

Methods

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

show :: Ptr a -> String Source #

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

Foldable (URec (Ptr ())) Source # 

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 ())) Source # 

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 #

Generic1 (URec (Ptr ())) Source # 

Associated Types

type Rep1 (URec (Ptr ()) :: * -> *) :: * -> * Source #

Methods

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

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

Storable (Ptr a) Source # 

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 #

Eq (URec (Ptr ()) p) # 

Methods

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

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

Ord (URec (Ptr ()) p) # 

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

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

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

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

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

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

Associated Types

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

Methods

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

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

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

Used for marking occurrences of Addr#

data URec (Ptr ()) = UAddr {}
type Rep (URec (Ptr ()) p) Source # 
type Rep (URec (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) Source # 

Methods

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

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

Ord (FunPtr a) Source # 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

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

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

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

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a) Source # 
Storable (FunPtr a) Source # 

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

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)

isTrue# :: Int# -> Bool #

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] Source # 

Methods

fromString :: String -> [a] Source #

IsString a => IsString (Identity a) Source # 
IsString a => IsString (Const * a b) Source # 

Methods

fromString :: String -> Const * a b Source #

Debugging

breakpoint :: a -> a Source #

Ids with special behaviour

lazy :: a -> a #

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 #

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.

Safe coercions

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

Since: 4.7.0.0

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

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#) k k a b => Coercible k a b #

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 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 (~#) j k a b => (j ~~ k) a b #

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

Instances

Monad (Proxy *) Source # 

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

Methods

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

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

Applicative (Proxy *) Source # 

Methods

pure :: a -> Proxy * a Source #

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

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

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

Foldable (Proxy *) Source # 

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

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 #

Generic1 (Proxy *) Source # 

Associated Types

type Rep1 (Proxy * :: * -> *) :: * -> * Source #

Methods

from1 :: Proxy * a -> Rep1 (Proxy *) a Source #

to1 :: Rep1 (Proxy *) a -> Proxy * a Source #

MonadPlus (Proxy *) Source # 

Methods

mzero :: Proxy * a Source #

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

Alternative (Proxy *) Source # 

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

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 #

Bifunctor (Const *) Source # 

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 #

Show2 (Const *) Source # 

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 *) Source # 

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 #

Ord2 (Const *) Source # 

Methods

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

Eq2 (Const *) Source # 

Methods

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

Show1 (Proxy *) Source #

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 *) Source #

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 #

Ord1 (Proxy *) Source #

Since: 4.9.0.0

Methods

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

Eq1 (Proxy *) Source #

Since: 4.9.0.0

Methods

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

Category * (->) Source # 

Methods

id :: cat a a Source #

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

Monad m => Category * (Kleisli m) Source # 

Methods

id :: cat a a Source #

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

Monad f => Monad (Alt * f) Source # 

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 t => Data (Proxy * t) Source # 

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 (Alt * f) Source # 

Methods

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

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

Functor (Const * m) Source # 

Methods

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

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

MonadFix f => MonadFix (Alt * f) Source # 

Methods

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

Applicative f => Applicative (Alt * f) Source # 

Methods

pure :: a -> Alt * f a Source #

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b 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) Source # 

Methods

pure :: a -> Const * m a Source #

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

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

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

Foldable (Const * m) Source # 

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 (Const * m) Source # 

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 #

Generic1 (Alt * f) Source # 

Associated Types

type Rep1 (Alt * f :: * -> *) :: * -> * Source #

Methods

from1 :: Alt * f a -> Rep1 (Alt * f) a Source #

to1 :: Rep1 (Alt * f) a -> Alt * f a Source #

Generic1 (Const * a) Source # 

Associated Types

type Rep1 (Const * a :: * -> *) :: * -> * Source #

Methods

from1 :: Const * a a -> Rep1 (Const * a) a Source #

to1 :: Rep1 (Const * a) a -> Const * a a Source #

MonadPlus f => MonadPlus (Alt * f) Source # 

Methods

mzero :: Alt * f a Source #

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

Alternative f => Alternative (Alt * f) Source # 

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 (Alt * f) Source # 

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) Source # 

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) Source # 

Methods

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

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

Ord a => Ord1 (Const * a) Source # 

Methods

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

Eq a => Eq1 (Const * a) Source # 

Methods

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

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

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 #

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

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) Source # 

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) Source # 

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 f, Functor g) => Functor (Product * f g) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

IsString a => IsString (Const * a b) Source # 

Methods

fromString :: String -> Const * a b Source #

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

Methods

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

(<*>) :: Product * f g (a -> b) -> Product * f g a -> Product * f g b 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 f, Foldable g) => Foldable (Product * f g) Source # 

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 #

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

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 #

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

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 #

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

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 #

Generic1 (Product * f g) Source # 

Associated Types

type Rep1 (Product * f g :: * -> *) :: * -> * Source #

Methods

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

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

Generic1 (Sum * f g) Source # 

Associated Types

type Rep1 (Sum * f g :: * -> *) :: * -> * Source #

Methods

from1 :: Sum * f g a -> Rep1 (Sum * f g) a Source #

to1 :: Rep1 (Sum * f g) a -> Sum * f g a Source #

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

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) Source # 

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

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

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

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

Methods

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

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

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

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 #

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

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 #

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

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 #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

min :: Sum * f g a -> Sum * f g a -> Sum * f g a #

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

Methods

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

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b 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 g) => Foldable (Compose * * f g) Source # 

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 g) => Traversable (Compose * * f g) Source # 

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 #

Functor f => Generic1 (Compose * * f g) Source # 

Associated Types

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

Methods

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

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

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

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 #

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

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) Source # 

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 #

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

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 Source # 
type (==) * a b
type Rep1 (Proxy *) Source # 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
type Rep1 (Alt * f) Source # 
type Rep1 (Alt * f) = D1 (MetaData "Alt" "Data.Monoid" "base" True) (C1 (MetaCons "Alt" PrefixI True) (S1 (MetaSel (Just Symbol "getAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep1 (Const * a) Source # 
type Rep1 (Const * a) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 (Product * f g) Source # 
type Rep1 (Sum * f g) Source # 
type Rep1 (Compose * * f g) Source # 
type Rep1 (Compose * * f g) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) f (Rec1 g))))

data RuntimeRep :: * #

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

PtrRepLifted

lifted; represented by a pointer

PtrRepUnlifted

unlifted; represented by a pointer

VoidRep

erased entirely

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

UnboxedTupleRep

An unboxed tuple; this doesn't specify a concrete rep

data VecCount :: * #

Length of a SIMD vector type

Constructors

Vec2 
Vec4 
Vec8 
Vec16 
Vec32 
Vec64 

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) Source # 

Methods

(==) :: Down a -> Down a -> Bool #

(/=) :: Down a -> Down a -> Bool #

Ord a => Ord (Down a) Source # 

Methods

compare :: Down a -> Down a -> Ordering #

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

(<=) :: Down a -> Down a -> Bool #

(>) :: Down a -> Down a -> Bool #

(>=) :: Down a -> Down a -> Bool #

max :: Down a -> Down a -> Down a #

min :: Down a -> Down a -> Down a #

Read a => Read (Down a) Source # 
Show a => Show (Down a) Source # 

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 Source # 
Data SpecConstrAnnotation Source # 

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 maintined 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 :: * #

The kind of constraints, like Show a

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

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: 4.9.0.0

IsList Version Source #

Since: 4.8.0.0

IsList [a] Source # 

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) Source # 

Associated Types

type Item (NonEmpty a) :: * Source #