foundation-0.0.18: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation

Contents

Description

I tried to picture clusters of information As they moved through the computer What do they look like?

Alternative Prelude

Synopsis

Standard

Operators

($) :: (a -> b) -> a -> b infixr 0 #

Application operator. This operator is redundant, since ordinary application (f x) means the same as (f $ x). However, $ has low, right-associative binding precedence, so it sometimes allows parentheses to be omitted; for example:

    f $ g $ h x  =  f (g (h x))

It is also useful in higher-order situations, such as map ($ 0) xs, or zipWith ($) fs xs.

($!) :: (a -> b) -> a -> b infixr 0 #

Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.

(&&) :: Bool -> Bool -> Bool infixr 3 #

Boolean "and"

(||) :: Bool -> Bool -> Bool infixr 2 #

Boolean "or"

(.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 #

morphism composition

Functions

not :: Bool -> Bool #

Boolean "not"

otherwise :: Bool #

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

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

data Tuple2 a b Source #

Strict tuple (a,b)

Constructors

Tuple2 !a !b 

Instances

Bifunctor Tuple2 Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Tuple2 a c -> Tuple2 b d #

first :: (a -> b) -> Tuple2 a c -> Tuple2 b c #

second :: (b -> c) -> Tuple2 a b -> Tuple2 a c #

Nthable 1 (Tuple2 a b) Source # 

Associated Types

type NthTy (1 :: Nat) (Tuple2 a b) :: * Source #

Methods

nth :: proxy 1 -> Tuple2 a b -> NthTy 1 (Tuple2 a b) Source #

Nthable 2 (Tuple2 a b) Source # 

Associated Types

type NthTy (2 :: Nat) (Tuple2 a b) :: * Source #

Methods

nth :: proxy 2 -> Tuple2 a b -> NthTy 2 (Tuple2 a b) Source #

(Eq b, Eq a) => Eq (Tuple2 a b) Source # 

Methods

(==) :: Tuple2 a b -> Tuple2 a b -> Bool #

(/=) :: Tuple2 a b -> Tuple2 a b -> Bool #

(Data b, Data a) => Data (Tuple2 a b) Source # 

Methods

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

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

toConstr :: Tuple2 a b -> Constr #

dataTypeOf :: Tuple2 a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Tuple2 a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tuple2 a b)) #

gmapT :: (forall c. Data c => c -> c) -> Tuple2 a b -> Tuple2 a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tuple2 a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tuple2 a b -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tuple2 a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) #

(Ord b, Ord a) => Ord (Tuple2 a b) Source # 

Methods

compare :: Tuple2 a b -> Tuple2 a b -> Ordering #

(<) :: Tuple2 a b -> Tuple2 a b -> Bool #

(<=) :: Tuple2 a b -> Tuple2 a b -> Bool #

(>) :: Tuple2 a b -> Tuple2 a b -> Bool #

(>=) :: Tuple2 a b -> Tuple2 a b -> Bool #

max :: Tuple2 a b -> Tuple2 a b -> Tuple2 a b #

min :: Tuple2 a b -> Tuple2 a b -> Tuple2 a b #

(Show b, Show a) => Show (Tuple2 a b) Source # 

Methods

showsPrec :: Int -> Tuple2 a b -> ShowS #

show :: Tuple2 a b -> String #

showList :: [Tuple2 a b] -> ShowS #

Generic (Tuple2 a b) Source # 

Associated Types

type Rep (Tuple2 a b) :: * -> * #

Methods

from :: Tuple2 a b -> Rep (Tuple2 a b) x #

to :: Rep (Tuple2 a b) x -> Tuple2 a b #

(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) Source # 

Methods

toNormalForm :: Tuple2 a b -> () #

Sndable (Tuple2 a b) Source # 

Associated Types

type ProductSecond (Tuple2 a b) :: * Source #

Methods

snd :: Tuple2 a b -> ProductSecond (Tuple2 a b) Source #

Fstable (Tuple2 a b) Source # 

Associated Types

type ProductFirst (Tuple2 a b) :: * Source #

Methods

fst :: Tuple2 a b -> ProductFirst (Tuple2 a b) Source #

(Hashable a, Hashable b) => Hashable (Tuple2 a b) Source # 

Methods

hashMix :: Hasher st => Tuple2 a b -> st -> st Source #

type NthTy 1 (Tuple2 a b) Source # 
type NthTy 1 (Tuple2 a b) = a
type NthTy 2 (Tuple2 a b) Source # 
type NthTy 2 (Tuple2 a b) = b
type Rep (Tuple2 a b) Source # 
type Rep (Tuple2 a b) = D1 * (MetaData "Tuple2" "Foundation.Tuple" "foundation-0.0.18-HaogxlJFAJ34vCWw3CWNZE" False) (C1 * (MetaCons "Tuple2" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * b))))
type ProductSecond (Tuple2 a b) Source # 
type ProductSecond (Tuple2 a b) = b
type ProductFirst (Tuple2 a b) Source # 
type ProductFirst (Tuple2 a b) = a

data Tuple3 a b c Source #

Strict tuple (a,b,c)

Constructors

Tuple3 !a !b !c 

Instances

Nthable 1 (Tuple3 a b c) Source # 

Associated Types

type NthTy (1 :: Nat) (Tuple3 a b c) :: * Source #

Methods

nth :: proxy 1 -> Tuple3 a b c -> NthTy 1 (Tuple3 a b c) Source #

Nthable 2 (Tuple3 a b c) Source # 

Associated Types

type NthTy (2 :: Nat) (Tuple3 a b c) :: * Source #

Methods

nth :: proxy 2 -> Tuple3 a b c -> NthTy 2 (Tuple3 a b c) Source #

Nthable 3 (Tuple3 a b c) Source # 

Associated Types

type NthTy (3 :: Nat) (Tuple3 a b c) :: * Source #

Methods

nth :: proxy 3 -> Tuple3 a b c -> NthTy 3 (Tuple3 a b c) Source #

(Eq c, Eq b, Eq a) => Eq (Tuple3 a b c) Source # 

Methods

(==) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(/=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(Data c, Data b, Data a) => Data (Tuple3 a b c) Source # 

Methods

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

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

toConstr :: Tuple3 a b c -> Constr #

dataTypeOf :: Tuple3 a b c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Tuple3 a b c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tuple3 a b c)) #

gmapT :: (forall d. Data d => d -> d) -> Tuple3 a b c -> Tuple3 a b c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tuple3 a b c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tuple3 a b c -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tuple3 a b c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tuple3 a b c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) #

(Ord c, Ord b, Ord a) => Ord (Tuple3 a b c) Source # 

Methods

compare :: Tuple3 a b c -> Tuple3 a b c -> Ordering #

(<) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(<=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(>) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(>=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

max :: Tuple3 a b c -> Tuple3 a b c -> Tuple3 a b c #

min :: Tuple3 a b c -> Tuple3 a b c -> Tuple3 a b c #

(Show c, Show b, Show a) => Show (Tuple3 a b c) Source # 

Methods

showsPrec :: Int -> Tuple3 a b c -> ShowS #

show :: Tuple3 a b c -> String #

showList :: [Tuple3 a b c] -> ShowS #

Generic (Tuple3 a b c) Source # 

Associated Types

type Rep (Tuple3 a b c) :: * -> * #

Methods

from :: Tuple3 a b c -> Rep (Tuple3 a b c) x #

to :: Rep (Tuple3 a b c) x -> Tuple3 a b c #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) Source # 

Methods

toNormalForm :: Tuple3 a b c -> () #

Thdable (Tuple3 a b c) Source # 

Associated Types

type ProductThird (Tuple3 a b c) :: * Source #

Methods

thd :: Tuple3 a b c -> ProductThird (Tuple3 a b c) Source #

Sndable (Tuple3 a b c) Source # 

Associated Types

type ProductSecond (Tuple3 a b c) :: * Source #

Methods

snd :: Tuple3 a b c -> ProductSecond (Tuple3 a b c) Source #

Fstable (Tuple3 a b c) Source # 

Associated Types

type ProductFirst (Tuple3 a b c) :: * Source #

Methods

fst :: Tuple3 a b c -> ProductFirst (Tuple3 a b c) Source #

(Hashable a, Hashable b, Hashable c) => Hashable (Tuple3 a b c) Source # 

Methods

hashMix :: Hasher st => Tuple3 a b c -> st -> st Source #

type NthTy 1 (Tuple3 a b c) Source # 
type NthTy 1 (Tuple3 a b c) = a
type NthTy 2 (Tuple3 a b c) Source # 
type NthTy 2 (Tuple3 a b c) = b
type NthTy 3 (Tuple3 a b c) Source # 
type NthTy 3 (Tuple3 a b c) = c
type Rep (Tuple3 a b c) Source # 
type ProductThird (Tuple3 a b c) Source # 
type ProductThird (Tuple3 a b c) = c
type ProductSecond (Tuple3 a b c) Source # 
type ProductSecond (Tuple3 a b c) = b
type ProductFirst (Tuple3 a b c) Source # 
type ProductFirst (Tuple3 a b c) = a

data Tuple4 a b c d Source #

Strict tuple (a,b,c,d)

Constructors

Tuple4 !a !b !c !d 

Instances

Nthable 1 (Tuple4 a b c d) Source # 

Associated Types

type NthTy (1 :: Nat) (Tuple4 a b c d) :: * Source #

Methods

nth :: proxy 1 -> Tuple4 a b c d -> NthTy 1 (Tuple4 a b c d) Source #

Nthable 2 (Tuple4 a b c d) Source # 

Associated Types

type NthTy (2 :: Nat) (Tuple4 a b c d) :: * Source #

Methods

nth :: proxy 2 -> Tuple4 a b c d -> NthTy 2 (Tuple4 a b c d) Source #

Nthable 3 (Tuple4 a b c d) Source # 

Associated Types

type NthTy (3 :: Nat) (Tuple4 a b c d) :: * Source #

Methods

nth :: proxy 3 -> Tuple4 a b c d -> NthTy 3 (Tuple4 a b c d) Source #

Nthable 4 (Tuple4 a b c d) Source # 

Associated Types

type NthTy (4 :: Nat) (Tuple4 a b c d) :: * Source #

Methods

nth :: proxy 4 -> Tuple4 a b c d -> NthTy 4 (Tuple4 a b c d) Source #

(Eq d, Eq c, Eq b, Eq a) => Eq (Tuple4 a b c d) Source # 

Methods

(==) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(/=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(Data d, Data c, Data b, Data a) => Data (Tuple4 a b c d) Source # 

Methods

gfoldl :: (forall e f. Data e => c (e -> f) -> e -> c f) -> (forall g. g -> c g) -> Tuple4 a b c d -> c (Tuple4 a b c d) #

gunfold :: (forall e r. Data e => c (e -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tuple4 a b c d) #

toConstr :: Tuple4 a b c d -> Constr #

dataTypeOf :: Tuple4 a b c d -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall e. Data e => c (t e)) -> Maybe (c (Tuple4 a b c d)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall e f. (Data e, Data f) => c (t e f)) -> Maybe (c (Tuple4 a b c d)) #

gmapT :: (forall e. Data e => e -> e) -> Tuple4 a b c d -> Tuple4 a b c d #

gmapQl :: (r -> r' -> r) -> r -> (forall e. Data e => e -> r') -> Tuple4 a b c d -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall e. Data e => e -> r') -> Tuple4 a b c d -> r #

gmapQ :: (forall e. Data e => e -> u) -> Tuple4 a b c d -> [u] #

gmapQi :: Int -> (forall e. Data e => e -> u) -> Tuple4 a b c d -> u #

gmapM :: Monad m => (forall e. Data e => e -> m e) -> Tuple4 a b c d -> m (Tuple4 a b c d) #

gmapMp :: MonadPlus m => (forall e. Data e => e -> m e) -> Tuple4 a b c d -> m (Tuple4 a b c d) #

gmapMo :: MonadPlus m => (forall e. Data e => e -> m e) -> Tuple4 a b c d -> m (Tuple4 a b c d) #

(Ord d, Ord c, Ord b, Ord a) => Ord (Tuple4 a b c d) Source # 

Methods

compare :: Tuple4 a b c d -> Tuple4 a b c d -> Ordering #

(<) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(<=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(>) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(>=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

max :: Tuple4 a b c d -> Tuple4 a b c d -> Tuple4 a b c d #

min :: Tuple4 a b c d -> Tuple4 a b c d -> Tuple4 a b c d #

(Show d, Show c, Show b, Show a) => Show (Tuple4 a b c d) Source # 

Methods

showsPrec :: Int -> Tuple4 a b c d -> ShowS #

show :: Tuple4 a b c d -> String #

showList :: [Tuple4 a b c d] -> ShowS #

Generic (Tuple4 a b c d) Source # 

Associated Types

type Rep (Tuple4 a b c d) :: * -> * #

Methods

from :: Tuple4 a b c d -> Rep (Tuple4 a b c d) x #

to :: Rep (Tuple4 a b c d) x -> Tuple4 a b c d #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) Source # 

Methods

toNormalForm :: Tuple4 a b c d -> () #

Thdable (Tuple4 a b c d) Source # 

Associated Types

type ProductThird (Tuple4 a b c d) :: * Source #

Methods

thd :: Tuple4 a b c d -> ProductThird (Tuple4 a b c d) Source #

Sndable (Tuple4 a b c d) Source # 

Associated Types

type ProductSecond (Tuple4 a b c d) :: * Source #

Methods

snd :: Tuple4 a b c d -> ProductSecond (Tuple4 a b c d) Source #

Fstable (Tuple4 a b c d) Source # 

Associated Types

type ProductFirst (Tuple4 a b c d) :: * Source #

Methods

fst :: Tuple4 a b c d -> ProductFirst (Tuple4 a b c d) Source #

(Hashable a, Hashable b, Hashable c, Hashable d) => Hashable (Tuple4 a b c d) Source # 

Methods

hashMix :: Hasher st => Tuple4 a b c d -> st -> st Source #

type NthTy 1 (Tuple4 a b c d) Source # 
type NthTy 1 (Tuple4 a b c d) = a
type NthTy 2 (Tuple4 a b c d) Source # 
type NthTy 2 (Tuple4 a b c d) = b
type NthTy 3 (Tuple4 a b c d) Source # 
type NthTy 3 (Tuple4 a b c d) = c
type NthTy 4 (Tuple4 a b c d) Source # 
type NthTy 4 (Tuple4 a b c d) = d
type Rep (Tuple4 a b c d) Source # 
type ProductThird (Tuple4 a b c d) Source # 
type ProductThird (Tuple4 a b c d) = c
type ProductSecond (Tuple4 a b c d) Source # 
type ProductSecond (Tuple4 a b c d) = b
type ProductFirst (Tuple4 a b c d) Source # 
type ProductFirst (Tuple4 a b c d) = a

class Fstable a where Source #

Class of product types that have a first element

Minimal complete definition

fst

Associated Types

type ProductFirst a Source #

Methods

fst :: a -> ProductFirst a Source #

Instances

Fstable (a, b) Source # 

Associated Types

type ProductFirst (a, b) :: * Source #

Methods

fst :: (a, b) -> ProductFirst (a, b) Source #

Fstable (Tuple2 a b) Source # 

Associated Types

type ProductFirst (Tuple2 a b) :: * Source #

Methods

fst :: Tuple2 a b -> ProductFirst (Tuple2 a b) Source #

Fstable (a, b, c) Source # 

Associated Types

type ProductFirst (a, b, c) :: * Source #

Methods

fst :: (a, b, c) -> ProductFirst (a, b, c) Source #

Fstable (Tuple3 a b c) Source # 

Associated Types

type ProductFirst (Tuple3 a b c) :: * Source #

Methods

fst :: Tuple3 a b c -> ProductFirst (Tuple3 a b c) Source #

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

Associated Types

type ProductFirst (a, b, c, d) :: * Source #

Methods

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

Fstable (Tuple4 a b c d) Source # 

Associated Types

type ProductFirst (Tuple4 a b c d) :: * Source #

Methods

fst :: Tuple4 a b c d -> ProductFirst (Tuple4 a b c d) Source #

class Sndable a where Source #

Class of product types that have a second element

Minimal complete definition

snd

Associated Types

type ProductSecond a Source #

Methods

snd :: a -> ProductSecond a Source #

Instances

Sndable (a, b) Source # 

Associated Types

type ProductSecond (a, b) :: * Source #

Methods

snd :: (a, b) -> ProductSecond (a, b) Source #

Sndable (Tuple2 a b) Source # 

Associated Types

type ProductSecond (Tuple2 a b) :: * Source #

Methods

snd :: Tuple2 a b -> ProductSecond (Tuple2 a b) Source #

Sndable (a, b, c) Source # 

Associated Types

type ProductSecond (a, b, c) :: * Source #

Methods

snd :: (a, b, c) -> ProductSecond (a, b, c) Source #

Sndable (Tuple3 a b c) Source # 

Associated Types

type ProductSecond (Tuple3 a b c) :: * Source #

Methods

snd :: Tuple3 a b c -> ProductSecond (Tuple3 a b c) Source #

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

Associated Types

type ProductSecond (a, b, c, d) :: * Source #

Methods

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

Sndable (Tuple4 a b c d) Source # 

Associated Types

type ProductSecond (Tuple4 a b c d) :: * Source #

Methods

snd :: Tuple4 a b c d -> ProductSecond (Tuple4 a b c d) Source #

class Thdable a where Source #

Class of product types that have a third element

Minimal complete definition

thd

Associated Types

type ProductThird a Source #

Methods

thd :: a -> ProductThird a Source #

Instances

Thdable (a, b, c) Source # 

Associated Types

type ProductThird (a, b, c) :: * Source #

Methods

thd :: (a, b, c) -> ProductThird (a, b, c) Source #

Thdable (Tuple3 a b c) Source # 

Associated Types

type ProductThird (Tuple3 a b c) :: * Source #

Methods

thd :: Tuple3 a b c -> ProductThird (Tuple3 a b c) Source #

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

Associated Types

type ProductThird (a, b, c, d) :: * Source #

Methods

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

Thdable (Tuple4 a b c d) Source # 

Associated Types

type ProductThird (Tuple4 a b c d) :: * Source #

Methods

thd :: Tuple4 a b c d -> ProductThird (Tuple4 a b c d) Source #

id :: Category k cat => forall (a :: k). cat a a #

the identity morphism

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

The maybe function takes a default value, a function, and a Maybe value. If the Maybe value is Nothing, the function returns the default value. Otherwise, it applies the function to the value inside the Just and returns the result.

Examples

Basic usage:

>>> maybe False odd (Just 3)
True
>>> maybe False odd Nothing
False

Read an integer from a string using readMaybe. If we succeed, return twice the integer; that is, apply (*2) to it. If instead we fail to parse an integer, return 0 by default:

>>> import Text.Read ( readMaybe )
>>> maybe 0 (*2) (readMaybe "5")
10
>>> maybe 0 (*2) (readMaybe "")
0

Apply show to a Maybe Int. If we have Just n, we want to show the underlying Int n. But if we have Nothing, we return the empty string instead of (for example) "Nothing":

>>> maybe "" show (Just 5)
"5"
>>> maybe "" show Nothing
""

either :: (a -> c) -> (b -> c) -> Either a b -> c #

Case analysis for the Either type. If the value is Left a, apply the first function to a; if it is Right b, apply the second function to b.

Examples

We create two values of type Either String Int, one using the Left constructor and another using the Right constructor. Then we apply "either" the length function (if we have a String) or the "times-two" function (if we have an Int):

>>> let s = Left "foo" :: Either String Int
>>> let n = Right 3 :: Either String Int
>>> either length (*2) s
3
>>> either length (*2) n
6

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

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

const :: a -> b -> a #

const x is a unary function which evaluates to x for all inputs.

For instance,

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

error :: HasCallStack => String -> a #

stop execution and displays an error message

putStr :: String -> IO () Source #

Print a string to standard output

putStrLn :: String -> IO () Source #

Print a string with a newline to standard output

getArgs :: IO [String] #

Returns a list of the program's command line arguments (not including the program name).

uncurry :: (a -> b -> c) -> (a, b) -> c #

uncurry converts a curried function to a function on pairs.

curry :: ((a, b) -> c) -> a -> b -> c #

curry converts an uncurried function to a curried function.

swap :: (a, b) -> (b, a) #

Swap the components of a pair.

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

until p f yields the result of applying f until p holds.

asTypeOf :: a -> a -> a #

asTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the second.

undefined :: HasCallStack => a #

A special case of error. It is expected that compilers will recognize this and insert error messages which are more appropriate to the context in which undefined appears.

seq :: a -> b -> b #

The value of seq a b is bottom if a is bottom, and otherwise equal to b. seq is usually introduced to improve performance by avoiding unneeded laziness.

A note on evaluation order: the expression seq a b does not guarantee that a will be evaluated before b. The only guarantee given by seq is that the both a and b will be evaluated before seq returns a value. In particular, this means that b may be evaluated before a. If you need to guarantee a specific order of evaluation, you must use the function pseq from the "parallel" package.

class NormalForm a #

Data that can be fully evaluated in Normal Form

Minimal complete definition

toNormalForm

Instances

NormalForm Bool 

Methods

toNormalForm :: Bool -> () #

NormalForm Char 

Methods

toNormalForm :: Char -> () #

NormalForm Double 

Methods

toNormalForm :: Double -> () #

NormalForm Float 

Methods

toNormalForm :: Float -> () #

NormalForm Int 

Methods

toNormalForm :: Int -> () #

NormalForm Int8 

Methods

toNormalForm :: Int8 -> () #

NormalForm Int16 

Methods

toNormalForm :: Int16 -> () #

NormalForm Int32 

Methods

toNormalForm :: Int32 -> () #

NormalForm Int64 

Methods

toNormalForm :: Int64 -> () #

NormalForm Integer 

Methods

toNormalForm :: Integer -> () #

NormalForm Natural 

Methods

toNormalForm :: Natural -> () #

NormalForm Word 

Methods

toNormalForm :: Word -> () #

NormalForm Word8 

Methods

toNormalForm :: Word8 -> () #

NormalForm Word16 

Methods

toNormalForm :: Word16 -> () #

NormalForm Word32 

Methods

toNormalForm :: Word32 -> () #

NormalForm Word64 

Methods

toNormalForm :: Word64 -> () #

NormalForm () 

Methods

toNormalForm :: () -> () #

NormalForm CChar 

Methods

toNormalForm :: CChar -> () #

NormalForm CSChar 

Methods

toNormalForm :: CSChar -> () #

NormalForm CUChar 

Methods

toNormalForm :: CUChar -> () #

NormalForm CShort 

Methods

toNormalForm :: CShort -> () #

NormalForm CUShort 

Methods

toNormalForm :: CUShort -> () #

NormalForm CInt 

Methods

toNormalForm :: CInt -> () #

NormalForm CUInt 

Methods

toNormalForm :: CUInt -> () #

NormalForm CLong 

Methods

toNormalForm :: CLong -> () #

NormalForm CULong 

Methods

toNormalForm :: CULong -> () #

NormalForm CLLong 

Methods

toNormalForm :: CLLong -> () #

NormalForm CULLong 

Methods

toNormalForm :: CULLong -> () #

NormalForm CFloat 

Methods

toNormalForm :: CFloat -> () #

NormalForm CDouble 

Methods

toNormalForm :: CDouble -> () #

NormalForm String 

Methods

toNormalForm :: String -> () #

NormalForm Word256 

Methods

toNormalForm :: Word256 -> () #

NormalForm Word128 

Methods

toNormalForm :: Word128 -> () #

NormalForm Char7 

Methods

toNormalForm :: Char7 -> () #

NormalForm IPv6 # 

Methods

toNormalForm :: IPv6 -> () #

NormalForm IPv4 # 

Methods

toNormalForm :: IPv4 -> () #

NormalForm UUID # 

Methods

toNormalForm :: UUID -> () #

NormalForm a => NormalForm [a] 

Methods

toNormalForm :: [a] -> () #

NormalForm a => NormalForm (Maybe a) 

Methods

toNormalForm :: Maybe a -> () #

NormalForm (Ptr a) 

Methods

toNormalForm :: Ptr a -> () #

NormalForm a => NormalForm (Array a) 

Methods

toNormalForm :: Array a -> () #

NormalForm (UArray ty) 

Methods

toNormalForm :: UArray ty -> () #

NormalForm (Block ty) 

Methods

toNormalForm :: Block ty -> () #

NormalForm (Offset a) 

Methods

toNormalForm :: Offset a -> () #

NormalForm (CountOf a) 

Methods

toNormalForm :: CountOf a -> () #

NormalForm (Zn64 n) 

Methods

toNormalForm :: Zn64 n -> () #

NormalForm (Zn n) 

Methods

toNormalForm :: Zn n -> () #

NormalForm a => NormalForm (LE a) 

Methods

toNormalForm :: LE a -> () #

NormalForm a => NormalForm (BE a) 

Methods

toNormalForm :: BE a -> () #

NormalForm (ChunkedUArray ty) # 

Methods

toNormalForm :: ChunkedUArray ty -> () #

(NormalForm l, NormalForm r) => NormalForm (Either l r) 

Methods

toNormalForm :: Either l r -> () #

(NormalForm a, NormalForm b) => NormalForm (a, b) 

Methods

toNormalForm :: (a, b) -> () #

NormalForm a => NormalForm (ListN n a) 

Methods

toNormalForm :: ListN n a -> () #

(NormalForm a, NormalForm b) => NormalForm (These a b) 

Methods

toNormalForm :: These a b -> () #

(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) # 

Methods

toNormalForm :: Tuple2 a b -> () #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (a, b, c) 

Methods

toNormalForm :: (a, b, c) -> () #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) # 

Methods

toNormalForm :: Tuple3 a b c -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (a, b, c, d) 

Methods

toNormalForm :: (a, b, c, d) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) # 

Methods

toNormalForm :: Tuple4 a b c d -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e) => NormalForm (a, b, c, d, e) 

Methods

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

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f) => NormalForm (a, b, c, d, e, f) 

Methods

toNormalForm :: (a, b, c, d, e, f) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g) => NormalForm (a, b, c, d, e, f, g) 

Methods

toNormalForm :: (a, b, c, d, e, f, g) -> () #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g, NormalForm h) => NormalForm (a, b, c, d, e, f, g, h) 

Methods

toNormalForm :: (a, b, c, d, e, f, g, h) -> () #

deepseq :: NormalForm a => a -> b -> b #

force :: NormalForm a => a -> a #

Type classes

class Show a #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Instances

Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Show Char

Since: 2.1

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int

Since: 2.1

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show Int8

Since: 2.1

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show Int16

Since: 2.1

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32

Since: 2.1

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64

Since: 2.1

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Integer

Since: 2.1

Show Natural

Since: 4.8.0.0

Show Ordering 
Show Word

Since: 2.1

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Show Word8

Since: 2.1

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Word16

Since: 2.1

Show Word32

Since: 2.1

Show Word64

Since: 2.1

Show CallStack

Since: 4.9.0.0

Show SomeTypeRep

Since: 4.10.0.0

Show () 

Methods

showsPrec :: Int -> () -> ShowS #

show :: () -> String #

showList :: [()] -> ShowS #

Show TyCon

Since: 2.1

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Module

Since: 4.9.0.0

Show TrName

Since: 4.9.0.0

Show FD

Since: 4.1.0.0

Methods

showsPrec :: Int -> FD -> ShowS #

show :: FD -> String #

showList :: [FD] -> ShowS #

Show EventLifetime 

Methods

showsPrec :: Int -> EventLifetime -> ShowS #

show :: EventLifetime -> String #

showList :: [EventLifetime] -> ShowS #

Show Timeout 

Methods

showsPrec :: Int -> Timeout -> ShowS #

show :: Timeout -> String #

showList :: [Timeout] -> ShowS #

Show HandleType

Since: 4.1.0.0

Methods

showsPrec :: Int -> HandleType -> ShowS #

show :: HandleType -> String #

showList :: [HandleType] -> ShowS #

Show Void

Since: 4.8.0.0

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show DataType 
Show Constr

Since: 4.0.0.0

Show DataRep 
Show ConstrRep 
Show Fixity 
Show RTSStats 
Show GCDetails 
Show GCStats 
Show Version 
Show HandlePosn

Since: 4.1.0.0

Show PatternMatchFail

Since: 4.0

Show RecSelError

Since: 4.0

Show RecConError

Since: 4.0

Show RecUpdError

Since: 4.0

Show NoMethodError

Since: 4.0

Show TypeError

Since: 4.9.0.0

Show NonTermination

Since: 4.0

Show NestedAtomically

Since: 4.0

Show ThreadId

Since: 4.2.0.0

Show BlockReason 
Show ThreadStatus 
Show Event

Since: 4.3.1.0

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Show Lifetime 
Show CDev 

Methods

showsPrec :: Int -> CDev -> ShowS #

show :: CDev -> String #

showList :: [CDev] -> ShowS #

Show CIno 

Methods

showsPrec :: Int -> CIno -> ShowS #

show :: CIno -> String #

showList :: [CIno] -> ShowS #

Show CMode 

Methods

showsPrec :: Int -> CMode -> ShowS #

show :: CMode -> String #

showList :: [CMode] -> ShowS #

Show COff 

Methods

showsPrec :: Int -> COff -> ShowS #

show :: COff -> String #

showList :: [COff] -> ShowS #

Show CPid 

Methods

showsPrec :: Int -> CPid -> ShowS #

show :: CPid -> String #

showList :: [CPid] -> ShowS #

Show CSsize 
Show CGid 

Methods

showsPrec :: Int -> CGid -> ShowS #

show :: CGid -> String #

showList :: [CGid] -> ShowS #

Show CNlink 
Show CUid 

Methods

showsPrec :: Int -> CUid -> ShowS #

show :: CUid -> String #

showList :: [CUid] -> ShowS #

Show CCc 

Methods

showsPrec :: Int -> CCc -> ShowS #

show :: CCc -> String #

showList :: [CCc] -> ShowS #

Show CSpeed 
Show CTcflag 
Show CRLim 

Methods

showsPrec :: Int -> CRLim -> ShowS #

show :: CRLim -> String #

showList :: [CRLim] -> ShowS #

Show CBlkSize 
Show CBlkCnt 
Show CClockId 
Show CFsBlkCnt 
Show CFsFilCnt 
Show CId 

Methods

showsPrec :: Int -> CId -> ShowS #

show :: CId -> String #

showList :: [CId] -> ShowS #

Show CKey 

Methods

showsPrec :: Int -> CKey -> ShowS #

show :: CKey -> String #

showList :: [CKey] -> ShowS #

Show CTimer 
Show Fd 

Methods

showsPrec :: Int -> Fd -> ShowS #

show :: Fd -> String #

showList :: [Fd] -> ShowS #

Show BlockedIndefinitelyOnMVar

Since: 4.1.0.0

Show BlockedIndefinitelyOnSTM

Since: 4.1.0.0

Show Deadlock

Since: 4.1.0.0

Show AllocationLimitExceeded

Since: 4.7.1.0

Show CompactionFailed

Since: 4.10.0.0

Show AssertionFailed

Since: 4.1.0.0

Show SomeAsyncException

Since: 4.7.0.0

Show AsyncException

Since: 4.1.0.0

Show ArrayException

Since: 4.1.0.0

Show ExitCode 
Show IOErrorType

Since: 4.1.0.0

Show Handle

Since: 4.1.0.0

Show BufferMode 
Show Newline 
Show NewlineMode 
Show SeekMode 
Show MaskingState 
Show IOException

Since: 4.1.0.0

Show ErrorCall

Since: 4.0.0.0

Show ArithException

Since: 4.0.0.0

Show All 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Any 

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Show Fixity 
Show Associativity 
Show SourceUnpackedness 
Show SourceStrictness 
Show DecidedStrictness 
Show SomeSymbol

Since: 4.7.0.0

Show SomeNat

Since: 4.7.0.0

Show CChar 

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Show CSChar 
Show CUChar 
Show CShort 
Show CUShort 
Show CInt 

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Show CUInt 

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Show CLong 

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Show CULong 
Show CLLong 
Show CULLong 
Show CBool 

Methods

showsPrec :: Int -> CBool -> ShowS #

show :: CBool -> String #

showList :: [CBool] -> ShowS #

Show CFloat 
Show CDouble 
Show CPtrdiff 
Show CSize 

Methods

showsPrec :: Int -> CSize -> ShowS #

show :: CSize -> String #

showList :: [CSize] -> ShowS #

Show CWchar 
Show CSigAtomic 
Show CClock 
Show CTime 

Methods

showsPrec :: Int -> CTime -> ShowS #

show :: CTime -> String #

showList :: [CTime] -> ShowS #

Show CUSeconds 
Show CSUSeconds 
Show CIntPtr 
Show CUIntPtr 
Show CIntMax 
Show CUIntMax 
Show WordPtr 
Show IntPtr 
Show IOMode 
Show Lexeme 
Show Number 
Show GeneralCategory 
Show SomeException

Since: 3.0

Show SrcLoc 
Show ASCII7_Invalid 

Methods

showsPrec :: Int -> ASCII7_Invalid -> ShowS #

show :: ASCII7_Invalid -> String #

showList :: [ASCII7_Invalid] -> ShowS #

Show ISO_8859_1_Invalid 

Methods

showsPrec :: Int -> ISO_8859_1_Invalid -> ShowS #

show :: ISO_8859_1_Invalid -> String #

showList :: [ISO_8859_1_Invalid] -> ShowS #

Show UTF16_Invalid 

Methods

showsPrec :: Int -> UTF16_Invalid -> ShowS #

show :: UTF16_Invalid -> String #

showList :: [UTF16_Invalid] -> ShowS #

Show UTF32_Invalid 

Methods

showsPrec :: Int -> UTF32_Invalid -> ShowS #

show :: UTF32_Invalid -> String #

showList :: [UTF32_Invalid] -> ShowS #

Show Encoding 
Show String 
Show ValidationFailure 
Show AsciiString 
Show OutOfBoundOperation 
Show OutOfBound 
Show RecastSourceSize 
Show RecastDestinationSize 
Show InvalidRecast 
Show NonEmptyCollectionIsEmpty 
Show FileSize 
Show Word256 
Show Word128 
Show Char7 

Methods

showsPrec :: Int -> Char7 -> ShowS #

show :: Char7 -> String #

showList :: [Char7] -> ShowS #

Show Endianness 
Show Bitmap # 
Show PartialError # 
Show And # 

Methods

showsPrec :: Int -> And -> ShowS #

show :: And -> String #

showList :: [And] -> ShowS #

Show Condition # 
Show Arch # 

Methods

showsPrec :: Int -> Arch -> ShowS #

show :: Arch -> String #

showList :: [Arch] -> ShowS #

Show OS # 

Methods

showsPrec :: Int -> OS -> ShowS #

show :: OS -> String #

showList :: [OS] -> ShowS #

Show Seconds # 
Show NanoSeconds # 
Show IPv6 # 

Methods

showsPrec :: Int -> IPv6 -> ShowS #

show :: IPv6 -> String #

showList :: [IPv6] -> ShowS #

Show IPv4 # 

Methods

showsPrec :: Int -> IPv4 -> ShowS #

show :: IPv4 -> String #

showList :: [IPv4] -> ShowS #

Show UUID # 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Show FileName # 
Show FilePath # 
Show Relativity # 
Show a => Show [a]

Since: 2.1

Methods

showsPrec :: Int -> [a] -> ShowS #

show :: [a] -> String #

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

Show a => Show (Maybe a) 

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (Ratio a)

Since: 2.0.1

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Ptr a)

Since: 2.1

Methods

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

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show (FunPtr a)

Since: 2.1

Methods

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

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show p => Show (Par1 p) 

Methods

showsPrec :: Int -> Par1 p -> ShowS #

show :: Par1 p -> String #

showList :: [Par1 p] -> ShowS #

Show a => Show (Min a) 

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Show a => Show (Max a) 

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Show a => Show (First a) 

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a) 

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show m => Show (WrappedMonoid m) 
Show a => Show (Option a) 

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show a => Show (ZipList a) 

Methods

showsPrec :: Int -> ZipList a -> ShowS #

show :: ZipList a -> String #

showList :: [ZipList a] -> ShowS #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: 4.8.0.0

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show (ForeignPtr a)

Since: 2.1

Show a => Show (Dual a) 

Methods

showsPrec :: Int -> Dual a -> ShowS #

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Show a => Show (Sum a) 

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Show a => Show (Product a) 

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Show a => Show (First a) 

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a) 

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Array a) 

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

(PrimType ty, Show ty) => Show (UArray ty) 

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

(PrimType ty, Show ty) => Show (Block ty) 

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show (Offset ty) 

Methods

showsPrec :: Int -> Offset ty -> ShowS #

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

Show (CountOf ty) 

Methods

showsPrec :: Int -> CountOf ty -> ShowS #

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Show (Zn64 n) 

Methods

showsPrec :: Int -> Zn64 n -> ShowS #

show :: Zn64 n -> String #

showList :: [Zn64 n] -> ShowS #

Show (Zn n) 

Methods

showsPrec :: Int -> Zn n -> ShowS #

show :: Zn n -> String #

showList :: [Zn n] -> ShowS #

Show (FinalPtr a) 

Methods

showsPrec :: Int -> FinalPtr a -> ShowS #

show :: FinalPtr a -> String #

showList :: [FinalPtr a] -> ShowS #

Show a => Show (LE a) 

Methods

showsPrec :: Int -> LE a -> ShowS #

show :: LE a -> String #

showList :: [LE a] -> ShowS #

Show a => Show (BE a) 

Methods

showsPrec :: Int -> BE a -> ShowS #

show :: BE a -> String #

showList :: [BE a] -> ShowS #

Show a => Show (DList a) # 

Methods

showsPrec :: Int -> DList a -> ShowS #

show :: DList a -> String #

showList :: [DList a] -> ShowS #

(Show ty, PrimType ty) => Show (ChunkedUArray ty) # 
Show (ParseError input) # 

Methods

showsPrec :: Int -> ParseError input -> ShowS #

show :: ParseError input -> String #

showList :: [ParseError input] -> ShowS #

(Show b, Show a) => Show (Either a b) 

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Show (V1 k p) 

Methods

showsPrec :: Int -> V1 k p -> ShowS #

show :: V1 k p -> String #

showList :: [V1 k p] -> ShowS #

Show (U1 k p)

Since: 4.9.0.0

Methods

showsPrec :: Int -> U1 k p -> ShowS #

show :: U1 k p -> String #

showList :: [U1 k p] -> ShowS #

Show (TypeRep k a) 

Methods

showsPrec :: Int -> TypeRep k a -> ShowS #

show :: TypeRep k a -> String #

showList :: [TypeRep k a] -> ShowS #

(Show a, Show b) => Show (a, b)

Since: 2.1

Methods

showsPrec :: Int -> (a, b) -> ShowS #

show :: (a, b) -> String #

showList :: [(a, b)] -> ShowS #

(Ix a, Show a, Show b) => Show (Array a b)

Since: 2.1

Methods

showsPrec :: Int -> Array a b -> ShowS #

show :: Array a b -> String #

showList :: [Array a b] -> ShowS #

(Show b, Show a) => Show (Arg a b) 

Methods

showsPrec :: Int -> Arg a b -> ShowS #

show :: Arg a b -> String #

showList :: [Arg a b] -> ShowS #

Show (Proxy k s)

Since: 4.7.0.0

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Show (ST s a)

Since: 2.1

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

Show a => Show (ListN n a) 

Methods

showsPrec :: Int -> ListN n a -> ShowS #

show :: ListN n a -> String #

showList :: [ListN n a] -> ShowS #

(Show b, Show a) => Show (These a b) 

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

Show k => Show (Result input k) # 

Methods

showsPrec :: Int -> Result input k -> ShowS #

show :: Result input k -> String #

showList :: [Result input k] -> ShowS #

(Show b, Show a) => Show (Tuple2 a b) # 

Methods

showsPrec :: Int -> Tuple2 a b -> ShowS #

show :: Tuple2 a b -> String #

showList :: [Tuple2 a b] -> ShowS #

Show (f p) => Show (Rec1 k f p) 

Methods

showsPrec :: Int -> Rec1 k f p -> ShowS #

show :: Rec1 k f p -> String #

showList :: [Rec1 k f p] -> ShowS #

Show (URec k Char p) 

Methods

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

show :: URec k Char p -> String #

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

Show (URec k Double p) 

Methods

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

show :: URec k Double p -> String #

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

Show (URec k Float p) 

Methods

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

show :: URec k Float p -> String #

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

Show (URec k Int p) 

Methods

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

show :: URec k Int p -> String #

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

Show (URec k Word p) 

Methods

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

show :: URec k Word p -> String #

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

(Show a, Show b, Show c) => Show (a, b, c)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c) -> ShowS #

show :: (a, b, c) -> String #

showList :: [(a, b, c)] -> ShowS #

Show a => Show (Const k a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Since: 4.8.0.0

Methods

showsPrec :: Int -> Const k a b -> ShowS #

show :: Const k a b -> String #

showList :: [Const k a b] -> ShowS #

Show (f a) => Show (Alt k f a) 

Methods

showsPrec :: Int -> Alt k f a -> ShowS #

show :: Alt k f a -> String #

showList :: [Alt k f a] -> ShowS #

Show (Coercion k a b) 

Methods

showsPrec :: Int -> Coercion k a b -> ShowS #

show :: Coercion k a b -> String #

showList :: [Coercion k a b] -> ShowS #

Show ((:~:) k a b) 

Methods

showsPrec :: Int -> (k :~: a) b -> ShowS #

show :: (k :~: a) b -> String #

showList :: [(k :~: a) b] -> ShowS #

(Show c, Show b, Show a) => Show (Tuple3 a b c) # 

Methods

showsPrec :: Int -> Tuple3 a b c -> ShowS #

show :: Tuple3 a b c -> String #

showList :: [Tuple3 a b c] -> ShowS #

Show c => Show (K1 k i c p) 

Methods

showsPrec :: Int -> K1 k i c p -> ShowS #

show :: K1 k i c p -> String #

showList :: [K1 k i c p] -> ShowS #

(Show (g p), Show (f p)) => Show ((:+:) k f g p) 

Methods

showsPrec :: Int -> (k :+: f) g p -> ShowS #

show :: (k :+: f) g p -> String #

showList :: [(k :+: f) g p] -> ShowS #

(Show (g p), Show (f p)) => Show ((:*:) k f g p) 

Methods

showsPrec :: Int -> (k :*: f) g p -> ShowS #

show :: (k :*: f) g p -> String #

showList :: [(k :*: f) g p] -> ShowS #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS #

show :: (a, b, c, d) -> String #

showList :: [(a, b, c, d)] -> ShowS #

Show ((:~~:) k1 k2 a b)

Since: 4.10.0.0

Methods

showsPrec :: Int -> (k1 :~~: k2) a b -> ShowS #

show :: (k1 :~~: k2) a b -> String #

showList :: [(k1 :~~: k2) a b] -> ShowS #

(Show d, Show c, Show b, Show a) => Show (Tuple4 a b c d) # 

Methods

showsPrec :: Int -> Tuple4 a b c d -> ShowS #

show :: Tuple4 a b c d -> String #

showList :: [Tuple4 a b c d] -> ShowS #

Show (f p) => Show (M1 k i c f p) 

Methods

showsPrec :: Int -> M1 k i c f p -> ShowS #

show :: M1 k i c f p -> String #

showList :: [M1 k i c f p] -> ShowS #

Show (f (g p)) => Show ((:.:) k2 k1 f g p) 

Methods

showsPrec :: Int -> (k2 :.: k1) f g p -> ShowS #

show :: (k2 :.: k1) f g p -> String #

showList :: [(k2 :.: k1) f g p] -> ShowS #

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS #

show :: (a, b, c, d, e) -> String #

showList :: [(a, b, c, d, e)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS #

show :: (a, b, c, d, e, f) -> String #

showList :: [(a, b, c, d, e, f)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS #

show :: (a, b, c, d, e, f, g) -> String #

showList :: [(a, b, c, d, e, f, g)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS #

show :: (a, b, c, d, e, f, g, h) -> String #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i) -> String #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: 2.1

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS #

show :: Show a => a -> String #

Use the Show class to create a String.

Note that this is not efficient, since an intermediate [Char] is going to be created before turning into a real String.

class Eq a => Ord a where #

The Ord class is used for totally ordered datatypes.

Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.

Minimal complete definition: either compare or <=. Using compare can be more efficient for complex types.

Minimal complete definition

compare | (<=)

Methods

compare :: a -> a -> Ordering #

(<) :: a -> a -> Bool infix 4 #

(<=) :: a -> a -> Bool infix 4 #

(>) :: a -> a -> Bool infix 4 #

(>=) :: a -> a -> Bool infix 4 #

max :: a -> a -> a #

min :: a -> a -> a #

Instances

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

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

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

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

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

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 #

Ord Double 
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 #

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 #

Ord Int8

Since: 2.1

Methods

compare :: Int8 -> Int8 -> Ordering #

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

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

(>) :: Int8 -> Int8 -> Bool #

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

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Ord Int16

Since: 2.1

Methods

compare :: Int16 -> Int16 -> Ordering #

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

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

(>) :: Int16 -> Int16 -> Bool #

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

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Ord Int32

Since: 2.1

Methods

compare :: Int32 -> Int32 -> Ordering #

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

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

(>) :: Int32 -> Int32 -> Bool #

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

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Ord Int64

Since: 2.1

Methods

compare :: Int64 -> Int64 -> Ordering #

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

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

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Ord Integer 
Ord Natural 
Ord Ordering 
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 #

Ord Word8

Since: 2.1

Methods

compare :: Word8 -> Word8 -> Ordering #

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

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

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Ord Word16

Since: 2.1

Ord Word32

Since: 2.1

Ord Word64

Since: 2.1

Ord SomeTypeRep 
Ord () 

Methods

compare :: () -> () -> Ordering #

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

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

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

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

max :: () -> () -> () #

min :: () -> () -> () #

Ord TyCon 

Methods

compare :: TyCon -> TyCon -> Ordering #

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

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

(>) :: TyCon -> TyCon -> Bool #

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

max :: TyCon -> TyCon -> TyCon #

min :: TyCon -> TyCon -> TyCon #

Ord BigNat 
Ord Void

Since: 4.8.0.0

Methods

compare :: Void -> Void -> Ordering #

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

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

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

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

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Ord Version

Since: 2.1

Ord ThreadId

Since: 4.2.0.0

Ord BlockReason 
Ord ThreadStatus 
Ord CDev 

Methods

compare :: CDev -> CDev -> Ordering #

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

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

(>) :: CDev -> CDev -> Bool #

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

max :: CDev -> CDev -> CDev #

min :: CDev -> CDev -> CDev #

Ord CIno 

Methods

compare :: CIno -> CIno -> Ordering #

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

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

(>) :: CIno -> CIno -> Bool #

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

max :: CIno -> CIno -> CIno #

min :: CIno -> CIno -> CIno #

Ord CMode 

Methods

compare :: CMode -> CMode -> Ordering #

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

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

(>) :: CMode -> CMode -> Bool #

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

max :: CMode -> CMode -> CMode #

min :: CMode -> CMode -> CMode #

Ord COff 

Methods

compare :: COff -> COff -> Ordering #

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

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

(>) :: COff -> COff -> Bool #

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

max :: COff -> COff -> COff #

min :: COff -> COff -> COff #

Ord CPid 

Methods

compare :: CPid -> CPid -> Ordering #

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

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

(>) :: CPid -> CPid -> Bool #

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

max :: CPid -> CPid -> CPid #

min :: CPid -> CPid -> CPid #

Ord CSsize 
Ord CGid 

Methods

compare :: CGid -> CGid -> Ordering #

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

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

(>) :: CGid -> CGid -> Bool #

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

max :: CGid -> CGid -> CGid #

min :: CGid -> CGid -> CGid #

Ord CNlink 
Ord CUid 

Methods

compare :: CUid -> CUid -> Ordering #

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

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

(>) :: CUid -> CUid -> Bool #

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

max :: CUid -> CUid -> CUid #

min :: CUid -> CUid -> CUid #

Ord CCc 

Methods

compare :: CCc -> CCc -> Ordering #

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

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

(>) :: CCc -> CCc -> Bool #

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

max :: CCc -> CCc -> CCc #

min :: CCc -> CCc -> CCc #

Ord CSpeed 
Ord CTcflag 
Ord CRLim 

Methods

compare :: CRLim -> CRLim -> Ordering #

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

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

(>) :: CRLim -> CRLim -> Bool #

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

max :: CRLim -> CRLim -> CRLim #

min :: CRLim -> CRLim -> CRLim #

Ord CBlkSize 
Ord CBlkCnt 
Ord CClockId 
Ord CFsBlkCnt 
Ord CFsFilCnt 
Ord CId 

Methods

compare :: CId -> CId -> Ordering #

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

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

(>) :: CId -> CId -> Bool #

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

max :: CId -> CId -> CId #

min :: CId -> CId -> CId #

Ord CKey 

Methods

compare :: CKey -> CKey -> Ordering #

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

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

(>) :: CKey -> CKey -> Bool #

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

max :: CKey -> CKey -> CKey #

min :: CKey -> CKey -> CKey #

Ord CTimer 
Ord Fd 

Methods

compare :: Fd -> Fd -> Ordering #

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

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

(>) :: Fd -> Fd -> Bool #

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

max :: Fd -> Fd -> Fd #

min :: Fd -> Fd -> Fd #

Ord AsyncException 
Ord ArrayException 
Ord ExitCode 
Ord BufferMode 
Ord Newline 
Ord NewlineMode 
Ord SeekMode 
Ord ErrorCall 
Ord ArithException 
Ord All 

Methods

compare :: All -> All -> Ordering #

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

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

(>) :: All -> All -> Bool #

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

max :: All -> All -> All #

min :: All -> All -> All #

Ord Any 

Methods

compare :: Any -> Any -> Ordering #

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

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

(>) :: Any -> Any -> Bool #

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

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Ord Fixity 
Ord Associativity 
Ord SourceUnpackedness 
Ord SourceStrictness 
Ord DecidedStrictness 
Ord SomeSymbol

Since: 4.7.0.0

Ord SomeNat

Since: 4.7.0.0

Ord CChar 

Methods

compare :: CChar -> CChar -> Ordering #

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

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

(>) :: CChar -> CChar -> Bool #

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

max :: CChar -> CChar -> CChar #

min :: CChar -> CChar -> CChar #

Ord CSChar 
Ord CUChar 
Ord CShort 
Ord CUShort 
Ord CInt 

Methods

compare :: CInt -> CInt -> Ordering #

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

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

(>) :: CInt -> CInt -> Bool #

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

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Ord CUInt 

Methods

compare :: CUInt -> CUInt -> Ordering #

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

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

(>) :: CUInt -> CUInt -> Bool #

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

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

Ord CLong 

Methods

compare :: CLong -> CLong -> Ordering #

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

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

(>) :: CLong -> CLong -> Bool #

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

max :: CLong -> CLong -> CLong #

min :: CLong -> CLong -> CLong #

Ord CULong 
Ord CLLong 
Ord CULLong 
Ord CBool 

Methods

compare :: CBool -> CBool -> Ordering #

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

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

(>) :: CBool -> CBool -> Bool #

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

max :: CBool -> CBool -> CBool #

min :: CBool -> CBool -> CBool #

Ord CFloat 
Ord CDouble 
Ord CPtrdiff 
Ord CSize 

Methods

compare :: CSize -> CSize -> Ordering #

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

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

(>) :: CSize -> CSize -> Bool #

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

max :: CSize -> CSize -> CSize #

min :: CSize -> CSize -> CSize #

Ord CWchar 
Ord CSigAtomic 
Ord CClock 
Ord CTime 

Methods

compare :: CTime -> CTime -> Ordering #

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

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

(>) :: CTime -> CTime -> Bool #

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

max :: CTime -> CTime -> CTime #

min :: CTime -> CTime -> CTime #

Ord CUSeconds 
Ord CSUSeconds 
Ord CIntPtr 
Ord CUIntPtr 
Ord CIntMax 
Ord CUIntMax 
Ord WordPtr 
Ord IntPtr 
Ord IOMode 
Ord GeneralCategory 
Ord UTF32_Invalid 

Methods

compare :: UTF32_Invalid -> UTF32_Invalid -> Ordering #

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

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

(>) :: UTF32_Invalid -> UTF32_Invalid -> Bool #

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

max :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid #

min :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid #

Ord Encoding 
Ord String 
Ord AsciiString 
Ord Addr 

Methods

compare :: Addr -> Addr -> Ordering #

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

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

(>) :: Addr -> Addr -> Bool #

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

max :: Addr -> Addr -> Addr #

min :: Addr -> Addr -> Addr #

Ord FileSize 
Ord Word256 
Ord Word128 
Ord Char7 

Methods

compare :: Char7 -> Char7 -> Ordering #

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

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

(>) :: Char7 -> Char7 -> Bool #

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

max :: Char7 -> Char7 -> Char7 #

min :: Char7 -> Char7 -> Char7 #

Ord Bitmap # 
Ord Arch # 

Methods

compare :: Arch -> Arch -> Ordering #

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

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

(>) :: Arch -> Arch -> Bool #

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

max :: Arch -> Arch -> Arch #

min :: Arch -> Arch -> Arch #

Ord OS # 

Methods

compare :: OS -> OS -> Ordering #

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

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

(>) :: OS -> OS -> Bool #

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

max :: OS -> OS -> OS #

min :: OS -> OS -> OS #

Ord Seconds # 
Ord NanoSeconds # 
Ord IPv6 # 

Methods

compare :: IPv6 -> IPv6 -> Ordering #

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

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

(>) :: IPv6 -> IPv6 -> Bool #

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

max :: IPv6 -> IPv6 -> IPv6 #

min :: IPv6 -> IPv6 -> IPv6 #

Ord IPv4 # 

Methods

compare :: IPv4 -> IPv4 -> Ordering #

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

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

(>) :: IPv4 -> IPv4 -> Bool #

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

max :: IPv4 -> IPv4 -> IPv4 #

min :: IPv4 -> IPv4 -> IPv4 #

Ord UUID # 

Methods

compare :: UUID -> UUID -> Ordering #

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

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

(>) :: UUID -> UUID -> Bool #

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Ord FilePath # 
Ord a => Ord [a] 

Methods

compare :: [a] -> [a] -> Ordering #

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

(<=) :: [a] -> [a] -> Bool #

(>) :: [a] -> [a] -> Bool #

(>=) :: [a] -> [a] -> Bool #

max :: [a] -> [a] -> [a] #

min :: [a] -> [a] -> [a] #

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering #

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

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

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

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Integral a => Ord (Ratio a)

Since: 2.0.1

Methods

compare :: Ratio a -> Ratio a -> Ordering #

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

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

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

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

max :: Ratio a -> Ratio a -> Ratio a #

min :: Ratio a -> Ratio a -> Ratio a #

Ord (Ptr a) 

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 #

Ord (FunPtr a) 

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 #

Ord p => Ord (Par1 p) 

Methods

compare :: Par1 p -> Par1 p -> Ordering #

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

(<=) :: Par1 p -> Par1 p -> Bool #

(>) :: Par1 p -> Par1 p -> Bool #

(>=) :: Par1 p -> Par1 p -> Bool #

max :: Par1 p -> Par1 p -> Par1 p #

min :: Par1 p -> Par1 p -> Par1 p #

Ord a => Ord (Min a) 

Methods

compare :: Min a -> Min a -> Ordering #

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

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

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

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

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

Ord a => Ord (Max a) 

Methods

compare :: Max a -> Max a -> Ordering #

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

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

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

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

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering #

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

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

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

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

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering #

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

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

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

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

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Ord m => Ord (WrappedMonoid m) 
Ord a => Ord (Option a) 

Methods

compare :: Option a -> Option a -> Ordering #

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

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

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

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

max :: Option a -> Option a -> Option a #

min :: Option a -> Option a -> Option a #

Ord a => Ord (NonEmpty a) 

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

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

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

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

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Ord a => Ord (ZipList a) 

Methods

compare :: ZipList a -> ZipList a -> Ordering #

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

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

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

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

max :: ZipList a -> ZipList a -> ZipList a #

min :: ZipList a -> ZipList a -> ZipList a #

Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

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

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

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

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

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Ord (ForeignPtr a)

Since: 2.1

Ord a => Ord (Dual a) 

Methods

compare :: Dual a -> Dual a -> Ordering #

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

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

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

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

max :: Dual a -> Dual a -> Dual a #

min :: Dual a -> Dual a -> Dual a #

Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering #

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

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

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

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

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Ord a => Ord (Product a) 

Methods

compare :: Product a -> Product a -> Ordering #

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

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

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

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

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering #

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

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

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

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

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering #

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

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

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

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

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Ord a => Ord (Array a) 

Methods

compare :: Array a -> Array a -> Ordering #

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

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

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

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

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

(PrimType ty, Ord ty) => Ord (UArray ty) 

Methods

compare :: UArray ty -> UArray ty -> Ordering #

(<) :: UArray ty -> UArray ty -> Bool #

(<=) :: UArray ty -> UArray ty -> Bool #

(>) :: UArray ty -> UArray ty -> Bool #

(>=) :: UArray ty -> UArray ty -> Bool #

max :: UArray ty -> UArray ty -> UArray ty #

min :: UArray ty -> UArray ty -> UArray ty #

(PrimType ty, Ord ty) => Ord (Block ty) 

Methods

compare :: Block ty -> Block ty -> Ordering #

(<) :: Block ty -> Block ty -> Bool #

(<=) :: Block ty -> Block ty -> Bool #

(>) :: Block ty -> Block ty -> Bool #

(>=) :: Block ty -> Block ty -> Bool #

max :: Block ty -> Block ty -> Block ty #

min :: Block ty -> Block ty -> Block ty #

Ord (Offset ty) 

Methods

compare :: Offset ty -> Offset ty -> Ordering #

(<) :: Offset ty -> Offset ty -> Bool #

(<=) :: Offset ty -> Offset ty -> Bool #

(>) :: Offset ty -> Offset ty -> Bool #

(>=) :: Offset ty -> Offset ty -> Bool #

max :: Offset ty -> Offset ty -> Offset ty #

min :: Offset ty -> Offset ty -> Offset ty #

Ord (CountOf ty) 

Methods

compare :: CountOf ty -> CountOf ty -> Ordering #

(<) :: CountOf ty -> CountOf ty -> Bool #

(<=) :: CountOf ty -> CountOf ty -> Bool #

(>) :: CountOf ty -> CountOf ty -> Bool #

(>=) :: CountOf ty -> CountOf ty -> Bool #

max :: CountOf ty -> CountOf ty -> CountOf ty #

min :: CountOf ty -> CountOf ty -> CountOf ty #

Ord (Zn64 n) 

Methods

compare :: Zn64 n -> Zn64 n -> Ordering #

(<) :: Zn64 n -> Zn64 n -> Bool #

(<=) :: Zn64 n -> Zn64 n -> Bool #

(>) :: Zn64 n -> Zn64 n -> Bool #

(>=) :: Zn64 n -> Zn64 n -> Bool #

max :: Zn64 n -> Zn64 n -> Zn64 n #

min :: Zn64 n -> Zn64 n -> Zn64 n #

Ord (Zn n) 

Methods

compare :: Zn n -> Zn n -> Ordering #

(<) :: Zn n -> Zn n -> Bool #

(<=) :: Zn n -> Zn n -> Bool #

(>) :: Zn n -> Zn n -> Bool #

(>=) :: Zn n -> Zn n -> Bool #

max :: Zn n -> Zn n -> Zn n #

min :: Zn n -> Zn n -> Zn n #

Ord (FinalPtr a) 

Methods

compare :: FinalPtr a -> FinalPtr a -> Ordering #

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

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

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

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

max :: FinalPtr a -> FinalPtr a -> FinalPtr a #

min :: FinalPtr a -> FinalPtr a -> FinalPtr a #

(ByteSwap a, Ord a) => Ord (LE a) 

Methods

compare :: LE a -> LE a -> Ordering #

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

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

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

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

max :: LE a -> LE a -> LE a #

min :: LE a -> LE a -> LE a #

(ByteSwap a, Ord a) => Ord (BE a) 

Methods

compare :: BE a -> BE a -> Ordering #

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

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

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

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

max :: BE a -> BE a -> BE a #

min :: BE a -> BE a -> BE a #

Ord a => Ord (DList a) # 

Methods

compare :: DList a -> DList a -> Ordering #

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

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

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

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

max :: DList a -> DList a -> DList a #

min :: DList a -> DList a -> DList a #

(Ord ty, PrimType ty) => Ord (ChunkedUArray ty) # 
(Ord b, Ord a) => Ord (Either a b) 

Methods

compare :: Either a b -> Either a b -> Ordering #

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

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

Ord (V1 k p) 

Methods

compare :: V1 k p -> V1 k p -> Ordering #

(<) :: V1 k p -> V1 k p -> Bool #

(<=) :: V1 k p -> V1 k p -> Bool #

(>) :: V1 k p -> V1 k p -> Bool #

(>=) :: V1 k p -> V1 k p -> Bool #

max :: V1 k p -> V1 k p -> V1 k p #

min :: V1 k p -> V1 k p -> V1 k p #

Ord (U1 k p)

Since: 4.9.0.0

Methods

compare :: U1 k p -> U1 k p -> Ordering #

(<) :: U1 k p -> U1 k p -> Bool #

(<=) :: U1 k p -> U1 k p -> Bool #

(>) :: U1 k p -> U1 k p -> Bool #

(>=) :: U1 k p -> U1 k p -> Bool #

max :: U1 k p -> U1 k p -> U1 k p #

min :: U1 k p -> U1 k p -> U1 k p #

Ord (TypeRep k a)

Since: 4.4.0.0

Methods

compare :: TypeRep k a -> TypeRep k a -> Ordering #

(<) :: TypeRep k a -> TypeRep k a -> Bool #

(<=) :: TypeRep k a -> TypeRep k a -> Bool #

(>) :: TypeRep k a -> TypeRep k a -> Bool #

(>=) :: TypeRep k a -> TypeRep k a -> Bool #

max :: TypeRep k a -> TypeRep k a -> TypeRep k a #

min :: TypeRep k a -> TypeRep k a -> TypeRep k a #

(Ord a, Ord b) => Ord (a, b) 

Methods

compare :: (a, b) -> (a, b) -> Ordering #

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

(<=) :: (a, b) -> (a, b) -> Bool #

(>) :: (a, b) -> (a, b) -> Bool #

(>=) :: (a, b) -> (a, b) -> Bool #

max :: (a, b) -> (a, b) -> (a, b) #

min :: (a, b) -> (a, b) -> (a, b) #

(Ix i, Ord e) => Ord (Array i e)

Since: 2.1

Methods

compare :: Array i e -> Array i e -> Ordering #

(<) :: Array i e -> Array i e -> Bool #

(<=) :: Array i e -> Array i e -> Bool #

(>) :: Array i e -> Array i e -> Bool #

(>=) :: Array i e -> Array i e -> Bool #

max :: Array i e -> Array i e -> Array i e #

min :: Array i e -> Array i e -> Array i e #

Ord a => Ord (Arg a b)

Since: 4.9.0.0

Methods

compare :: Arg a b -> Arg a b -> Ordering #

(<) :: Arg a b -> Arg a b -> Bool #

(<=) :: Arg a b -> Arg a b -> Bool #

(>) :: Arg a b -> Arg a b -> Bool #

(>=) :: Arg a b -> Arg a b -> Bool #

max :: Arg a b -> Arg a b -> Arg a b #

min :: Arg a b -> Arg a b -> Arg a b #

Ord (Proxy k s)

Since: 4.7.0.0

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Ord a => Ord (ListN n a) 

Methods

compare :: ListN n a -> ListN n a -> Ordering #

(<) :: ListN n a -> ListN n a -> Bool #

(<=) :: ListN n a -> ListN n a -> Bool #

(>) :: ListN n a -> ListN n a -> Bool #

(>=) :: ListN n a -> ListN n a -> Bool #

max :: ListN n a -> ListN n a -> ListN n a #

min :: ListN n a -> ListN n a -> ListN n a #

(Ord b, Ord a) => Ord (These a b) 

Methods

compare :: These a b -> These a b -> Ordering #

(<) :: These a b -> These a b -> Bool #

(<=) :: These a b -> These a b -> Bool #

(>) :: These a b -> These a b -> Bool #

(>=) :: These a b -> These a b -> Bool #

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

(Ord b, Ord a) => Ord (Tuple2 a b) # 

Methods

compare :: Tuple2 a b -> Tuple2 a b -> Ordering #

(<) :: Tuple2 a b -> Tuple2 a b -> Bool #

(<=) :: Tuple2 a b -> Tuple2 a b -> Bool #

(>) :: Tuple2 a b -> Tuple2 a b -> Bool #

(>=) :: Tuple2 a b -> Tuple2 a b -> Bool #

max :: Tuple2 a b -> Tuple2 a b -> Tuple2 a b #

min :: Tuple2 a b -> Tuple2 a b -> Tuple2 a b #

Ord (f p) => Ord (Rec1 k f p) 

Methods

compare :: Rec1 k f p -> Rec1 k f p -> Ordering #

(<) :: Rec1 k f p -> Rec1 k f p -> Bool #

(<=) :: Rec1 k f p -> Rec1 k f p -> Bool #

(>) :: Rec1 k f p -> Rec1 k f p -> Bool #

(>=) :: Rec1 k f p -> Rec1 k f p -> Bool #

max :: Rec1 k f p -> Rec1 k f p -> Rec1 k f p #

min :: Rec1 k f p -> Rec1 k f p -> Rec1 k f p #

Ord (URec k (Ptr ()) p) 

Methods

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

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

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

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

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

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

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

Ord (URec k Char p) 

Methods

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

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

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

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

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

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

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

Ord (URec k Double p) 

Methods

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

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

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

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

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

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

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

Ord (URec k Float p) 

Methods

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

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

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

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

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

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

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

Ord (URec k Int p) 

Methods

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

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

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

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

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

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

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

Ord (URec k Word p) 

Methods

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

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

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

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

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

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

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

(Ord a, Ord b, Ord c) => Ord (a, b, c) 

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering #

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

(<=) :: (a, b, c) -> (a, b, c) -> Bool #

(>) :: (a, b, c) -> (a, b, c) -> Bool #

(>=) :: (a, b, c) -> (a, b, c) -> Bool #

max :: (a, b, c) -> (a, b, c) -> (a, b, c) #

min :: (a, b, c) -> (a, b, c) -> (a, b, c) #

Ord a => Ord (Const k a b) 

Methods

compare :: Const k a b -> Const k a b -> Ordering #

(<) :: Const k a b -> Const k a b -> Bool #

(<=) :: Const k a b -> Const k a b -> Bool #

(>) :: Const k a b -> Const k a b -> Bool #

(>=) :: Const k a b -> Const k a b -> Bool #

max :: Const k a b -> Const k a b -> Const k a b #

min :: Const k a b -> Const k a b -> Const k a b #

Ord (f a) => Ord (Alt k f a) 

Methods

compare :: Alt k f a -> Alt k f a -> Ordering #

(<) :: Alt k f a -> Alt k f a -> Bool #

(<=) :: Alt k f a -> Alt k f a -> Bool #

(>) :: Alt k f a -> Alt k f a -> Bool #

(>=) :: Alt k f a -> Alt k f a -> Bool #

max :: Alt k f a -> Alt k f a -> Alt k f a #

min :: Alt k f a -> Alt k f a -> Alt k f a #

Ord (Coercion k a b) 

Methods

compare :: Coercion k a b -> Coercion k a b -> Ordering #

(<) :: Coercion k a b -> Coercion k a b -> Bool #

(<=) :: Coercion k a b -> Coercion k a b -> Bool #

(>) :: Coercion k a b -> Coercion k a b -> Bool #

(>=) :: Coercion k a b -> Coercion k a b -> Bool #

max :: Coercion k a b -> Coercion k a b -> Coercion k a b #

min :: Coercion k a b -> Coercion k a b -> Coercion k a b #

Ord ((:~:) k a b) 

Methods

compare :: (k :~: a) b -> (k :~: a) b -> Ordering #

(<) :: (k :~: a) b -> (k :~: a) b -> Bool #

(<=) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>=) :: (k :~: a) b -> (k :~: a) b -> Bool #

max :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

min :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

(Ord c, Ord b, Ord a) => Ord (Tuple3 a b c) # 

Methods

compare :: Tuple3 a b c -> Tuple3 a b c -> Ordering #

(<) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(<=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(>) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(>=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

max :: Tuple3 a b c -> Tuple3 a b c -> Tuple3 a b c #

min :: Tuple3 a b c -> Tuple3 a b c -> Tuple3 a b c #

Ord c => Ord (K1 k i c p) 

Methods

compare :: K1 k i c p -> K1 k i c p -> Ordering #

(<) :: K1 k i c p -> K1 k i c p -> Bool #

(<=) :: K1 k i c p -> K1 k i c p -> Bool #

(>) :: K1 k i c p -> K1 k i c p -> Bool #

(>=) :: K1 k i c p -> K1 k i c p -> Bool #

max :: K1 k i c p -> K1 k i c p -> K1 k i c p #

min :: K1 k i c p -> K1 k i c p -> K1 k i c p #

(Ord (g p), Ord (f p)) => Ord ((:+:) k f g p) 

Methods

compare :: (k :+: f) g p -> (k :+: f) g p -> Ordering #

(<) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

(<=) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

(>) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

(>=) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

max :: (k :+: f) g p -> (k :+: f) g p -> (k :+: f) g p #

min :: (k :+: f) g p -> (k :+: f) g p -> (k :+: f) g p #

(Ord (g p), Ord (f p)) => Ord ((:*:) k f g p) 

Methods

compare :: (k :*: f) g p -> (k :*: f) g p -> Ordering #

(<) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

(<=) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

(>) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

(>=) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

max :: (k :*: f) g p -> (k :*: f) g p -> (k :*: f) g p #

min :: (k :*: f) g p -> (k :*: f) g p -> (k :*: f) g p #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 

Methods

compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering #

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

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

(>) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

Ord ((:~~:) k1 k2 a b)

Since: 4.10.0.0

Methods

compare :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Ordering #

(<) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

(<=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

(>) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

(>=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

max :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

min :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

(Ord d, Ord c, Ord b, Ord a) => Ord (Tuple4 a b c d) # 

Methods

compare :: Tuple4 a b c d -> Tuple4 a b c d -> Ordering #

(<) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(<=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(>) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(>=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

max :: Tuple4 a b c d -> Tuple4 a b c d -> Tuple4 a b c d #

min :: Tuple4 a b c d -> Tuple4 a b c d -> Tuple4 a b c d #

Ord (f p) => Ord (M1 k i c f p) 

Methods

compare :: M1 k i c f p -> M1 k i c f p -> Ordering #

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

(<=) :: M1 k i c f p -> M1 k i c f p -> Bool #

(>) :: M1 k i c f p -> M1 k i c f p -> Bool #

(>=) :: M1 k i c f p -> M1 k i c f p -> Bool #

max :: M1 k i c f p -> M1 k i c f p -> M1 k i c f p #

min :: M1 k i c f p -> M1 k i c f p -> M1 k i c f p #

Ord (f (g p)) => Ord ((:.:) k2 k1 f g p) 

Methods

compare :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Ordering #

(<) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

(<=) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

(>) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

(>=) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

max :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> (k2 :.: k1) f g p #

min :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> (k2 :.: k1) f g p #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 

Methods

compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering #

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

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

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

(>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) 

Methods

compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering #

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

(<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) #

min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) 

Methods

compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering #

(<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) #

min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) 

Methods

compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) #

min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) 

Methods

compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) #

min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

(>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) #

min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) #

min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) #

min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

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

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

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

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

class Eq a where #

The Eq class defines equality (==) and inequality (/=). All the basic datatypes exported by the Prelude are instances of Eq, and Eq may be derived for any datatype whose constituents are also instances of Eq.

Minimal complete definition: either == or /=.

Minimal complete definition

(==) | (/=)

Methods

(==) :: a -> a -> Bool infix 4 #

(/=) :: a -> a -> Bool infix 4 #

Instances

Eq Bool 

Methods

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

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

Eq Char 

Methods

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

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

Eq Double 

Methods

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

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

Eq Float 

Methods

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

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

Eq Int 

Methods

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

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

Eq Int8

Since: 2.1

Methods

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

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

Eq Int16

Since: 2.1

Methods

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

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

Eq Int32

Since: 2.1

Methods

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

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

Eq Int64

Since: 2.1

Methods

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

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

Eq Integer 

Methods

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

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

Eq Natural 

Methods

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

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

Eq Ordering 
Eq Word 

Methods

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

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

Eq Word8

Since: 2.1

Methods

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

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

Eq Word16

Since: 2.1

Methods

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

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

Eq Word32

Since: 2.1

Methods

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

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

Eq Word64

Since: 2.1

Methods

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

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

Eq SomeTypeRep 
Eq () 

Methods

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

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

Eq TyCon 

Methods

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

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

Eq Module 

Methods

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

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

Eq TrName 

Methods

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

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

Eq EventLifetime 

Methods

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

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

Eq BigNat 

Methods

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

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

Eq Void

Since: 4.8.0.0

Methods

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

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

Eq SpecConstrAnnotation 
Eq Constr

Equality of constructors

Since: 4.0.0.0

Methods

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

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

Eq DataRep 

Methods

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

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

Eq ConstrRep 
Eq Fixity 

Methods

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

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

Eq Version

Since: 2.1

Methods

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

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

Eq HandlePosn

Since: 4.1.0.0

Eq ThreadId

Since: 4.2.0.0

Eq BlockReason 
Eq ThreadStatus 
Eq Event 

Methods

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

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

Eq Lifetime 
Eq CDev 

Methods

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

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

Eq CIno 

Methods

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

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

Eq CMode 

Methods

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

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

Eq COff 

Methods

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

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

Eq CPid 

Methods

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

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

Eq CSsize 

Methods

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

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

Eq CGid 

Methods

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

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

Eq CNlink 

Methods

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

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

Eq CUid 

Methods

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

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

Eq CCc 

Methods

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

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

Eq CSpeed 

Methods

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

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

Eq CTcflag 

Methods

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

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

Eq CRLim 

Methods

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

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

Eq CBlkSize 
Eq CBlkCnt 

Methods

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

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

Eq CClockId 
Eq CFsBlkCnt 
Eq CFsFilCnt 
Eq CId 

Methods

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

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

Eq CKey 

Methods

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

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

Eq CTimer 

Methods

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

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

Eq Fd 

Methods

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

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

Eq Errno

Since: 2.1

Methods

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

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

Eq AsyncException 
Eq ArrayException 
Eq ExitCode 
Eq IOErrorType

Since: 4.1.0.0

Eq Handle

Since: 4.1.0.0

Methods

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

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

Eq BufferMode 
Eq Newline 

Methods

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

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

Eq NewlineMode 
Eq IODeviceType 
Eq SeekMode 
Eq MaskingState 
Eq IOException

Since: 4.1.0.0

Eq ErrorCall 
Eq ArithException 
Eq All 

Methods

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

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

Eq Any 

Methods

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

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

Eq Fixity 

Methods

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

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

Eq Associativity 
Eq SourceUnpackedness 
Eq SourceStrictness 
Eq DecidedStrictness 
Eq SomeSymbol

Since: 4.7.0.0

Eq SomeNat

Since: 4.7.0.0

Methods

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

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

Eq CChar 

Methods

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

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

Eq CSChar 

Methods

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

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

Eq CUChar 

Methods

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

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

Eq CShort 

Methods

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

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

Eq CUShort 

Methods

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

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

Eq CInt 

Methods

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

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

Eq CUInt 

Methods

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

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

Eq CLong 

Methods

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

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

Eq CULong 

Methods

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

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

Eq CLLong 

Methods

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

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

Eq CULLong 

Methods

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

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

Eq CBool 

Methods

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

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

Eq CFloat 

Methods

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

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

Eq CDouble 

Methods

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

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

Eq CPtrdiff 
Eq CSize 

Methods

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

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

Eq CWchar 

Methods

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

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

Eq CSigAtomic 
Eq CClock 

Methods

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

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

Eq CTime 

Methods

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

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

Eq CUSeconds 
Eq CSUSeconds 
Eq CIntPtr 

Methods

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

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

Eq CUIntPtr 
Eq CIntMax 

Methods

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

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

Eq CUIntMax 
Eq WordPtr 

Methods

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

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

Eq IntPtr 

Methods

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

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

Eq IOMode 

Methods

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

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

Eq Lexeme 

Methods

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

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

Eq Number 

Methods

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

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

Eq GeneralCategory 
Eq SrcLoc 

Methods

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

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

Eq ASCII7_Invalid 

Methods

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

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

Eq ISO_8859_1_Invalid 

Methods

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

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

Eq UTF16_Invalid 

Methods

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

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

Eq UTF32_Invalid 

Methods

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

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

Eq Encoding 
Eq String 

Methods

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

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

Eq ValidationFailure 
Eq AsciiString 
Eq OutOfBoundOperation 
Eq RecastSourceSize 
Eq RecastDestinationSize 
Eq Addr 

Methods

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

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

Eq FileSize 
Eq Word256 

Methods

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

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

Eq Word128 

Methods

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

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

Eq Char7 

Methods

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

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

Eq Endianness 
Eq Sign # 

Methods

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

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

Eq Bitmap # 

Methods

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

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

Eq PartialError # 
Eq And # 

Methods

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

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

Eq Condition # 
Eq Arch # 

Methods

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

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

Eq OS # 

Methods

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

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

Eq Seconds # 

Methods

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

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

Eq NanoSeconds # 
Eq IPv6 # 

Methods

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

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

Eq IPv4 # 

Methods

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

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

Eq UUID # 

Methods

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

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

Eq FileName # 
Eq FilePath # 
Eq Relativity # 
Eq a => Eq [a] 

Methods

(==) :: [a] -> [a] -> Bool #

(/=) :: [a] -> [a] -> Bool #

Eq a => Eq (Maybe a) 

Methods

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

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

Eq a => Eq (Ratio a) 

Methods

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

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

Eq (Ptr a) 

Methods

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

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

Eq (FunPtr a) 

Methods

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

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

Eq p => Eq (Par1 p) 

Methods

(==) :: Par1 p -> Par1 p -> Bool #

(/=) :: Par1 p -> Par1 p -> Bool #

Eq a => Eq (Min a) 

Methods

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

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

Eq a => Eq (Max a) 

Methods

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

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

Eq a => Eq (First a) 

Methods

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

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

Eq a => Eq (Last a) 

Methods

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

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

Eq m => Eq (WrappedMonoid m) 
Eq a => Eq (Option a) 

Methods

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

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

Eq a => Eq (NonEmpty a) 

Methods

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

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

Eq a => Eq (ZipList a) 

Methods

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

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

Eq a => Eq (Identity a) 

Methods

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

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

Eq (TVar a)

Since: 4.8.0.0

Methods

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

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

Eq (ForeignPtr a)

Since: 2.1

Methods

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

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

Eq (IORef a)

Since: 4.1.0.0

Methods

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

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

Eq a => Eq (Dual a) 

Methods

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

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

Eq a => Eq (Sum a) 

Methods

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

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

Eq a => Eq (Product a) 

Methods

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

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

Eq a => Eq (First a) 

Methods

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

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

Eq a => Eq (Last a) 

Methods

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

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

Eq a => Eq (Array a) 

Methods

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

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

(PrimType ty, Eq ty) => Eq (UArray ty) 

Methods

(==) :: UArray ty -> UArray ty -> Bool #

(/=) :: UArray ty -> UArray ty -> Bool #

(PrimType ty, Eq ty) => Eq (Block ty) 

Methods

(==) :: Block ty -> Block ty -> Bool #

(/=) :: Block ty -> Block ty -> Bool #

Eq a => Eq (NonEmpty a) 

Methods

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

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

Eq (Offset ty) 

Methods

(==) :: Offset ty -> Offset ty -> Bool #

(/=) :: Offset ty -> Offset ty -> Bool #

Eq (CountOf ty) 

Methods

(==) :: CountOf ty -> CountOf ty -> Bool #

(/=) :: CountOf ty -> CountOf ty -> Bool #

Eq (Zn64 n) 

Methods

(==) :: Zn64 n -> Zn64 n -> Bool #

(/=) :: Zn64 n -> Zn64 n -> Bool #

Eq (Zn n) 

Methods

(==) :: Zn n -> Zn n -> Bool #

(/=) :: Zn n -> Zn n -> Bool #

Eq (FinalPtr a) 

Methods

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

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

Eq a => Eq (LE a) 

Methods

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

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

Eq a => Eq (BE a) 

Methods

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

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

Eq a => Eq (DList a) # 

Methods

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

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

PrimType ty => Eq (ChunkedUArray ty) # 
(Eq b, Eq a) => Eq (Either a b) 

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

Eq (V1 k p) 

Methods

(==) :: V1 k p -> V1 k p -> Bool #

(/=) :: V1 k p -> V1 k p -> Bool #

Eq (U1 k p)

Since: 4.9.0.0

Methods

(==) :: U1 k p -> U1 k p -> Bool #

(/=) :: U1 k p -> U1 k p -> Bool #

Eq (TypeRep k a)

Since: 2.1

Methods

(==) :: TypeRep k a -> TypeRep k a -> Bool #

(/=) :: TypeRep k a -> TypeRep k a -> Bool #

(Eq a, Eq b) => Eq (a, b) 

Methods

(==) :: (a, b) -> (a, b) -> Bool #

(/=) :: (a, b) -> (a, b) -> Bool #

(Ix i, Eq e) => Eq (Array i e)

Since: 2.1

Methods

(==) :: Array i e -> Array i e -> Bool #

(/=) :: Array i e -> Array i e -> Bool #

Eq a => Eq (Arg a b)

Since: 4.9.0.0

Methods

(==) :: Arg a b -> Arg a b -> Bool #

(/=) :: Arg a b -> Arg a b -> Bool #

Eq (Proxy k s)

Since: 4.7.0.0

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Eq a => Eq (ListN n a) 

Methods

(==) :: ListN n a -> ListN n a -> Bool #

(/=) :: ListN n a -> ListN n a -> Bool #

(Eq b, Eq a) => Eq (These a b) 

Methods

(==) :: These a b -> These a b -> Bool #

(/=) :: These a b -> These a b -> Bool #

(Eq b, Eq a) => Eq (Tuple2 a b) # 

Methods

(==) :: Tuple2 a b -> Tuple2 a b -> Bool #

(/=) :: Tuple2 a b -> Tuple2 a b -> Bool #

Eq (f p) => Eq (Rec1 k f p) 

Methods

(==) :: Rec1 k f p -> Rec1 k f p -> Bool #

(/=) :: Rec1 k f p -> Rec1 k f p -> Bool #

Eq (URec k (Ptr ()) p) 

Methods

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

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

Eq (URec k Char p) 

Methods

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

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

Eq (URec k Double p) 

Methods

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

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

Eq (URec k Float p) 

Methods

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

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

Eq (URec k Int p) 

Methods

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

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

Eq (URec k Word p) 

Methods

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

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

(Eq a, Eq b, Eq c) => Eq (a, b, c) 

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool #

(/=) :: (a, b, c) -> (a, b, c) -> Bool #

Eq (STArray s i e)

Since: 2.1

Methods

(==) :: STArray s i e -> STArray s i e -> Bool #

(/=) :: STArray s i e -> STArray s i e -> Bool #

Eq a => Eq (Const k a b) 

Methods

(==) :: Const k a b -> Const k a b -> Bool #

(/=) :: Const k a b -> Const k a b -> Bool #

Eq (f a) => Eq (Alt k f a) 

Methods

(==) :: Alt k f a -> Alt k f a -> Bool #

(/=) :: Alt k f a -> Alt k f a -> Bool #

Eq (Coercion k a b) 

Methods

(==) :: Coercion k a b -> Coercion k a b -> Bool #

(/=) :: Coercion k a b -> Coercion k a b -> Bool #

Eq ((:~:) k a b) 

Methods

(==) :: (k :~: a) b -> (k :~: a) b -> Bool #

(/=) :: (k :~: a) b -> (k :~: a) b -> Bool #

(Eq c, Eq b, Eq a) => Eq (Tuple3 a b c) # 

Methods

(==) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

(/=) :: Tuple3 a b c -> Tuple3 a b c -> Bool #

Eq c => Eq (K1 k i c p) 

Methods

(==) :: K1 k i c p -> K1 k i c p -> Bool #

(/=) :: K1 k i c p -> K1 k i c p -> Bool #

(Eq (g p), Eq (f p)) => Eq ((:+:) k f g p) 

Methods

(==) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

(/=) :: (k :+: f) g p -> (k :+: f) g p -> Bool #

(Eq (g p), Eq (f p)) => Eq ((:*:) k f g p) 

Methods

(==) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

(/=) :: (k :*: f) g p -> (k :*: f) g p -> Bool #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) 

Methods

(==) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

(/=) :: (a, b, c, d) -> (a, b, c, d) -> Bool #

Eq ((:~~:) k1 k2 a b)

Since: 4.10.0.0

Methods

(==) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

(/=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool #

(Eq d, Eq c, Eq b, Eq a) => Eq (Tuple4 a b c d) # 

Methods

(==) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

(/=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool #

Eq (f p) => Eq (M1 k i c f p) 

Methods

(==) :: M1 k i c f p -> M1 k i c f p -> Bool #

(/=) :: M1 k i c f p -> M1 k i c f p -> Bool #

Eq (f (g p)) => Eq ((:.:) k2 k1 f g p) 

Methods

(==) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

(/=) :: (k2 :.: k1) f g p -> (k2 :.: k1) f g p -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) 

Methods

(==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) 

Methods

(==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(/=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) 

Methods

(==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(/=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) 

Methods

(==) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

class Bounded a where #

The Bounded class is used to name the upper and lower limits of a type. Ord is not a superclass of Bounded since types that are not totally ordered may also have upper and lower bounds.

The Bounded class may be derived for any enumeration type; minBound is the first constructor listed in the data declaration and maxBound is the last. Bounded may also be derived for single-constructor datatypes whose constituent types are in Bounded.

Minimal complete definition

minBound, maxBound

Methods

minBound :: a #

maxBound :: a #

Instances

Bounded Bool

Since: 2.1

Bounded Char

Since: 2.1

Bounded Int

Since: 2.1

Methods

minBound :: Int #

maxBound :: Int #

Bounded Int8

Since: 2.1

Bounded Int16

Since: 2.1

Bounded Int32

Since: 2.1

Bounded Int64

Since: 2.1

Bounded Ordering

Since: 2.1

Bounded Word

Since: 2.1

Bounded Word8

Since: 2.1

Bounded Word16

Since: 2.1

Bounded Word32

Since: 2.1

Bounded Word64

Since: 2.1

Bounded VecCount

Since: 4.10.0.0

Bounded VecElem

Since: 4.10.0.0

Bounded ()

Since: 2.1

Methods

minBound :: () #

maxBound :: () #

Bounded CDev 
Bounded CIno 
Bounded CMode 
Bounded COff 
Bounded CPid 
Bounded CSsize 
Bounded CGid 
Bounded CNlink 
Bounded CUid 
Bounded CTcflag 
Bounded CRLim 
Bounded CBlkSize 
Bounded CBlkCnt 
Bounded CClockId 
Bounded CFsBlkCnt 
Bounded CFsFilCnt 
Bounded CId 

Methods

minBound :: CId #

maxBound :: CId #

Bounded CKey 
Bounded Fd 

Methods

minBound :: Fd #

maxBound :: Fd #

Bounded All 

Methods

minBound :: All #

maxBound :: All #

Bounded Any 

Methods

minBound :: Any #

maxBound :: Any #

Bounded Associativity 
Bounded SourceUnpackedness 
Bounded SourceStrictness 
Bounded DecidedStrictness 
Bounded CChar 
Bounded CSChar 
Bounded CUChar 
Bounded CShort 
Bounded CUShort 
Bounded CInt 
Bounded CUInt 
Bounded CLong 
Bounded CULong 
Bounded CLLong 
Bounded CULLong 
Bounded CBool 
Bounded CPtrdiff 
Bounded CSize 
Bounded CWchar 
Bounded CSigAtomic 
Bounded CIntPtr 
Bounded CUIntPtr 
Bounded CIntMax 
Bounded CUIntMax 
Bounded WordPtr 
Bounded IntPtr 
Bounded GeneralCategory 
Bounded UTF32_Invalid 

Methods

minBound :: UTF32_Invalid #

maxBound :: UTF32_Invalid #

Bounded Encoding 
Bounded Word256 
Bounded Word128 
Bounded Arch # 
Bounded OS # 

Methods

minBound :: OS #

maxBound :: OS #

Bounded Seconds # 
Bounded NanoSeconds # 
Bounded a => Bounded (Min a) 

Methods

minBound :: Min a #

maxBound :: Min a #

Bounded a => Bounded (Max a) 

Methods

minBound :: Max a #

maxBound :: Max a #

Bounded a => Bounded (First a) 

Methods

minBound :: First a #

maxBound :: First a #

Bounded a => Bounded (Last a) 

Methods

minBound :: Last a #

maxBound :: Last a #

Bounded m => Bounded (WrappedMonoid m) 
Bounded a => Bounded (Identity a) 
Bounded a => Bounded (Dual a) 

Methods

minBound :: Dual a #

maxBound :: Dual a #

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Bounded a => Bounded (Product a) 
(Bounded a, Bounded b) => Bounded (a, b)

Since: 2.1

Methods

minBound :: (a, b) #

maxBound :: (a, b) #

Bounded (Proxy k t) 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c)

Since: 2.1

Methods

minBound :: (a, b, c) #

maxBound :: (a, b, c) #

Bounded a => Bounded (Const k a b) 

Methods

minBound :: Const k a b #

maxBound :: Const k a b #

Coercible k a b => Bounded (Coercion k a b)

Since: 4.7.0.0

Methods

minBound :: Coercion k a b #

maxBound :: Coercion k a b #

(~) k a b => Bounded ((:~:) k a b)

Since: 4.7.0.0

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d)

Since: 2.1

Methods

minBound :: (a, b, c, d) #

maxBound :: (a, b, c, d) #

(~~) k1 k2 a b => Bounded ((:~~:) k1 k2 a b)

Since: 4.10.0.0

Methods

minBound :: (k1 :~~: k2) a b #

maxBound :: (k1 :~~: k2) a b #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e)

Since: 2.1

Methods

minBound :: (a, b, c, d, e) #

maxBound :: (a, b, c, d, e) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f) #

maxBound :: (a, b, c, d, e, f) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g) #

maxBound :: (a, b, c, d, e, f, g) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h) #

maxBound :: (a, b, c, d, e, f, g, h) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i) #

maxBound :: (a, b, c, d, e, f, g, h, i) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j) #

maxBound :: (a, b, c, d, e, f, g, h, i, j) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: 2.1

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

class Enum a where #

Class Enum defines operations on sequentially ordered types.

The enumFrom... methods are used in Haskell's translation of arithmetic sequences.

Instances of Enum may be derived for any enumeration type (types whose constructors have no fields). The nullary constructors are assumed to be numbered left-to-right by fromEnum from 0 through n-1. See Chapter 10 of the Haskell Report for more details.

For any type that is an instance of class Bounded as well as Enum, the following should hold:

   enumFrom     x   = enumFromTo     x maxBound
   enumFromThen x y = enumFromThenTo x y bound
     where
       bound | fromEnum y >= fromEnum x = maxBound
             | otherwise                = minBound

Minimal complete definition

toEnum, fromEnum

Methods

succ :: a -> a #

the successor of a value. For numeric types, succ adds 1.

pred :: a -> a #

the predecessor of a value. For numeric types, pred subtracts 1.

toEnum :: Int -> a #

Convert from an Int.

fromEnum :: a -> Int #

Convert to an Int. It is implementation-dependent what fromEnum returns when applied to a value that is too large to fit in an Int.

enumFrom :: a -> [a] #

Used in Haskell's translation of [n..].

enumFromThen :: a -> a -> [a] #

Used in Haskell's translation of [n,n'..].

enumFromTo :: a -> a -> [a] #

Used in Haskell's translation of [n..m].

enumFromThenTo :: a -> a -> a -> [a] #

Used in Haskell's translation of [n,n'..m].

Instances

Enum Bool

Since: 2.1

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Enum Char

Since: 2.1

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Enum Int

Since: 2.1

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Enum Int8

Since: 2.1

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Enum Int16

Since: 2.1

Enum Int32

Since: 2.1

Enum Int64

Since: 2.1

Enum Integer

Since: 2.1

Enum Natural

Since: 4.8.0.0

Enum Ordering

Since: 2.1

Enum Word

Since: 2.1

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Enum Word8

Since: 2.1

Enum Word16

Since: 2.1

Enum Word32

Since: 2.1

Enum Word64

Since: 2.1

Enum VecCount

Since: 4.10.0.0

Enum VecElem

Since: 4.10.0.0

Enum ()

Since: 2.1

Methods

succ :: () -> () #

pred :: () -> () #

toEnum :: Int -> () #

fromEnum :: () -> Int #

enumFrom :: () -> [()] #

enumFromThen :: () -> () -> [()] #

enumFromTo :: () -> () -> [()] #

enumFromThenTo :: () -> () -> () -> [()] #

Enum CDev 

Methods

succ :: CDev -> CDev #

pred :: CDev -> CDev #

toEnum :: Int -> CDev #

fromEnum :: CDev -> Int #

enumFrom :: CDev -> [CDev] #

enumFromThen :: CDev -> CDev -> [CDev] #

enumFromTo :: CDev -> CDev -> [CDev] #

enumFromThenTo :: CDev -> CDev -> CDev -> [CDev] #

Enum CIno 

Methods

succ :: CIno -> CIno #

pred :: CIno -> CIno #

toEnum :: Int -> CIno #

fromEnum :: CIno -> Int #

enumFrom :: CIno -> [CIno] #

enumFromThen :: CIno -> CIno -> [CIno] #

enumFromTo :: CIno -> CIno -> [CIno] #

enumFromThenTo :: CIno -> CIno -> CIno -> [CIno] #

Enum CMode 
Enum COff 

Methods

succ :: COff -> COff #

pred :: COff -> COff #

toEnum :: Int -> COff #

fromEnum :: COff -> Int #

enumFrom :: COff -> [COff] #

enumFromThen :: COff -> COff -> [COff] #

enumFromTo :: COff -> COff -> [COff] #

enumFromThenTo :: COff -> COff -> COff -> [COff] #

Enum CPid 

Methods

succ :: CPid -> CPid #

pred :: CPid -> CPid #

toEnum :: Int -> CPid #

fromEnum :: CPid -> Int #

enumFrom :: CPid -> [CPid] #

enumFromThen :: CPid -> CPid -> [CPid] #

enumFromTo :: CPid -> CPid -> [CPid] #

enumFromThenTo :: CPid -> CPid -> CPid -> [CPid] #

Enum CSsize 
Enum CGid 

Methods

succ :: CGid -> CGid #

pred :: CGid -> CGid #

toEnum :: Int -> CGid #

fromEnum :: CGid -> Int #

enumFrom :: CGid -> [CGid] #

enumFromThen :: CGid -> CGid -> [CGid] #

enumFromTo :: CGid -> CGid -> [CGid] #

enumFromThenTo :: CGid -> CGid -> CGid -> [CGid] #

Enum CNlink 
Enum CUid 

Methods

succ :: CUid -> CUid #

pred :: CUid -> CUid #

toEnum :: Int -> CUid #

fromEnum :: CUid -> Int #

enumFrom :: CUid -> [CUid] #

enumFromThen :: CUid -> CUid -> [CUid] #

enumFromTo :: CUid -> CUid -> [CUid] #

enumFromThenTo :: CUid -> CUid -> CUid -> [CUid] #

Enum CCc 

Methods

succ :: CCc -> CCc #

pred :: CCc -> CCc #

toEnum :: Int -> CCc #

fromEnum :: CCc -> Int #

enumFrom :: CCc -> [CCc] #

enumFromThen :: CCc -> CCc -> [CCc] #

enumFromTo :: CCc -> CCc -> [CCc] #

enumFromThenTo :: CCc -> CCc -> CCc -> [CCc] #

Enum CSpeed 
Enum CTcflag 
Enum CRLim 
Enum CBlkSize 
Enum CBlkCnt 
Enum CClockId 
Enum CFsBlkCnt 
Enum CFsFilCnt 
Enum CId 

Methods

succ :: CId -> CId #

pred :: CId -> CId #

toEnum :: Int -> CId #

fromEnum :: CId -> Int #

enumFrom :: CId -> [CId] #

enumFromThen :: CId -> CId -> [CId] #

enumFromTo :: CId -> CId -> [CId] #

enumFromThenTo :: CId -> CId -> CId -> [CId] #

Enum CKey 

Methods

succ :: CKey -> CKey #

pred :: CKey -> CKey #

toEnum :: Int -> CKey #

fromEnum :: CKey -> Int #

enumFrom :: CKey -> [CKey] #

enumFromThen :: CKey -> CKey -> [CKey] #

enumFromTo :: CKey -> CKey -> [CKey] #

enumFromThenTo :: CKey -> CKey -> CKey -> [CKey] #

Enum Fd 

Methods

succ :: Fd -> Fd #

pred :: Fd -> Fd #

toEnum :: Int -> Fd #

fromEnum :: Fd -> Int #

enumFrom :: Fd -> [Fd] #

enumFromThen :: Fd -> Fd -> [Fd] #

enumFromTo :: Fd -> Fd -> [Fd] #

enumFromThenTo :: Fd -> Fd -> Fd -> [Fd] #

Enum SeekMode 
Enum Associativity 
Enum SourceUnpackedness 
Enum SourceStrictness 
Enum DecidedStrictness 
Enum CChar 
Enum CSChar 
Enum CUChar 
Enum CShort 
Enum CUShort 
Enum CInt 

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

enumFromThen :: CInt -> CInt -> [CInt] #

enumFromTo :: CInt -> CInt -> [CInt] #

enumFromThenTo :: CInt -> CInt -> CInt -> [CInt] #

Enum CUInt 
Enum CLong 
Enum CULong 
Enum CLLong 
Enum CULLong 
Enum CBool 
Enum CFloat 
Enum CDouble 
Enum CPtrdiff 
Enum CSize 
Enum CWchar 
Enum CSigAtomic 
Enum CClock 
Enum CTime 
Enum CUSeconds 
Enum CSUSeconds 
Enum CIntPtr 
Enum CUIntPtr 
Enum CIntMax 
Enum CUIntMax 
Enum WordPtr 
Enum IntPtr 
Enum IOMode 
Enum GeneralCategory 
Enum UTF32_Invalid 

Methods

succ :: UTF32_Invalid -> UTF32_Invalid #

pred :: UTF32_Invalid -> UTF32_Invalid #

toEnum :: Int -> UTF32_Invalid #

fromEnum :: UTF32_Invalid -> Int #

enumFrom :: UTF32_Invalid -> [UTF32_Invalid] #

enumFromThen :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] #

enumFromTo :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] #

enumFromThenTo :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] #

Enum Encoding 
Enum Word256 
Enum Word128 
Enum Arch # 

Methods

succ :: Arch -> Arch #

pred :: Arch -> Arch #

toEnum :: Int -> Arch #

fromEnum :: Arch -> Int #

enumFrom :: Arch -> [Arch] #

enumFromThen :: Arch -> Arch -> [Arch] #

enumFromTo :: Arch -> Arch -> [Arch] #

enumFromThenTo :: Arch -> Arch -> Arch -> [Arch] #

Enum OS # 

Methods

succ :: OS -> OS #

pred :: OS -> OS #

toEnum :: Int -> OS #

fromEnum :: OS -> Int #

enumFrom :: OS -> [OS] #

enumFromThen :: OS -> OS -> [OS] #

enumFromTo :: OS -> OS -> [OS] #

enumFromThenTo :: OS -> OS -> OS -> [OS] #

Enum Seconds # 
Enum NanoSeconds # 
Integral a => Enum (Ratio a)

Since: 2.0.1

Methods

succ :: Ratio a -> Ratio a #

pred :: Ratio a -> Ratio a #

toEnum :: Int -> Ratio a #

fromEnum :: Ratio a -> Int #

enumFrom :: Ratio a -> [Ratio a] #

enumFromThen :: Ratio a -> Ratio a -> [Ratio a] #

enumFromTo :: Ratio a -> Ratio a -> [Ratio a] #

enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a] #

Enum a => Enum (Min a)

Since: 4.9.0.0

Methods

succ :: Min a -> Min a #

pred :: Min a -> Min a #

toEnum :: Int -> Min a #

fromEnum :: Min a -> Int #

enumFrom :: Min a -> [Min a] #

enumFromThen :: Min a -> Min a -> [Min a] #

enumFromTo :: Min a -> Min a -> [Min a] #

enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] #

Enum a => Enum (Max a)

Since: 4.9.0.0

Methods

succ :: Max a -> Max a #

pred :: Max a -> Max a #

toEnum :: Int -> Max a #

fromEnum :: Max a -> Int #

enumFrom :: Max a -> [Max a] #

enumFromThen :: Max a -> Max a -> [Max a] #

enumFromTo :: Max a -> Max a -> [Max a] #

enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] #

Enum a => Enum (First a)

Since: 4.9.0.0

Methods

succ :: First a -> First a #

pred :: First a -> First a #

toEnum :: Int -> First a #

fromEnum :: First a -> Int #

enumFrom :: First a -> [First a] #

enumFromThen :: First a -> First a -> [First a] #

enumFromTo :: First a -> First a -> [First a] #

enumFromThenTo :: First a -> First a -> First a -> [First a] #

Enum a => Enum (Last a)

Since: 4.9.0.0

Methods

succ :: Last a -> Last a #

pred :: Last a -> Last a #

toEnum :: Int -> Last a #

fromEnum :: Last a -> Int #

enumFrom :: Last a -> [Last a] #

enumFromThen :: Last a -> Last a -> [Last a] #

enumFromTo :: Last a -> Last a -> [Last a] #

enumFromThenTo :: Last a -> Last a -> Last a -> [Last a] #

Enum a => Enum (WrappedMonoid a)

Since: 4.9.0.0

Enum a => Enum (Identity a) 
Enum (Offset ty) 

Methods

succ :: Offset ty -> Offset ty #

pred :: Offset ty -> Offset ty #

toEnum :: Int -> Offset ty #

fromEnum :: Offset ty -> Int #

enumFrom :: Offset ty -> [Offset ty] #

enumFromThen :: Offset ty -> Offset ty -> [Offset ty] #

enumFromTo :: Offset ty -> Offset ty -> [Offset ty] #

enumFromThenTo :: Offset ty -> Offset ty -> Offset ty -> [Offset ty] #

Enum (CountOf ty) 

Methods

succ :: CountOf ty -> CountOf ty #

pred :: CountOf ty -> CountOf ty #

toEnum :: Int -> CountOf ty #

fromEnum :: CountOf ty -> Int #

enumFrom :: CountOf ty -> [CountOf ty] #

enumFromThen :: CountOf ty -> CountOf ty -> [CountOf ty] #

enumFromTo :: CountOf ty -> CountOf ty -> [CountOf ty] #

enumFromThenTo :: CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty] #

Enum (Proxy k s)

Since: 4.7.0.0

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Enum a => Enum (Const k a b) 

Methods

succ :: Const k a b -> Const k a b #

pred :: Const k a b -> Const k a b #

toEnum :: Int -> Const k a b #

fromEnum :: Const k a b -> Int #

enumFrom :: Const k a b -> [Const k a b] #

enumFromThen :: Const k a b -> Const k a b -> [Const k a b] #

enumFromTo :: Const k a b -> Const k a b -> [Const k a b] #

enumFromThenTo :: Const k a b -> Const k a b -> Const k a b -> [Const k a b] #

Enum (f a) => Enum (Alt k f a) 

Methods

succ :: Alt k f a -> Alt k f a #

pred :: Alt k f a -> Alt k f a #

toEnum :: Int -> Alt k f a #

fromEnum :: Alt k f a -> Int #

enumFrom :: Alt k f a -> [Alt k f a] #

enumFromThen :: Alt k f a -> Alt k f a -> [Alt k f a] #

enumFromTo :: Alt k f a -> Alt k f a -> [Alt k f a] #

enumFromThenTo :: Alt k f a -> Alt k f a -> Alt k f a -> [Alt k f a] #

Coercible k a b => Enum (Coercion k a b)

Since: 4.7.0.0

Methods

succ :: Coercion k a b -> Coercion k a b #

pred :: Coercion k a b -> Coercion k a b #

toEnum :: Int -> Coercion k a b #

fromEnum :: Coercion k a b -> Int #

enumFrom :: Coercion k a b -> [Coercion k a b] #

enumFromThen :: Coercion k a b -> Coercion k a b -> [Coercion k a b] #

enumFromTo :: Coercion k a b -> Coercion k a b -> [Coercion k a b] #

enumFromThenTo :: Coercion k a b -> Coercion k a b -> Coercion k a b -> [Coercion k a b] #

(~) k a b => Enum ((:~:) k a b)

Since: 4.7.0.0

Methods

succ :: (k :~: a) b -> (k :~: a) b #

pred :: (k :~: a) b -> (k :~: a) b #

toEnum :: Int -> (k :~: a) b #

fromEnum :: (k :~: a) b -> Int #

enumFrom :: (k :~: a) b -> [(k :~: a) b] #

enumFromThen :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromTo :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromThenTo :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

(~~) k1 k2 a b => Enum ((:~~:) k1 k2 a b)

Since: 4.10.0.0

Methods

succ :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

pred :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

toEnum :: Int -> (k1 :~~: k2) a b #

fromEnum :: (k1 :~~: k2) a b -> Int #

enumFrom :: (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromThen :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromTo :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromThenTo :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

class Functor (f :: * -> *) where #

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

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

The instances of Functor for lists, Maybe and IO satisfy these laws.

Minimal complete definition

fmap

Methods

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

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

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

Instances

Functor []

Since: 2.1

Methods

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

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

Functor Maybe

Since: 2.1

Methods

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

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

Functor IO

Since: 2.1

Methods

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

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

Functor Par1 

Methods

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

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

Functor P 

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Functor Min

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

Functor Max

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max a #

Functor First

Since: 4.9.0.0

Methods

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

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

Functor Last

Since: 4.9.0.0

Methods

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

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

Functor Option

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Functor NonEmpty

Since: 4.9.0.0

Methods

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

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

Functor ZipList 

Methods

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

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

Functor Identity

Since: 4.8.0.0

Methods

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

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

Functor Handler

Since: 4.6.0.0

Methods

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

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

Functor STM

Since: 4.3.0.0

Methods

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

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

Functor Dual

Since: 4.8.0.0

Methods

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

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

Functor Sum

Since: 4.8.0.0

Methods

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

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

Functor Product

Since: 4.8.0.0

Methods

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

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

Functor First 

Methods

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

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

Functor Last 

Methods

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

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

Functor ReadP

Since: 2.1

Methods

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

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

Functor Array 

Methods

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

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

Functor DList # 

Methods

fmap :: (a -> b) -> DList a -> DList b #

(<$) :: a -> DList b -> DList a #

Functor Partial # 

Methods

fmap :: (a -> b) -> Partial a -> Partial b #

(<$) :: a -> Partial b -> Partial a #

Functor Gen # 

Methods

fmap :: (a -> b) -> Gen a -> Gen b #

(<$) :: a -> Gen b -> Gen a #

Functor Check # 

Methods

fmap :: (a -> b) -> Check a -> Check b #

(<$) :: a -> Check b -> Check a #

Functor (Either a)

Since: 3.0

Methods

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

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

Functor (V1 *) 

Methods

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

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

Functor (U1 *)

Since: 4.9.0.0

Methods

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

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

Functor ((,) a)

Since: 2.1

Methods

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

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

Functor (Array i)

Since: 2.1

Methods

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

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

Functor (Arg a)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b #

(<$) :: a -> Arg a b -> Arg a a #

Monad m => Functor (WrappedMonad m)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Functor (ArrowMonad a)

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

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

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

Functor (ST s)

Since: 2.1

Methods

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

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

Functor (These a) 

Methods

fmap :: (a -> b) -> These a a -> These a b #

(<$) :: a -> These a b -> These a a #

Functor m => Functor (ResourceT m) # 

Methods

fmap :: (a -> b) -> ResourceT m a -> ResourceT m b #

(<$) :: a -> ResourceT m b -> ResourceT m a #

Functor (Parser input) # 

Methods

fmap :: (a -> b) -> Parser input a -> Parser input b #

(<$) :: a -> Parser input b -> Parser input a #

Functor (Result input) # 

Methods

fmap :: (a -> b) -> Result input a -> Result input b #

(<$) :: a -> Result input b -> Result input a #

Functor (MonadRandomState gen) # 

Methods

fmap :: (a -> b) -> MonadRandomState gen a -> MonadRandomState gen b #

(<$) :: a -> MonadRandomState gen b -> MonadRandomState gen a #

Functor f => Functor (Rec1 * f) 

Methods

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

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

Functor (URec * Char) 

Methods

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

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

Functor (URec * Double) 

Methods

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

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

Functor (URec * Float) 

Methods

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

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

Functor (URec * Int) 

Methods

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

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

Functor (URec * Word) 

Methods

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

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

Functor (URec * (Ptr ())) 

Methods

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

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

Arrow a => Functor (WrappedArrow a b)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a #

Functor (Const * m)

Since: 2.1

Methods

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

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

Functor f => Functor (Alt * f) 

Methods

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

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

Monad m => Functor (State s m) 

Methods

fmap :: (a -> b) -> State s m a -> State s m b #

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

Monad m => Functor (Reader r m) 

Methods

fmap :: (a -> b) -> Reader r m a -> Reader r m b #

(<$) :: a -> Reader r m b -> Reader r m a #

Functor m => Functor (StateT s m) # 

Methods

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

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

Functor m => Functor (ReaderT r m) # 

Methods

fmap :: (a -> b) -> ReaderT r m a -> ReaderT r m b #

(<$) :: a -> ReaderT r m b -> ReaderT r m a #

Functor m => Functor (ExceptT e m) # 

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b #

(<$) :: a -> ExceptT e m b -> ExceptT e m a #

Monad m => Functor (ZipSink i m) # 

Methods

fmap :: (a -> b) -> ZipSink i m a -> ZipSink i m b #

(<$) :: a -> ZipSink i m b -> ZipSink i m a #

Functor ((->) LiftedRep LiftedRep r)

Since: 2.1

Methods

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

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

Functor (K1 * i c) 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

Functor (Conduit i o m) # 

Methods

fmap :: (a -> b) -> Conduit i o m a -> Conduit i o m b #

(<$) :: a -> Conduit i o m b -> Conduit i o m a #

Functor f => Functor (M1 * i c f) 

Methods

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

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

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

Methods

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

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

Monad state => Functor (Builder collection mutCollection step state err) 

Methods

fmap :: (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b #

(<$) :: a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a #

class Integral a where #

Integral Literal support

e.g. 123 :: Integer 123 :: Word8

Minimal complete definition

fromInteger

Methods

fromInteger :: Integer -> a #

Instances

Integral Double 
Integral Float 

Methods

fromInteger :: Integer -> Float #

Integral Int 

Methods

fromInteger :: Integer -> Int #

Integral Int8 

Methods

fromInteger :: Integer -> Int8 #

Integral Int16 

Methods

fromInteger :: Integer -> Int16 #

Integral Int32 

Methods

fromInteger :: Integer -> Int32 #

Integral Int64 

Methods

fromInteger :: Integer -> Int64 #

Integral Integer 
Integral Natural 
Integral Word 

Methods

fromInteger :: Integer -> Word #

Integral Word8 

Methods

fromInteger :: Integer -> Word8 #

Integral Word16 
Integral Word32 
Integral Word64 
Integral COff 

Methods

fromInteger :: Integer -> COff #

Integral CChar 

Methods

fromInteger :: Integer -> CChar #

Integral CSChar 
Integral CUChar 
Integral CShort 
Integral CUShort 
Integral CInt 

Methods

fromInteger :: Integer -> CInt #

Integral CUInt 

Methods

fromInteger :: Integer -> CUInt #

Integral CLong 

Methods

fromInteger :: Integer -> CLong #

Integral CULong 
Integral CLLong 
Integral CULLong 
Integral CBool 

Methods

fromInteger :: Integer -> CBool #

Integral CFloat 
Integral CDouble 
Integral CPtrdiff 
Integral CSize 

Methods

fromInteger :: Integer -> CSize #

Integral CWchar 
Integral CSigAtomic 
Integral CClock 
Integral CTime 

Methods

fromInteger :: Integer -> CTime #

Integral CUSeconds 
Integral CSUSeconds 
Integral CIntPtr 
Integral CUIntPtr 
Integral CIntMax 
Integral CUIntMax 
Integral IntPtr 
Integral Word256 
Integral Word128 
Integral (Offset ty) 

Methods

fromInteger :: Integer -> Offset ty #

Integral (CountOf ty) 

Methods

fromInteger :: Integer -> CountOf ty #

class Fractional a where #

Fractional Literal support

e.g. 1.2 :: Double 0.03 :: Float

Minimal complete definition

fromRational

Methods

fromRational :: Rational -> a #

class HasNegation a where #

Negation support

e.g. -(f x)

Minimal complete definition

negate

Methods

negate :: a -> a #

class Bifunctor (p :: * -> * -> *) where #

Formally, the class Bifunctor represents a bifunctor from Hask -> Hask.

Intuitively it is a bifunctor where both the first and second arguments are covariant.

You can define a Bifunctor by either defining bimap or by defining both first and second.

If you supply bimap, you should ensure that:

bimap id idid

If you supply first and second, ensure:

first idid
second idid

If you supply both, you should also ensure:

bimap f g ≡ first f . second g

These ensure by parametricity:

bimap  (f . g) (h . i) ≡ bimap f h . bimap g i
first  (f . g) ≡ first  f . first  g
second (f . g) ≡ second f . second g

Since: 4.8.0.0

Minimal complete definition

bimap | first, second

Methods

bimap :: (a -> b) -> (c -> d) -> p a c -> p b d #

Map over both arguments at the same time.

bimap f g ≡ first f . second g

first :: (a -> b) -> p a c -> p b c #

Map covariantly over the first argument.

first f ≡ bimap f id

second :: (b -> c) -> p a b -> p a c #

Map covariantly over the second argument.

secondbimap id

Instances

Bifunctor Either

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d #

first :: (a -> b) -> Either a c -> Either b c #

second :: (b -> c) -> Either a b -> Either a c #

Bifunctor (,)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) #

first :: (a -> b) -> (a, c) -> (b, c) #

second :: (b -> c) -> (a, b) -> (a, c) #

Bifunctor Arg

Since: 4.9.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> Arg a c -> Arg b d #

first :: (a -> b) -> Arg a c -> Arg b c #

second :: (b -> c) -> Arg a b -> Arg a c #

Bifunctor These 

Methods

bimap :: (a -> b) -> (c -> d) -> These a c -> These b d #

first :: (a -> b) -> These a c -> These b c #

second :: (b -> c) -> These a b -> These a c #

Bifunctor Tuple2 # 

Methods

bimap :: (a -> b) -> (c -> d) -> Tuple2 a c -> Tuple2 b d #

first :: (a -> b) -> Tuple2 a c -> Tuple2 b c #

second :: (b -> c) -> Tuple2 a b -> Tuple2 a c #

Bifunctor ((,,) x1)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, a, c) -> (x1, b, d) #

first :: (a -> b) -> (x1, a, c) -> (x1, b, c) #

second :: (b -> c) -> (x1, a, b) -> (x1, a, c) #

Bifunctor (Const *)

Since: 4.8.0.0

Methods

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

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

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

Bifunctor (K1 * i)

Since: 4.9.0.0

Methods

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

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

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

Bifunctor ((,,,) x1 x2)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, a, c) -> (x1, x2, b, d) #

first :: (a -> b) -> (x1, x2, a, c) -> (x1, x2, b, c) #

second :: (b -> c) -> (x1, x2, a, b) -> (x1, x2, a, c) #

Bifunctor ((,,,,) x1 x2 x3)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, d) #

first :: (a -> b) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, c) #

second :: (b -> c) -> (x1, x2, x3, a, b) -> (x1, x2, x3, a, c) #

Bifunctor ((,,,,,) x1 x2 x3 x4)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, d) #

first :: (a -> b) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, c) #

second :: (b -> c) -> (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, a, c) #

Bifunctor ((,,,,,,) x1 x2 x3 x4 x5)

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, d) #

first :: (a -> b) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, c) #

second :: (b -> c) -> (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, a, c) #

class Functor f => Applicative (f :: * -> *) where #

A functor with application, providing operations to

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

A minimal complete definition must include implementations of pure and of either <*> or liftA2. If it defines both, then they must behave the same as their default definitions:

(<*>) = liftA2 id liftA2 f x y = f <$> x <*> y

Further, any definition must satisfy the following:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

It may be useful to note that supposing

forall x y. p (q x y) = f x . g y

it follows from the above that

liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, ((<*>) | liftA2)

Methods

pure :: a -> f a #

Lift a value.

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

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

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

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*>.

(*>) :: f a -> f b -> f b infixl 4 #

Sequence actions, discarding the value of the first argument.

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

Sequence actions, discarding the value of the second argument.

Instances

Applicative []

Since: 2.1

Methods

pure :: a -> [a] #

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

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

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

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

Applicative Maybe

Since: 2.1

Methods

pure :: a -> Maybe a #

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

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

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

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

Applicative IO

Since: 2.1

Methods

pure :: a -> IO a #

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

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

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

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

Applicative Par1

Since: 4.9.0.0

Methods

pure :: a -> Par1 a #

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

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

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

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

Applicative P

Since: 4.5.0.0

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Applicative Min

Since: 4.9.0.0

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

liftA2 :: (a -> b -> c) -> Min a -> Min b -> Min c #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max

Since: 4.9.0.0

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

liftA2 :: (a -> b -> c) -> Max a -> Max b -> Max c #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First

Since: 4.9.0.0

Methods

pure :: a -> First a #

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

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

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

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

Applicative Last

Since: 4.9.0.0

Methods

pure :: a -> Last a #

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

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

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

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

Applicative Option

Since: 4.9.0.0

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

liftA2 :: (a -> b -> c) -> Option a -> Option b -> Option c #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty

Since: 4.9.0.0

Methods

pure :: a -> NonEmpty a #

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

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

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

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

Applicative ZipList
f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN

ZipList (zipWithN f xs1 ... xsN)

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

(\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
    = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
    = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}

Since: 2.1

Methods

pure :: a -> ZipList a #

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

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

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

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

Applicative Identity

Since: 4.8.0.0

Methods

pure :: a -> Identity a #

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

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

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

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

Applicative STM

Since: 4.8.0.0

Methods

pure :: a -> STM a #

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

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

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

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

Applicative Dual

Since: 4.8.0.0

Methods

pure :: a -> Dual a #

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

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

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

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

Applicative Sum

Since: 4.8.0.0

Methods

pure :: a -> Sum a #

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

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

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

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

Applicative Product

Since: 4.8.0.0

Methods

pure :: a -> Product a #

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

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

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

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

Applicative First 

Methods

pure :: a -> First a #

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

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

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

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

Applicative Last 

Methods

pure :: a -> Last a #

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

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

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

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

Applicative ReadP

Since: 4.6.0.0

Methods

pure :: a -> ReadP a #

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

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

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

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

Applicative DList # 

Methods

pure :: a -> DList a #

(<*>) :: DList (a -> b) -> DList a -> DList b #

liftA2 :: (a -> b -> c) -> DList a -> DList b -> DList c #

(*>) :: DList a -> DList b -> DList b #

(<*) :: DList a -> DList b -> DList a #

Applicative Partial # 

Methods

pure :: a -> Partial a #

(<*>) :: Partial (a -> b) -> Partial a -> Partial b #

liftA2 :: (a -> b -> c) -> Partial a -> Partial b -> Partial c #

(*>) :: Partial a -> Partial b -> Partial b #

(<*) :: Partial a -> Partial b -> Partial a #

Applicative Gen # 

Methods

pure :: a -> Gen a #

(<*>) :: Gen (a -> b) -> Gen a -> Gen b #

liftA2 :: (a -> b -> c) -> Gen a -> Gen b -> Gen c #

(*>) :: Gen a -> Gen b -> Gen b #

(<*) :: Gen a -> Gen b -> Gen a #

Applicative Check # 

Methods

pure :: a -> Check a #

(<*>) :: Check (a -> b) -> Check a -> Check b #

liftA2 :: (a -> b -> c) -> Check a -> Check b -> Check c #

(*>) :: Check a -> Check b -> Check b #

(<*) :: Check a -> Check b -> Check a #

Applicative (Either e)

Since: 3.0

Methods

pure :: a -> Either e a #

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

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

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

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

Applicative (U1 *)

Since: 4.9.0.0

Methods

pure :: a -> U1 * a #

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

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

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

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

Monoid a => Applicative ((,) a)

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

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

Since: 2.1

Methods

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

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

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

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

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

Monad m => Applicative (WrappedMonad m)

Since: 2.1

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a)

Since: 4.6.0.0

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

liftA2 :: (a -> b -> c) -> ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a c #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *)

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

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

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

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

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

Applicative (ST s)

Since: 4.4.0.0

Methods

pure :: a -> ST s a #

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

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

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

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

Applicative m => Applicative (ResourceT m) # 

Methods

pure :: a -> ResourceT m a #

(<*>) :: ResourceT m (a -> b) -> ResourceT m a -> ResourceT m b #

liftA2 :: (a -> b -> c) -> ResourceT m a -> ResourceT m b -> ResourceT m c #

(*>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

(<*) :: ResourceT m a -> ResourceT m b -> ResourceT m a #

ParserSource input => Applicative (Parser input) # 

Methods

pure :: a -> Parser input a #

(<*>) :: Parser input (a -> b) -> Parser input a -> Parser input b #

liftA2 :: (a -> b -> c) -> Parser input a -> Parser input b -> Parser input c #

(*>) :: Parser input a -> Parser input b -> Parser input b #

(<*) :: Parser input a -> Parser input b -> Parser input a #

Applicative (MonadRandomState gen) # 

Methods

pure :: a -> MonadRandomState gen a #

(<*>) :: MonadRandomState gen (a -> b) -> MonadRandomState gen a -> MonadRandomState gen b #

liftA2 :: (a -> b -> c) -> MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen c #

(*>) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen b #

(<*) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen a #

Applicative f => Applicative (Rec1 * f)

Since: 4.9.0.0

Methods

pure :: a -> Rec1 * f a #

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

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

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

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

Arrow a => Applicative (WrappedArrow a b)

Since: 2.1

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

liftA2 :: (a -> b -> c) -> WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b c #

(*>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b #

(<*) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b a #

Monoid m => Applicative (Const * m)

Since: 2.0.1

Methods

pure :: a -> Const * m a #

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

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

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

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

Applicative f => Applicative (Alt * f) 

Methods

pure :: a -> Alt * f a #

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

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

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

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

Monad m => Applicative (State s m) 

Methods

pure :: a -> State s m a #

(<*>) :: State s m (a -> b) -> State s m a -> State s m b #

liftA2 :: (a -> b -> c) -> State s m a -> State s m b -> State s m c #

(*>) :: State s m a -> State s m b -> State s m b #

(<*) :: State s m a -> State s m b -> State s m a #

Monad m => Applicative (Reader r m) 

Methods

pure :: a -> Reader r m a #

(<*>) :: Reader r m (a -> b) -> Reader r m a -> Reader r m b #

liftA2 :: (a -> b -> c) -> Reader r m a -> Reader r m b -> Reader r m c #

(*>) :: Reader r m a -> Reader r m b -> Reader r m b #

(<*) :: Reader r m a -> Reader r m b -> Reader r m a #

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

Methods

pure :: a -> StateT s m a #

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

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

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

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

Applicative m => Applicative (ReaderT r m) # 

Methods

pure :: a -> ReaderT r m a #

(<*>) :: ReaderT r m (a -> b) -> ReaderT r m a -> ReaderT r m b #

liftA2 :: (a -> b -> c) -> ReaderT r m a -> ReaderT r m b -> ReaderT r m c #

(*>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

(<*) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m a #

(Functor m, Monad m) => Applicative (ExceptT e m) # 

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Monad m => Applicative (ZipSink i m) # 

Methods

pure :: a -> ZipSink i m a #

(<*>) :: ZipSink i m (a -> b) -> ZipSink i m a -> ZipSink i m b #

liftA2 :: (a -> b -> c) -> ZipSink i m a -> ZipSink i m b -> ZipSink i m c #

(*>) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m b #

(<*) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m a #

Applicative ((->) LiftedRep LiftedRep a)

Since: 2.1

Methods

pure :: a -> (LiftedRep -> LiftedRep) a a #

(<*>) :: (LiftedRep -> LiftedRep) a (a -> b) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b #

liftA2 :: (a -> b -> c) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a c #

(*>) :: (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a b #

(<*) :: (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a a #

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

Since: 4.9.0.0

Methods

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

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

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

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

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

Applicative (Conduit i o m) # 

Methods

pure :: a -> Conduit i o m a #

(<*>) :: Conduit i o m (a -> b) -> Conduit i o m a -> Conduit i o m b #

liftA2 :: (a -> b -> c) -> Conduit i o m a -> Conduit i o m b -> Conduit i o m c #

(*>) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m b #

(<*) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m a #

Applicative f => Applicative (M1 * i c f)

Since: 4.9.0.0

Methods

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

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

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

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

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

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

Since: 4.9.0.0

Methods

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

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

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

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

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

Monad state => Applicative (Builder collection mutCollection step state err) 

Methods

pure :: a -> Builder collection mutCollection step state err a #

(<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b #

liftA2 :: (a -> b -> c) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err c #

(*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b #

(<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a #

class Applicative m => Monad (m :: * -> *) where #

The Monad class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. Haskell's do expressions provide a convenient syntax for writing monadic expressions.

Instances of Monad should satisfy the following laws:

Furthermore, the Monad and Applicative operations should relate as follows:

The above laws imply:

and that pure and (<*>) satisfy the applicative functor laws.

The instances of Monad for lists, Maybe and IO defined in the Prelude satisfy these laws.

Minimal complete definition

(>>=)

Methods

(>>=) :: m a -> (a -> m b) -> m b infixl 1 #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

(>>) :: m a -> m b -> m b infixl 1 #

Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.

return :: a -> m a #

Inject a value into the monadic type.

fail :: String -> m a #

Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression.

As part of the MonadFail proposal (MFP), this function is moved to its own class MonadFail (see Control.Monad.Fail for more details). The definition here will be removed in a future release.

Instances

Monad []

Since: 2.1

Methods

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

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

return :: a -> [a] #

fail :: String -> [a] #

Monad Maybe

Since: 2.1

Methods

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

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

return :: a -> Maybe a #

fail :: String -> Maybe a #

Monad IO

Since: 2.1

Methods

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

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

return :: a -> IO a #

fail :: String -> IO a #

Monad Par1

Since: 4.9.0.0

Methods

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

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

return :: a -> Par1 a #

fail :: String -> Par1 a #

Monad P

Since: 2.1

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

fail :: String -> P a #

Monad Min

Since: 4.9.0.0

Methods

(>>=) :: Min a -> (a -> Min b) -> Min b #

(>>) :: Min a -> Min b -> Min b #

return :: a -> Min a #

fail :: String -> Min a #

Monad Max

Since: 4.9.0.0

Methods

(>>=) :: Max a -> (a -> Max b) -> Max b #

(>>) :: Max a -> Max b -> Max b #

return :: a -> Max a #

fail :: String -> Max a #

Monad First

Since: 4.9.0.0

Methods

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

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

return :: a -> First a #

fail :: String -> First a #

Monad Last

Since: 4.9.0.0

Methods

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

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

return :: a -> Last a #

fail :: String -> Last a #

Monad Option

Since: 4.9.0.0

Methods

(>>=) :: Option a -> (a -> Option b) -> Option b #

(>>) :: Option a -> Option b -> Option b #

return :: a -> Option a #

fail :: String -> Option a #

Monad NonEmpty

Since: 4.9.0.0

Methods

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

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

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Monad Identity

Since: 4.8.0.0

Methods

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

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

return :: a -> Identity a #

fail :: String -> Identity a #

Monad STM

Since: 4.3.0.0

Methods

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

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

return :: a -> STM a #

fail :: String -> STM a #

Monad Dual

Since: 4.8.0.0

Methods

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

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

return :: a -> Dual a #

fail :: String -> Dual a #

Monad Sum

Since: 4.8.0.0

Methods

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

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

return :: a -> Sum a #

fail :: String -> Sum a #

Monad Product

Since: 4.8.0.0

Methods

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

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

return :: a -> Product a #

fail :: String -> Product a #

Monad First 

Methods

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

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

return :: a -> First a #

fail :: String -> First a #

Monad Last 

Methods

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

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

return :: a -> Last a #

fail :: String -> Last a #

Monad ReadP

Since: 2.1

Methods

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

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

return :: a -> ReadP a #

fail :: String -> ReadP a #

Monad DList # 

Methods

(>>=) :: DList a -> (a -> DList b) -> DList b #

(>>) :: DList a -> DList b -> DList b #

return :: a -> DList a #

fail :: String -> DList a #

Monad Partial # 

Methods

(>>=) :: Partial a -> (a -> Partial b) -> Partial b #

(>>) :: Partial a -> Partial b -> Partial b #

return :: a -> Partial a #

fail :: String -> Partial a #

Monad Gen # 

Methods

(>>=) :: Gen a -> (a -> Gen b) -> Gen b #

(>>) :: Gen a -> Gen b -> Gen b #

return :: a -> Gen a #

fail :: String -> Gen a #

Monad Check # 

Methods

(>>=) :: Check a -> (a -> Check b) -> Check b #

(>>) :: Check a -> Check b -> Check b #

return :: a -> Check a #

fail :: String -> Check a #

Monad (Either e)

Since: 4.4.0.0

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b #

(>>) :: Either e a -> Either e b -> Either e b #

return :: a -> Either e a #

fail :: String -> Either e a #

Monad (U1 *)

Since: 4.9.0.0

Methods

(>>=) :: U1 * a -> (a -> U1 * b) -> U1 * b #

(>>) :: U1 * a -> U1 * b -> U1 * b #

return :: a -> U1 * a #

fail :: String -> U1 * a #

Monoid a => Monad ((,) a)

Since: 4.9.0.0

Methods

(>>=) :: (a, a) -> (a -> (a, b)) -> (a, b) #

(>>) :: (a, a) -> (a, b) -> (a, b) #

return :: a -> (a, a) #

fail :: String -> (a, a) #

Monad m => Monad (WrappedMonad m) 

Methods

(>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b #

(>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

return :: a -> WrappedMonad m a #

fail :: String -> WrappedMonad m a #

ArrowApply a => Monad (ArrowMonad a)

Since: 2.1

Methods

(>>=) :: ArrowMonad a a -> (a -> ArrowMonad a b) -> ArrowMonad a b #

(>>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

return :: a -> ArrowMonad a a #

fail :: String -> ArrowMonad a a #

Monad (Proxy *)

Since: 4.7.0.0

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Monad (ST s)

Since: 2.1

Methods

(>>=) :: ST s a -> (a -> ST s b) -> ST s b #

(>>) :: ST s a -> ST s b -> ST s b #

return :: a -> ST s a #

fail :: String -> ST s a #

Monad m => Monad (ResourceT m) # 

Methods

(>>=) :: ResourceT m a -> (a -> ResourceT m b) -> ResourceT m b #

(>>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

return :: a -> ResourceT m a #

fail :: String -> ResourceT m a #

ParserSource input => Monad (Parser input) # 

Methods

(>>=) :: Parser input a -> (a -> Parser input b) -> Parser input b #

(>>) :: Parser input a -> Parser input b -> Parser input b #

return :: a -> Parser input a #

fail :: String -> Parser input a #

Monad (MonadRandomState gen) # 

Methods

(>>=) :: MonadRandomState gen a -> (a -> MonadRandomState gen b) -> MonadRandomState gen b #

(>>) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen b #

return :: a -> MonadRandomState gen a #

fail :: String -> MonadRandomState gen a #

Monad f => Monad (Rec1 * f)

Since: 4.9.0.0

Methods

(>>=) :: Rec1 * f a -> (a -> Rec1 * f b) -> Rec1 * f b #

(>>) :: Rec1 * f a -> Rec1 * f b -> Rec1 * f b #

return :: a -> Rec1 * f a #

fail :: String -> Rec1 * f a #

Monad f => Monad (Alt * f) 

Methods

(>>=) :: Alt * f a -> (a -> Alt * f b) -> Alt * f b #

(>>) :: Alt * f a -> Alt * f b -> Alt * f b #

return :: a -> Alt * f a #

fail :: String -> Alt * f a #

Monad m => Monad (State r m) 

Methods

(>>=) :: State r m a -> (a -> State r m b) -> State r m b #

(>>) :: State r m a -> State r m b -> State r m b #

return :: a -> State r m a #

fail :: String -> State r m a #

Monad m => Monad (Reader r m) 

Methods

(>>=) :: Reader r m a -> (a -> Reader r m b) -> Reader r m b #

(>>) :: Reader r m a -> Reader r m b -> Reader r m b #

return :: a -> Reader r m a #

fail :: String -> Reader r m a #

(Functor m, Monad m) => Monad (StateT s m) # 

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b #

return :: a -> StateT s m a #

fail :: String -> StateT s m a #

Monad m => Monad (ReaderT r m) # 

Methods

(>>=) :: ReaderT r m a -> (a -> ReaderT r m b) -> ReaderT r m b #

(>>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

return :: a -> ReaderT r m a #

fail :: String -> ReaderT r m a #

Monad m => Monad (ExceptT e m) # 

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

return :: a -> ExceptT e m a #

fail :: String -> ExceptT e m a #

Monad ((->) LiftedRep LiftedRep r)

Since: 2.1

Methods

(>>=) :: (LiftedRep -> LiftedRep) r a -> (a -> (LiftedRep -> LiftedRep) r b) -> (LiftedRep -> LiftedRep) r b #

(>>) :: (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b -> (LiftedRep -> LiftedRep) r b #

return :: a -> (LiftedRep -> LiftedRep) r a #

fail :: String -> (LiftedRep -> LiftedRep) r a #

(Monad f, Monad g) => Monad ((:*:) * f g)

Since: 4.9.0.0

Methods

(>>=) :: (* :*: f) g a -> (a -> (* :*: f) g b) -> (* :*: f) g b #

(>>) :: (* :*: f) g a -> (* :*: f) g b -> (* :*: f) g b #

return :: a -> (* :*: f) g a #

fail :: String -> (* :*: f) g a #

Monad (Conduit i o m) # 

Methods

(>>=) :: Conduit i o m a -> (a -> Conduit i o m b) -> Conduit i o m b #

(>>) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m b #

return :: a -> Conduit i o m a #

fail :: String -> Conduit i o m a #

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 #

(>>) :: M1 * i c f a -> M1 * i c f b -> M1 * i c f b #

return :: a -> M1 * i c f a #

fail :: String -> M1 * i c f a #

Monad state => Monad (Builder collection mutCollection step state err) 

Methods

(>>=) :: Builder collection mutCollection step state err a -> (a -> Builder collection mutCollection step state err b) -> Builder collection mutCollection step state err b #

(>>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b #

return :: a -> Builder collection mutCollection step state err a #

fail :: String -> Builder collection mutCollection step state err a #

(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #

Same as >>=, but with the arguments interchanged.

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a #

Instances

IsString String 

Methods

fromString :: String -> String #

IsString AsciiString 
IsString Builder # 

Methods

fromString :: String -> Builder #

IsString IPv6 # 

Methods

fromString :: String -> IPv6 #

IsString IPv4 # 

Methods

fromString :: String -> IPv4 #

IsString FileName # 
IsString FilePath # 
(~) * a Char => IsString [a]

(a ~ Char) context was introduced in 4.9.0.0

Since: 2.1

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

IsString a => IsString (Const * a b)

Since: 4.9.0.0

Methods

fromString :: String -> Const * a b #

class IsList l where #

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 :: * #

The Item type function returns the type of items of the structure l.

Methods

fromList :: [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [Item l] -> l #

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] #

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

Associated Types

type Item CallStack :: * #

IsList Version

Since: 4.8.0.0

Associated Types

type Item Version :: * #

IsList String 

Associated Types

type Item String :: * #

IsList AsciiString 
IsList Bitmap # 

Associated Types

type Item Bitmap :: * #

IsList [a]

Since: 4.7.0.0

Associated Types

type Item [a] :: * #

Methods

fromList :: [Item [a]] -> [a] #

fromListN :: Int -> [Item [a]] -> [a] #

toList :: [a] -> [Item [a]] #

IsList (NonEmpty a)

Since: 4.9.0.0

Associated Types

type Item (NonEmpty a) :: * #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

IsList (Array ty) 

Associated Types

type Item (Array ty) :: * #

Methods

fromList :: [Item (Array ty)] -> Array ty #

fromListN :: Int -> [Item (Array ty)] -> Array ty #

toList :: Array ty -> [Item (Array ty)] #

PrimType ty => IsList (UArray ty) 

Associated Types

type Item (UArray ty) :: * #

Methods

fromList :: [Item (UArray ty)] -> UArray ty #

fromListN :: Int -> [Item (UArray ty)] -> UArray ty #

toList :: UArray ty -> [Item (UArray ty)] #

PrimType ty => IsList (Block ty) 

Associated Types

type Item (Block ty) :: * #

Methods

fromList :: [Item (Block ty)] -> Block ty #

fromListN :: Int -> [Item (Block ty)] -> Block ty #

toList :: Block ty -> [Item (Block ty)] #

IsList c => IsList (NonEmpty c) 

Associated Types

type Item (NonEmpty c) :: * #

Methods

fromList :: [Item (NonEmpty c)] -> NonEmpty c #

fromListN :: Int -> [Item (NonEmpty c)] -> NonEmpty c #

toList :: NonEmpty c -> [Item (NonEmpty c)] #

IsList (DList a) # 

Associated Types

type Item (DList a) :: * #

Methods

fromList :: [Item (DList a)] -> DList a #

fromListN :: Int -> [Item (DList a)] -> DList a #

toList :: DList a -> [Item (DList a)] #

PrimType ty => IsList (ChunkedUArray ty) # 

Associated Types

type Item (ChunkedUArray ty) :: * #

Numeric type classes

class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a where #

Number literals, convertible through the generic Integer type.

all number are Enum'erable, meaning that you can move to next element

Minimal complete definition

toInteger

Methods

toInteger :: a -> Integer #

Instances

IsIntegral Int 

Methods

toInteger :: Int -> Integer #

IsIntegral Int8 

Methods

toInteger :: Int8 -> Integer #

IsIntegral Int16 

Methods

toInteger :: Int16 -> Integer #

IsIntegral Int32 

Methods

toInteger :: Int32 -> Integer #

IsIntegral Int64 

Methods

toInteger :: Int64 -> Integer #

IsIntegral Integer 

Methods

toInteger :: Integer -> Integer #

IsIntegral Natural 

Methods

toInteger :: Natural -> Integer #

IsIntegral Word 

Methods

toInteger :: Word -> Integer #

IsIntegral Word8 

Methods

toInteger :: Word8 -> Integer #

IsIntegral Word16 

Methods

toInteger :: Word16 -> Integer #

IsIntegral Word32 

Methods

toInteger :: Word32 -> Integer #

IsIntegral Word64 

Methods

toInteger :: Word64 -> Integer #

IsIntegral CChar 

Methods

toInteger :: CChar -> Integer #

IsIntegral CSChar 

Methods

toInteger :: CSChar -> Integer #

IsIntegral CUChar 

Methods

toInteger :: CUChar -> Integer #

IsIntegral CShort 

Methods

toInteger :: CShort -> Integer #

IsIntegral CUShort 

Methods

toInteger :: CUShort -> Integer #

IsIntegral CInt 

Methods

toInteger :: CInt -> Integer #

IsIntegral CUInt 

Methods

toInteger :: CUInt -> Integer #

IsIntegral CLong 

Methods

toInteger :: CLong -> Integer #

IsIntegral CULong 

Methods

toInteger :: CULong -> Integer #

IsIntegral CLLong 

Methods

toInteger :: CLLong -> Integer #

IsIntegral CULLong 

Methods

toInteger :: CULLong -> Integer #

IsIntegral CBool 

Methods

toInteger :: CBool -> Integer #

IsIntegral CPtrdiff 
IsIntegral CSize 

Methods

toInteger :: CSize -> Integer #

IsIntegral CWchar 

Methods

toInteger :: CWchar -> Integer #

IsIntegral CSigAtomic 
IsIntegral CIntPtr 

Methods

toInteger :: CIntPtr -> Integer #

IsIntegral CUIntPtr 
IsIntegral CIntMax 

Methods

toInteger :: CIntMax -> Integer #

IsIntegral CUIntMax 
IsIntegral Word256 

Methods

toInteger :: Word256 -> Integer #

IsIntegral Word128 

Methods

toInteger :: Word128 -> Integer #

IsIntegral (Offset ty) 

Methods

toInteger :: Offset ty -> Integer #

IsIntegral (CountOf ty) 

Methods

toInteger :: CountOf ty -> Integer #

class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a where #

Non Negative Number literals, convertible through the generic Natural type

Minimal complete definition

toNatural

Methods

toNatural :: a -> Natural #

class Signed a where Source #

types that have sign and can be made absolute

Minimal complete definition

abs, signum

Methods

abs :: a -> a Source #

signum :: a -> Sign Source #

class Additive a where #

Represent class of things that can be added together, contains a neutral element and is commutative.

x + azero = x
azero + x = x
x + y = y + x

Minimal complete definition

azero, (+)

Methods

azero :: a #

(+) :: a -> a -> a infixl 6 #

scale :: IsNatural n => n -> a -> a #

Instances

Additive Double 

Methods

azero :: Double #

(+) :: Double -> Double -> Double #

scale :: IsNatural n => n -> Double -> Double #

Additive Float 

Methods

azero :: Float #

(+) :: Float -> Float -> Float #

scale :: IsNatural n => n -> Float -> Float #

Additive Int 

Methods

azero :: Int #

(+) :: Int -> Int -> Int #

scale :: IsNatural n => n -> Int -> Int #

Additive Int8 

Methods

azero :: Int8 #

(+) :: Int8 -> Int8 -> Int8 #

scale :: IsNatural n => n -> Int8 -> Int8 #

Additive Int16 

Methods

azero :: Int16 #

(+) :: Int16 -> Int16 -> Int16 #

scale :: IsNatural n => n -> Int16 -> Int16 #

Additive Int32 

Methods

azero :: Int32 #

(+) :: Int32 -> Int32 -> Int32 #

scale :: IsNatural n => n -> Int32 -> Int32 #

Additive Int64 

Methods

azero :: Int64 #

(+) :: Int64 -> Int64 -> Int64 #

scale :: IsNatural n => n -> Int64 -> Int64 #

Additive Integer 

Methods

azero :: Integer #

(+) :: Integer -> Integer -> Integer #

scale :: IsNatural n => n -> Integer -> Integer #

Additive Natural 

Methods

azero :: Natural #

(+) :: Natural -> Natural -> Natural #

scale :: IsNatural n => n -> Natural -> Natural #

Additive Word 

Methods

azero :: Word #

(+) :: Word -> Word -> Word #

scale :: IsNatural n => n -> Word -> Word #

Additive Word8 

Methods

azero :: Word8 #

(+) :: Word8 -> Word8 -> Word8 #

scale :: IsNatural n => n -> Word8 -> Word8 #

Additive Word16 

Methods

azero :: Word16 #

(+) :: Word16 -> Word16 -> Word16 #

scale :: IsNatural n => n -> Word16 -> Word16 #

Additive Word32 

Methods

azero :: Word32 #

(+) :: Word32 -> Word32 -> Word32 #

scale :: IsNatural n => n -> Word32 -> Word32 #

Additive Word64 

Methods

azero :: Word64 #

(+) :: Word64 -> Word64 -> Word64 #

scale :: IsNatural n => n -> Word64 -> Word64 #

Additive COff 

Methods

azero :: COff #

(+) :: COff -> COff -> COff #

scale :: IsNatural n => n -> COff -> COff #

Additive CChar 

Methods

azero :: CChar #

(+) :: CChar -> CChar -> CChar #

scale :: IsNatural n => n -> CChar -> CChar #

Additive CSChar 

Methods

azero :: CSChar #

(+) :: CSChar -> CSChar -> CSChar #

scale :: IsNatural n => n -> CSChar -> CSChar #

Additive CUChar 

Methods

azero :: CUChar #

(+) :: CUChar -> CUChar -> CUChar #

scale :: IsNatural n => n -> CUChar -> CUChar #

Additive CShort 

Methods

azero :: CShort #

(+) :: CShort -> CShort -> CShort #

scale :: IsNatural n => n -> CShort -> CShort #

Additive CUShort 

Methods

azero :: CUShort #

(+) :: CUShort -> CUShort -> CUShort #

scale :: IsNatural n => n -> CUShort -> CUShort #

Additive CInt 

Methods

azero :: CInt #

(+) :: CInt -> CInt -> CInt #

scale :: IsNatural n => n -> CInt -> CInt #

Additive CUInt 

Methods

azero :: CUInt #

(+) :: CUInt -> CUInt -> CUInt #

scale :: IsNatural n => n -> CUInt -> CUInt #

Additive CLong 

Methods

azero :: CLong #

(+) :: CLong -> CLong -> CLong #

scale :: IsNatural n => n -> CLong -> CLong #

Additive CULong 

Methods

azero :: CULong #

(+) :: CULong -> CULong -> CULong #

scale :: IsNatural n => n -> CULong -> CULong #

Additive CLLong 

Methods

azero :: CLLong #

(+) :: CLLong -> CLLong -> CLLong #

scale :: IsNatural n => n -> CLLong -> CLLong #

Additive CULLong 

Methods

azero :: CULLong #

(+) :: CULLong -> CULLong -> CULLong #

scale :: IsNatural n => n -> CULLong -> CULLong #

Additive CFloat 

Methods

azero :: CFloat #

(+) :: CFloat -> CFloat -> CFloat #

scale :: IsNatural n => n -> CFloat -> CFloat #

Additive CDouble 

Methods

azero :: CDouble #

(+) :: CDouble -> CDouble -> CDouble #

scale :: IsNatural n => n -> CDouble -> CDouble #

Additive CPtrdiff 
Additive CSize 

Methods

azero :: CSize #

(+) :: CSize -> CSize -> CSize #

scale :: IsNatural n => n -> CSize -> CSize #

Additive CWchar 

Methods

azero :: CWchar #

(+) :: CWchar -> CWchar -> CWchar #

scale :: IsNatural n => n -> CWchar -> CWchar #

Additive CSigAtomic 
Additive CClock 

Methods

azero :: CClock #

(+) :: CClock -> CClock -> CClock #

scale :: IsNatural n => n -> CClock -> CClock #

Additive CTime 

Methods

azero :: CTime #

(+) :: CTime -> CTime -> CTime #

scale :: IsNatural n => n -> CTime -> CTime #

Additive CUSeconds 
Additive CSUSeconds 
Additive CIntPtr 

Methods

azero :: CIntPtr #

(+) :: CIntPtr -> CIntPtr -> CIntPtr #

scale :: IsNatural n => n -> CIntPtr -> CIntPtr #

Additive CUIntPtr 
Additive CIntMax 

Methods

azero :: CIntMax #

(+) :: CIntMax -> CIntMax -> CIntMax #

scale :: IsNatural n => n -> CIntMax -> CIntMax #

Additive CUIntMax 
Additive Word256 

Methods

azero :: Word256 #

(+) :: Word256 -> Word256 -> Word256 #

scale :: IsNatural n => n -> Word256 -> Word256 #

Additive Word128 

Methods

azero :: Word128 #

(+) :: Word128 -> Word128 -> Word128 #

scale :: IsNatural n => n -> Word128 -> Word128 #

Additive Seconds # 

Methods

azero :: Seconds #

(+) :: Seconds -> Seconds -> Seconds #

scale :: IsNatural n => n -> Seconds -> Seconds #

Additive NanoSeconds # 
Additive (Offset ty) 

Methods

azero :: Offset ty #

(+) :: Offset ty -> Offset ty -> Offset ty #

scale :: IsNatural n => n -> Offset ty -> Offset ty #

Additive (CountOf ty) 

Methods

azero :: CountOf ty #

(+) :: CountOf ty -> CountOf ty -> CountOf ty #

scale :: IsNatural n => n -> CountOf ty -> CountOf ty #

(KnownNat n, NatWithinBound Word64 n) => Additive (Zn64 n) 

Methods

azero :: Zn64 n #

(+) :: Zn64 n -> Zn64 n -> Zn64 n #

scale :: IsNatural n => n -> Zn64 n -> Zn64 n #

KnownNat n => Additive (Zn n) 

Methods

azero :: Zn n #

(+) :: Zn n -> Zn n -> Zn n #

scale :: IsNatural n => n -> Zn n -> Zn n #

class Subtractive a where #

Represent class of things that can be subtracted.

Note that the result is not necessary of the same type as the operand depending on the actual type.

For example:

(-) :: Int -> Int -> Int
(-) :: DateTime -> DateTime -> Seconds
(-) :: Ptr a -> Ptr a -> PtrDiff
(-) :: Natural -> Natural -> Maybe Natural

Minimal complete definition

(-)

Associated Types

type Difference a :: * #

Methods

(-) :: a -> a -> Difference a infixl 6 #

Instances

Subtractive Char 

Associated Types

type Difference Char :: * #

Methods

(-) :: Char -> Char -> Difference Char #

Subtractive Double 

Associated Types

type Difference Double :: * #

Subtractive Float 

Associated Types

type Difference Float :: * #

Methods

(-) :: Float -> Float -> Difference Float #

Subtractive Int 

Associated Types

type Difference Int :: * #

Methods

(-) :: Int -> Int -> Difference Int #

Subtractive Int8 

Associated Types

type Difference Int8 :: * #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

Subtractive Int16 

Associated Types

type Difference Int16 :: * #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

Subtractive Int32 

Associated Types

type Difference Int32 :: * #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

Subtractive Int64 

Associated Types

type Difference Int64 :: * #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

Subtractive Integer 

Associated Types

type Difference Integer :: * #

Subtractive Natural 

Associated Types

type Difference Natural :: * #

Subtractive Word 

Associated Types

type Difference Word :: * #

Methods

(-) :: Word -> Word -> Difference Word #

Subtractive Word8 

Associated Types

type Difference Word8 :: * #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

Subtractive Word16 

Associated Types

type Difference Word16 :: * #

Subtractive Word32 

Associated Types

type Difference Word32 :: * #

Subtractive Word64 

Associated Types

type Difference Word64 :: * #

Subtractive COff 

Associated Types

type Difference COff :: * #

Methods

(-) :: COff -> COff -> Difference COff #

Subtractive CChar 

Associated Types

type Difference CChar :: * #

Methods

(-) :: CChar -> CChar -> Difference CChar #

Subtractive CSChar 

Associated Types

type Difference CSChar :: * #

Subtractive CUChar 

Associated Types

type Difference CUChar :: * #

Subtractive CShort 

Associated Types

type Difference CShort :: * #

Subtractive CUShort 

Associated Types

type Difference CUShort :: * #

Subtractive CInt 

Associated Types

type Difference CInt :: * #

Methods

(-) :: CInt -> CInt -> Difference CInt #

Subtractive CUInt 

Associated Types

type Difference CUInt :: * #

Methods

(-) :: CUInt -> CUInt -> Difference CUInt #

Subtractive CLong 

Associated Types

type Difference CLong :: * #

Methods

(-) :: CLong -> CLong -> Difference CLong #

Subtractive CULong 

Associated Types

type Difference CULong :: * #

Subtractive CLLong 

Associated Types

type Difference CLLong :: * #

Subtractive CULLong 

Associated Types

type Difference CULLong :: * #

Subtractive CBool 

Associated Types

type Difference CBool :: * #

Methods

(-) :: CBool -> CBool -> Difference CBool #

Subtractive CFloat 

Associated Types

type Difference CFloat :: * #

Subtractive CDouble 

Associated Types

type Difference CDouble :: * #

Subtractive CPtrdiff 

Associated Types

type Difference CPtrdiff :: * #

Subtractive CSize 

Associated Types

type Difference CSize :: * #

Methods

(-) :: CSize -> CSize -> Difference CSize #

Subtractive CWchar 

Associated Types

type Difference CWchar :: * #

Subtractive CSigAtomic 

Associated Types

type Difference CSigAtomic :: * #

Subtractive CClock 

Associated Types

type Difference CClock :: * #

Subtractive CTime 

Associated Types

type Difference CTime :: * #

Methods

(-) :: CTime -> CTime -> Difference CTime #

Subtractive CUSeconds 

Associated Types

type Difference CUSeconds :: * #

Subtractive CSUSeconds 

Associated Types

type Difference CSUSeconds :: * #

Subtractive CIntPtr 

Associated Types

type Difference CIntPtr :: * #

Subtractive CUIntPtr 

Associated Types

type Difference CUIntPtr :: * #

Subtractive CIntMax 

Associated Types

type Difference CIntMax :: * #

Subtractive CUIntMax 

Associated Types

type Difference CUIntMax :: * #

Subtractive Word256 

Associated Types

type Difference Word256 :: * #

Subtractive Word128 

Associated Types

type Difference Word128 :: * #

Subtractive (Offset ty) 

Associated Types

type Difference (Offset ty) :: * #

Methods

(-) :: Offset ty -> Offset ty -> Difference (Offset ty) #

Subtractive (CountOf ty) 

Associated Types

type Difference (CountOf ty) :: * #

Methods

(-) :: CountOf ty -> CountOf ty -> Difference (CountOf ty) #

(KnownNat n, NatWithinBound Word64 n) => Subtractive (Zn64 n) 

Associated Types

type Difference (Zn64 n) :: * #

Methods

(-) :: Zn64 n -> Zn64 n -> Difference (Zn64 n) #

KnownNat n => Subtractive (Zn n) 

Associated Types

type Difference (Zn n) :: * #

Methods

(-) :: Zn n -> Zn n -> Difference (Zn n) #

class Multiplicative a where #

Represent class of things that can be multiplied together

x * midentity = x
midentity * x = x

Minimal complete definition

midentity, (*)

Methods

midentity :: a #

Identity element over multiplication

(*) :: a -> a -> a infixl 7 #

Multiplication of 2 elements that result in another element

(^) :: (IsNatural n, IDivisible n) => a -> n -> a infixr 8 #

Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (IsNatural n) => a -> n -> a

Instances

Multiplicative Double 

Methods

midentity :: Double #

(*) :: Double -> Double -> Double #

(^) :: (IsNatural n, IDivisible n) => Double -> n -> Double #

Multiplicative Float 

Methods

midentity :: Float #

(*) :: Float -> Float -> Float #

(^) :: (IsNatural n, IDivisible n) => Float -> n -> Float #

Multiplicative Int 

Methods

midentity :: Int #

(*) :: Int -> Int -> Int #

(^) :: (IsNatural n, IDivisible n) => Int -> n -> Int #

Multiplicative Int8 

Methods

midentity :: Int8 #

(*) :: Int8 -> Int8 -> Int8 #

(^) :: (IsNatural n, IDivisible n) => Int8 -> n -> Int8 #

Multiplicative Int16 

Methods

midentity :: Int16 #

(*) :: Int16 -> Int16 -> Int16 #

(^) :: (IsNatural n, IDivisible n) => Int16 -> n -> Int16 #

Multiplicative Int32 

Methods

midentity :: Int32 #

(*) :: Int32 -> Int32 -> Int32 #

(^) :: (IsNatural n, IDivisible n) => Int32 -> n -> Int32 #

Multiplicative Int64 

Methods

midentity :: Int64 #

(*) :: Int64 -> Int64 -> Int64 #

(^) :: (IsNatural n, IDivisible n) => Int64 -> n -> Int64 #

Multiplicative Integer 
Multiplicative Natural 
Multiplicative Rational 
Multiplicative Word 

Methods

midentity :: Word #

(*) :: Word -> Word -> Word #

(^) :: (IsNatural n, IDivisible n) => Word -> n -> Word #

Multiplicative Word8 

Methods

midentity :: Word8 #

(*) :: Word8 -> Word8 -> Word8 #

(^) :: (IsNatural n, IDivisible n) => Word8 -> n -> Word8 #

Multiplicative Word16 

Methods

midentity :: Word16 #

(*) :: Word16 -> Word16 -> Word16 #

(^) :: (IsNatural n, IDivisible n) => Word16 -> n -> Word16 #

Multiplicative Word32 

Methods

midentity :: Word32 #

(*) :: Word32 -> Word32 -> Word32 #

(^) :: (IsNatural n, IDivisible n) => Word32 -> n -> Word32 #

Multiplicative Word64 

Methods

midentity :: Word64 #

(*) :: Word64 -> Word64 -> Word64 #

(^) :: (IsNatural n, IDivisible n) => Word64 -> n -> Word64 #

Multiplicative COff 

Methods

midentity :: COff #

(*) :: COff -> COff -> COff #

(^) :: (IsNatural n, IDivisible n) => COff -> n -> COff #

Multiplicative CChar 

Methods

midentity :: CChar #

(*) :: CChar -> CChar -> CChar #

(^) :: (IsNatural n, IDivisible n) => CChar -> n -> CChar #

Multiplicative CSChar 

Methods

midentity :: CSChar #

(*) :: CSChar -> CSChar -> CSChar #

(^) :: (IsNatural n, IDivisible n) => CSChar -> n -> CSChar #

Multiplicative CUChar 

Methods

midentity :: CUChar #

(*) :: CUChar -> CUChar -> CUChar #

(^) :: (IsNatural n, IDivisible n) => CUChar -> n -> CUChar #

Multiplicative CShort 

Methods

midentity :: CShort #

(*) :: CShort -> CShort -> CShort #

(^) :: (IsNatural n, IDivisible n) => CShort -> n -> CShort #

Multiplicative CUShort 
Multiplicative CInt 

Methods

midentity :: CInt #

(*) :: CInt -> CInt -> CInt #

(^) :: (IsNatural n, IDivisible n) => CInt -> n -> CInt #

Multiplicative CUInt 

Methods

midentity :: CUInt #

(*) :: CUInt -> CUInt -> CUInt #

(^) :: (IsNatural n, IDivisible n) => CUInt -> n -> CUInt #

Multiplicative CLong 

Methods

midentity :: CLong #

(*) :: CLong -> CLong -> CLong #

(^) :: (IsNatural n, IDivisible n) => CLong -> n -> CLong #

Multiplicative CULong 

Methods

midentity :: CULong #

(*) :: CULong -> CULong -> CULong #

(^) :: (IsNatural n, IDivisible n) => CULong -> n -> CULong #

Multiplicative CLLong 

Methods

midentity :: CLLong #

(*) :: CLLong -> CLLong -> CLLong #

(^) :: (IsNatural n, IDivisible n) => CLLong -> n -> CLLong #

Multiplicative CULLong 
Multiplicative CFloat 

Methods

midentity :: CFloat #

(*) :: CFloat -> CFloat -> CFloat #

(^) :: (IsNatural n, IDivisible n) => CFloat -> n -> CFloat #

Multiplicative CDouble 
Multiplicative CPtrdiff 
Multiplicative CSize 

Methods

midentity :: CSize #

(*) :: CSize -> CSize -> CSize #

(^) :: (IsNatural n, IDivisible n) => CSize -> n -> CSize #

Multiplicative CWchar 

Methods

midentity :: CWchar #

(*) :: CWchar -> CWchar -> CWchar #

(^) :: (IsNatural n, IDivisible n) => CWchar -> n -> CWchar #

Multiplicative CSigAtomic 
Multiplicative CClock 

Methods

midentity :: CClock #

(*) :: CClock -> CClock -> CClock #

(^) :: (IsNatural n, IDivisible n) => CClock -> n -> CClock #

Multiplicative CTime 

Methods

midentity :: CTime #

(*) :: CTime -> CTime -> CTime #

(^) :: (IsNatural n, IDivisible n) => CTime -> n -> CTime #

Multiplicative CUSeconds 
Multiplicative CSUSeconds 
Multiplicative CIntPtr 
Multiplicative CUIntPtr 
Multiplicative CIntMax 
Multiplicative CUIntMax 
Multiplicative Word256 
Multiplicative Word128 

class (Additive a, Multiplicative a) => IDivisible a where #

Represent types that supports an euclidian division

(x ‘div‘ y) * y + (x ‘mod‘ y) == x

Minimal complete definition

div, mod | divMod

Methods

div :: a -> a -> a #

mod :: a -> a -> a #

divMod :: a -> a -> (a, a) #

Instances

IDivisible Int 

Methods

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

divMod :: Int -> Int -> (Int, Int) #

IDivisible Int8 

Methods

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

IDivisible Int16 

Methods

div :: Int16 -> Int16 -> Int16 #

mod :: Int16 -> Int16 -> Int16 #

divMod :: Int16 -> Int16 -> (Int16, Int16) #

IDivisible Int32 

Methods

div :: Int32 -> Int32 -> Int32 #

mod :: Int32 -> Int32 -> Int32 #

divMod :: Int32 -> Int32 -> (Int32, Int32) #

IDivisible Int64 

Methods

div :: Int64 -> Int64 -> Int64 #

mod :: Int64 -> Int64 -> Int64 #

divMod :: Int64 -> Int64 -> (Int64, Int64) #

IDivisible Integer 
IDivisible Natural 
IDivisible Word 

Methods

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

divMod :: Word -> Word -> (Word, Word) #

IDivisible Word8 

Methods

div :: Word8 -> Word8 -> Word8 #

mod :: Word8 -> Word8 -> Word8 #

divMod :: Word8 -> Word8 -> (Word8, Word8) #

IDivisible Word16 

Methods

div :: Word16 -> Word16 -> Word16 #

mod :: Word16 -> Word16 -> Word16 #

divMod :: Word16 -> Word16 -> (Word16, Word16) #

IDivisible Word32 

Methods

div :: Word32 -> Word32 -> Word32 #

mod :: Word32 -> Word32 -> Word32 #

divMod :: Word32 -> Word32 -> (Word32, Word32) #

IDivisible Word64 

Methods

div :: Word64 -> Word64 -> Word64 #

mod :: Word64 -> Word64 -> Word64 #

divMod :: Word64 -> Word64 -> (Word64, Word64) #

IDivisible CChar 

Methods

div :: CChar -> CChar -> CChar #

mod :: CChar -> CChar -> CChar #

divMod :: CChar -> CChar -> (CChar, CChar) #

IDivisible CSChar 

Methods

div :: CSChar -> CSChar -> CSChar #

mod :: CSChar -> CSChar -> CSChar #

divMod :: CSChar -> CSChar -> (CSChar, CSChar) #

IDivisible CUChar 

Methods

div :: CUChar -> CUChar -> CUChar #

mod :: CUChar -> CUChar -> CUChar #

divMod :: CUChar -> CUChar -> (CUChar, CUChar) #

IDivisible CShort 

Methods

div :: CShort -> CShort -> CShort #

mod :: CShort -> CShort -> CShort #

divMod :: CShort -> CShort -> (CShort, CShort) #

IDivisible CUShort 
IDivisible CInt 

Methods

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

divMod :: CInt -> CInt -> (CInt, CInt) #

IDivisible CUInt 

Methods

div :: CUInt -> CUInt -> CUInt #

mod :: CUInt -> CUInt -> CUInt #

divMod :: CUInt -> CUInt -> (CUInt, CUInt) #

IDivisible CLong 

Methods

div :: CLong -> CLong -> CLong #

mod :: CLong -> CLong -> CLong #

divMod :: CLong -> CLong -> (CLong, CLong) #

IDivisible CULong 

Methods

div :: CULong -> CULong -> CULong #

mod :: CULong -> CULong -> CULong #

divMod :: CULong -> CULong -> (CULong, CULong) #

IDivisible CLLong 

Methods

div :: CLLong -> CLLong -> CLLong #

mod :: CLLong -> CLLong -> CLLong #

divMod :: CLLong -> CLLong -> (CLLong, CLLong) #

IDivisible CULLong 
IDivisible CPtrdiff 
IDivisible CSize 

Methods

div :: CSize -> CSize -> CSize #

mod :: CSize -> CSize -> CSize #

divMod :: CSize -> CSize -> (CSize, CSize) #

IDivisible CWchar 

Methods

div :: CWchar -> CWchar -> CWchar #

mod :: CWchar -> CWchar -> CWchar #

divMod :: CWchar -> CWchar -> (CWchar, CWchar) #

IDivisible CSigAtomic 
IDivisible CIntPtr 
IDivisible CUIntPtr 
IDivisible CIntMax 
IDivisible CUIntMax 
IDivisible Word256 
IDivisible Word128 

class Multiplicative a => Divisible a where #

Support for division between same types

This is likely to change to represent specific mathematic divisions

Minimal complete definition

(/)

Methods

(/) :: a -> a -> a infixl 7 #

Instances

Data types

data Maybe a :: * -> * #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

Monad Maybe

Since: 2.1

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

fail :: String -> Maybe a #

Functor Maybe

Since: 2.1

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Applicative Maybe

Since: 2.1

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe

Since: 2.1

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe

Since: 2.1

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

Alternative Maybe

Since: 2.1

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

MonadPlus Maybe

Since: 2.1

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadFailure Maybe 

Associated Types

type Failure (Maybe :: * -> *) :: * #

Methods

mFail :: Failure Maybe -> Maybe () #

Eq a => Eq (Maybe a) 

Methods

(==) :: Maybe a -> Maybe a -> Bool #

(/=) :: Maybe a -> Maybe a -> Bool #

Data a => Data (Maybe a)

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) #

toConstr :: Maybe a -> Constr #

dataTypeOf :: Maybe a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) #

gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) #

Ord a => Ord (Maybe a) 

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

(<=) :: Maybe a -> Maybe a -> Bool #

(>) :: Maybe a -> Maybe a -> Bool #

(>=) :: Maybe a -> Maybe a -> Bool #

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a)

Since: 2.1

Show a => Show (Maybe a) 

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a)

Since: 4.9.0.0

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there used to be no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Since: 2.1

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

SingKind a => SingKind (Maybe a)

Since: 4.9.0.0

Associated Types

type DemoteRep (Maybe a) :: *

Methods

fromSing :: Sing (Maybe a) a -> DemoteRep (Maybe a)

NormalForm a => NormalForm (Maybe a) 

Methods

toNormalForm :: Maybe a -> () #

Arbitrary a => Arbitrary (Maybe a) Source # 

Methods

arbitrary :: Gen (Maybe a) Source #

Generic1 * Maybe 

Associated Types

type Rep1 Maybe (f :: Maybe -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Maybe f a #

to1 :: Rep1 Maybe f a -> f a #

SingI (Maybe a) (Nothing a)

Since: 4.9.0.0

Methods

sing :: Sing (Nothing a) a

SingI a1 a2 => SingI (Maybe a1) (Just a1 a2)

Since: 4.9.0.0

Methods

sing :: Sing (Just a1 a2) a

type Failure Maybe 
type Failure Maybe = ()
type Rep (Maybe a) 
type Rep (Maybe a) = D1 * (MetaData "Maybe" "GHC.Base" "base" False) ((:+:) * (C1 * (MetaCons "Nothing" PrefixI False) (U1 *)) (C1 * (MetaCons "Just" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))
data Sing (Maybe a) 
data Sing (Maybe a) where
type DemoteRep (Maybe a) 
type DemoteRep (Maybe a) = Maybe (DemoteRep a)
type Rep1 * Maybe 
type (==) (Maybe k) a b 
type (==) (Maybe k) a b = EqMaybe k a b

data Ordering :: * #

Constructors

LT 
EQ 
GT 

Instances

Bounded Ordering

Since: 2.1

Enum Ordering

Since: 2.1

Eq Ordering 
Data Ordering

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering #

toConstr :: Ordering -> Constr #

dataTypeOf :: Ordering -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) #

gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering #

Ord Ordering 
Read Ordering

Since: 2.1

Show Ordering 
Ix Ordering

Since: 2.1

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Semigroup Ordering

Since: 4.9.0.0

Monoid Ordering

Since: 2.1

type Rep Ordering 
type Rep Ordering = D1 * (MetaData "Ordering" "GHC.Types" "ghc-prim" False) ((:+:) * (C1 * (MetaCons "LT" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EQ" PrefixI False) (U1 *)) (C1 * (MetaCons "GT" PrefixI False) (U1 *))))
type (==) Ordering a b 
type (==) Ordering a b = EqOrdering a b

data Bool :: * #

Constructors

False 
True 

Instances

Bounded Bool

Since: 2.1

Enum Bool

Since: 2.1

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 

Methods

(==) :: Bool -> Bool -> Bool #

(/=) :: Bool -> Bool -> Bool #

Data Bool

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool #

toConstr :: Bool -> Constr #

dataTypeOf :: Bool -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bool) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) #

gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool #

Ord Bool 

Methods

compare :: Bool -> Bool -> Ordering #

(<) :: Bool -> Bool -> Bool #

(<=) :: Bool -> Bool -> Bool #

(>) :: Bool -> Bool -> Bool #

(>=) :: Bool -> Bool -> Bool #

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool

Since: 2.1

Show Bool 

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Ix Bool

Since: 2.1

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

SingKind Bool

Since: 4.9.0.0

Associated Types

type DemoteRep Bool :: *

Methods

fromSing :: Sing Bool a -> DemoteRep Bool

Storable Bool

Since: 2.1

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Bits Bool

Interpret Bool as 1-bit bit-field

Since: 4.7.0.0

FiniteBits Bool

Since: 4.7.0.0

NormalForm Bool 

Methods

toNormalForm :: Bool -> () #

Arbitrary Bool Source # 
IsProperty Bool Source # 
SingI Bool False

Since: 4.9.0.0

Methods

sing :: Sing False a

SingI Bool True

Since: 4.9.0.0

Methods

sing :: Sing True a

IsProperty (String, Bool) Source # 
type Rep Bool 
type Rep Bool = D1 * (MetaData "Bool" "GHC.Types" "ghc-prim" False) ((:+:) * (C1 * (MetaCons "False" PrefixI False) (U1 *)) (C1 * (MetaCons "True" PrefixI False) (U1 *)))
data Sing Bool 
data Sing Bool where
type DemoteRep Bool 
type DemoteRep Bool = Bool
type (==) Bool a b 
type (==) Bool a b = EqBool a b

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).

Instances

Bounded Char

Since: 2.1

Enum Char

Since: 2.1

Methods

succ :: Char -> Char #

pred :: Char -> Char #

toEnum :: Int -> Char #

fromEnum :: Char -> Int #

enumFrom :: Char -> [Char] #

enumFromThen :: Char -> Char -> [Char] #

enumFromTo :: Char -> Char -> [Char] #

enumFromThenTo :: Char -> Char -> Char -> [Char] #

Eq Char 

Methods

(==) :: Char -> Char -> Bool #

(/=) :: Char -> Char -> Bool #

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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char #

toConstr :: Char -> Constr #

dataTypeOf :: Char -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Char) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) #

gmapT :: (forall b. Data b => b -> b) -> Char -> Char #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r #

gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char #

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

Since: 2.1

Show Char

Since: 2.1

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Ix Char

Since: 2.1

Methods

range :: (Char, Char) -> [Char] #

index :: (Char, Char) -> Char -> Int #

unsafeIndex :: (Char, Char) -> Char -> Int

inRange :: (Char, Char) -> Char -> Bool #

rangeSize :: (Char, Char) -> Int #

unsafeRangeSize :: (Char, Char) -> Int

PrintfArg Char

Since: 2.1

IsChar Char

Since: 2.1

Methods

toChar :: Char -> Char #

fromChar :: Char -> Char #

Storable Char

Since: 2.1

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

NormalForm Char 

Methods

toNormalForm :: Char -> () #

PrimType Char 
PrimMemoryComparable Char 
Subtractive Char 

Associated Types

type Difference Char :: * #

Methods

(-) :: Char -> Char -> Difference Char #

StorableFixed Char Source # 

Methods

size :: proxy Char -> CountOf Word8 Source #

alignment :: proxy Char -> CountOf Word8 Source #

Storable Char Source # 

Methods

peek :: Ptr Char -> IO Char Source #

poke :: Ptr Char -> Char -> IO () Source #

Arbitrary Char Source # 
Generic1 k (URec k Char) 

Associated Types

type Rep1 (URec k Char) (f :: URec k Char -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Char) f a #

to1 :: Rep1 (URec k Char) f a -> f a #

Functor (URec * Char) 

Methods

fmap :: (a -> b) -> URec * Char a -> URec * Char b #

(<$) :: a -> URec * Char b -> URec * Char a #

Foldable (URec * Char) 

Methods

fold :: Monoid m => URec * Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Char a -> m #

foldr :: (a -> b -> b) -> b -> URec * Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Char a -> b #

foldl :: (b -> a -> b) -> b -> URec * Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Char a -> b #

foldr1 :: (a -> a -> a) -> URec * Char a -> a #

foldl1 :: (a -> a -> a) -> URec * Char a -> a #

toList :: URec * Char a -> [a] #

null :: URec * Char a -> Bool #

length :: URec * Char a -> Int #

elem :: Eq a => a -> URec * Char a -> Bool #

maximum :: Ord a => URec * Char a -> a #

minimum :: Ord a => URec * Char a -> a #

sum :: Num a => URec * Char a -> a #

product :: Num a => URec * Char a -> a #

Traversable (URec * Char) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Char a -> f (URec * Char b) #

sequenceA :: Applicative f => URec * Char (f a) -> f (URec * Char a) #

mapM :: Monad m => (a -> m b) -> URec * Char a -> m (URec * Char b) #

sequence :: Monad m => URec * Char (m a) -> m (URec * Char a) #

Eq (URec k Char p) 

Methods

(==) :: URec k Char p -> URec k Char p -> Bool #

(/=) :: URec k Char p -> URec k Char p -> Bool #

Ord (URec k Char p) 

Methods

compare :: URec k Char p -> URec k Char p -> Ordering #

(<) :: URec k Char p -> URec k Char p -> Bool #

(<=) :: URec k Char p -> URec k Char p -> Bool #

(>) :: URec k Char p -> URec k Char p -> Bool #

(>=) :: URec k Char p -> URec k Char p -> Bool #

max :: URec k Char p -> URec k Char p -> URec k Char p #

min :: URec k Char p -> URec k Char p -> URec k Char p #

Show (URec k Char p) 

Methods

showsPrec :: Int -> URec k Char p -> ShowS #

show :: URec k Char p -> String #

showList :: [URec k Char p] -> ShowS #

Generic (URec k Char p) 

Associated Types

type Rep (URec k Char p) :: * -> * #

Methods

from :: URec k Char p -> Rep (URec k Char p) x #

to :: Rep (URec k Char p) x -> URec k Char p #

type Difference Char 
type NatNumMaxBound Char 
type NatNumMaxBound Char = 1114111
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 IO a :: * -> * #

A value of type IO a is a computation which, when performed, does some I/O before returning a value of type a.

There is really only one way to "perform" an I/O action: bind it to Main.main in your program. When your program is run, the I/O will be performed. It isn't possible to perform I/O from an arbitrary function, unless that function is itself in the IO monad and called at some point, directly or indirectly, from Main.main.

IO is a monad, so IO actions can be combined using either the do-notation or the >> and >>= operations from the Monad class.

Instances

Monad IO

Since: 2.1

Methods

(>>=) :: IO a -> (a -> IO b) -> IO b #

(>>) :: IO a -> IO b -> IO b #

return :: a -> IO a #

fail :: String -> IO a #

Functor IO

Since: 2.1

Methods

fmap :: (a -> b) -> IO a -> IO b #

(<$) :: a -> IO b -> IO a #

Applicative IO

Since: 2.1

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

liftA2 :: (a -> b -> c) -> IO a -> IO b -> IO c #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

MonadIO IO

Since: 4.9.0.0

Methods

liftIO :: IO a -> IO a #

Alternative IO

Since: 4.9.0.0

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

MonadPlus IO

Since: 4.9.0.0

Methods

mzero :: IO a #

mplus :: IO a -> IO a -> IO a #

PrimMonad IO 

Associated Types

type PrimState (IO :: * -> *) :: * #

type PrimVar (IO :: * -> *) :: * -> * #

MonadBracket IO Source # 

Methods

generalBracket :: IO a -> (a -> b -> IO ignored1) -> (a -> SomeException -> IO ignored2) -> (a -> IO b) -> IO b Source #

MonadCatch IO Source # 

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a Source #

MonadThrow IO Source # 

Methods

throw :: Exception e => e -> IO a Source #

MonadRandom IO Source # 
Semigroup a => Semigroup (IO a)

Since: 4.10.0.0

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

(~) * a () => PrintfType (IO a)

Since: 4.7.0.0

Methods

spr :: String -> [UPrintf] -> IO a

(~) * a () => HPrintfType (IO a)

Since: 4.7.0.0

Methods

hspr :: Handle -> String -> [UPrintf] -> IO a

type PrimVar IO 
type PrimState IO 

data Either a b :: * -> * -> * #

The Either type represents values with two possibilities: a value of type Either a b is either Left a or Right b.

The Either type is sometimes used to represent a value which is either correct or an error; by convention, the Left constructor is used to hold an error value and the Right constructor is used to hold a correct value (mnemonic: "right" also means "correct").

Examples

The type Either String Int is the type of values which can be either a String or an Int. The Left constructor can be used only on Strings, and the Right constructor can be used only on Ints:

>>> let s = Left "foo" :: Either String Int
>>> s
Left "foo"
>>> let n = Right 3 :: Either String Int
>>> n
Right 3
>>> :type s
s :: Either String Int
>>> :type n
n :: Either String Int

The fmap from our Functor instance will ignore Left values, but will apply the supplied function to values contained in a Right:

>>> let s = Left "foo" :: Either String Int
>>> let n = Right 3 :: Either String Int
>>> fmap (*2) s
Left "foo"
>>> fmap (*2) n
Right 6

The Monad instance for Either allows us to chain together multiple actions which may fail, and fail overall if any of the individual steps failed. First we'll write a function that can either parse an Int from a Char, or fail.

>>> import Data.Char ( digitToInt, isDigit )
>>> :{
    let parseEither :: Char -> Either String Int
        parseEither c
          | isDigit c = Right (digitToInt c)
          | otherwise = Left "parse error"
>>> :}

The following should work, since both '1' and '2' can be parsed as Ints.

>>> :{
    let parseMultiple :: Either String Int
        parseMultiple = do
          x <- parseEither '1'
          y <- parseEither '2'
          return (x + y)
>>> :}
>>> parseMultiple
Right 3

But the following should fail overall, since the first operation where we attempt to parse 'm' as an Int will fail:

>>> :{
    let parseMultiple :: Either String Int
        parseMultiple = do
          x <- parseEither 'm'
          y <- parseEither '2'
          return (x + y)
>>> :}
>>> parseMultiple
Left "parse error"

Constructors

Left a 
Right b 

Instances

Bifunctor Either

Since: 4.8.0.0

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d #

first :: (a -> b) -> Either a c -> Either b c #

second :: (b -> c) -> Either a b -> Either a c #

Monad (Either e)

Since: 4.4.0.0

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b #

(>>) :: Either e a -> Either e b -> Either e b #

return :: a -> Either e a #

fail :: String -> Either e a #

Functor (Either a)

Since: 3.0

Methods

fmap :: (a -> b) -> Either a a -> Either a b #

(<$) :: a -> Either a b -> Either a a #

Applicative (Either e)

Since: 3.0

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Foldable (Either a)

Since: 4.7.0.0

Methods

fold :: Monoid m => Either a m -> m #

foldMap :: Monoid m => (a -> m) -> Either a a -> m #

foldr :: (a -> b -> b) -> b -> Either a a -> b #

foldr' :: (a -> b -> b) -> b -> Either a a -> b #

foldl :: (b -> a -> b) -> b -> Either a a -> b #

foldl' :: (b -> a -> b) -> b -> Either a a -> b #

foldr1 :: (a -> a -> a) -> Either a a -> a #

foldl1 :: (a -> a -> a) -> Either a a -> a #

toList :: Either a a -> [a] #

null :: Either a a -> Bool #

length :: Either a a -> Int #

elem :: Eq a => a -> Either a a -> Bool #

maximum :: Ord a => Either a a -> a #

minimum :: Ord a => Either a a -> a #

sum :: Num a => Either a a -> a #

product :: Num a => Either a a -> a #

Traversable (Either a)

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Either a a -> f (Either a b) #

sequenceA :: Applicative f => Either a (f a) -> f (Either a a) #

mapM :: Monad m => (a -> m b) -> Either a a -> m (Either a b) #

sequence :: Monad m => Either a (m a) -> m (Either a a) #

MonadFailure (Either a) 

Associated Types

type Failure (Either a :: * -> *) :: * #

Methods

mFail :: Failure (Either a) -> Either a () #

Generic1 * (Either a) 

Associated Types

type Rep1 (Either a) (f :: Either a -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Either a) f a #

to1 :: Rep1 (Either a) f a -> f a #

(Eq b, Eq a) => Eq (Either a b) 

Methods

(==) :: Either a b -> Either a b -> Bool #

(/=) :: Either a b -> Either a b -> Bool #

(Data a, Data b) => Data (Either a b)

Since: 4.0.0.0

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> Either a b -> c (Either a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) #

toConstr :: Either a b -> Constr #

dataTypeOf :: Either a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) #

gmapT :: (forall c. Data c => c -> c) -> Either a b -> Either a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) #

(Ord b, Ord a) => Ord (Either a b) 

Methods

compare :: Either a b -> Either a b -> Ordering #

(<) :: Either a b -> Either a b -> Bool #

(<=) :: Either a b -> Either a b -> Bool #

(>) :: Either a b -> Either a b -> Bool #

(>=) :: Either a b -> Either a b -> Bool #

max :: Either a b -> Either a b -> Either a b #

min :: Either a b -> Either a b -> Either a b #

(Read b, Read a) => Read (Either a b) 
(Show b, Show a) => Show (Either a b) 

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Semigroup (Either a b)

Since: 4.9.0.0

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b => b -> Either a b -> Either a b #

(NormalForm l, NormalForm r) => NormalForm (Either l r) 

Methods

toNormalForm :: Either l r -> () #

(Arbitrary l, Arbitrary r) => Arbitrary (Either l r) Source # 

Methods

arbitrary :: Gen (Either l r) Source #

type Failure (Either a) 
type Failure (Either a) = a
type Rep1 * (Either a) 
type Rep (Either a b) 
type (==) (Either k1 k2) a b 
type (==) (Either k1 k2) a b = EqEither k1 k2 a b

Numbers

data Int8 :: * #

8-bit signed integer type

Instances

Bounded Int8

Since: 2.1

Enum Int8

Since: 2.1

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Eq Int8

Since: 2.1

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Integral Int8

Since: 2.1

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Data Int8

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int8 -> c Int8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 #

toConstr :: Int8 -> Constr #

dataTypeOf :: Int8 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int8) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int8) #

gmapT :: (forall b. Data b => b -> b) -> Int8 -> Int8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

Num Int8

Since: 2.1

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8

Since: 2.1

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

(>=) :: Int8 -> Int8 -> Bool #

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Read Int8

Since: 2.1

Real Int8

Since: 2.1

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: 2.1

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8

Since: 2.1

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int

PrintfArg Int8

Since: 2.1

Storable Int8

Since: 2.1

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: 2.1

FiniteBits Int8

Since: 4.6.0.0

NormalForm Int8 

Methods

toNormalForm :: Int8 -> () #

PrimType Int8 
PrimMemoryComparable Int8 
Multiplicative Int8 

Methods

midentity :: Int8 #

(*) :: Int8 -> Int8 -> Int8 #

(^) :: (IsNatural n, IDivisible n) => Int8 -> n -> Int8 #

IDivisible Int8 

Methods

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

Additive Int8 

Methods

azero :: Int8 #

(+) :: Int8 -> Int8 -> Int8 #

scale :: IsNatural n => n -> Int8 -> Int8 #

Subtractive Int8 

Associated Types

type Difference Int8 :: * #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 #

IsIntegral Int8 

Methods

toInteger :: Int8 -> Integer #

Integral Int8 

Methods

fromInteger :: Integer -> Int8 #

HasNegation Int8 

Methods

negate :: Int8 -> Int8 #

Signed Int8 Source # 

Methods

abs :: Int8 -> Int8 Source #

signum :: Int8 -> Sign Source #

StorableFixed Int8 Source # 

Methods

size :: proxy Int8 -> CountOf Word8 Source #

alignment :: proxy Int8 -> CountOf Word8 Source #

Storable Int8 Source # 

Methods

peek :: Ptr Int8 -> IO Int8 Source #

poke :: Ptr Int8 -> Int8 -> IO () Source #

Arbitrary Int8 Source # 
Hashable Int8 Source # 

Methods

hashMix :: Hasher st => Int8 -> st -> st Source #

IntegralDownsize Int Int8 
IntegralDownsize Int64 Int8 
IntegralDownsize Integer Int8 
IntegralUpsize Int8 Int 

Methods

integralUpsize :: Int8 -> Int #

IntegralUpsize Int8 Int16 

Methods

integralUpsize :: Int8 -> Int16 #

IntegralUpsize Int8 Int32 

Methods

integralUpsize :: Int8 -> Int32 #

IntegralUpsize Int8 Int64 

Methods

integralUpsize :: Int8 -> Int64 #

IntegralCast Int8 Word8 

Methods

integralCast :: Int8 -> Word8 #

IntegralCast Word8 Int8 

Methods

integralCast :: Word8 -> Int8 #

type Difference Int8 
type NatNumMaxBound Int8 
type NatNumMaxBound Int8 = 127

data Int16 :: * #

16-bit signed integer type

Instances

Bounded Int16

Since: 2.1

Enum Int16

Since: 2.1

Eq Int16

Since: 2.1

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Integral Int16

Since: 2.1

Data Int16

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int16 -> c Int16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 #

toConstr :: Int16 -> Constr #

dataTypeOf :: Int16 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int16) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int16) #

gmapT :: (forall b. Data b => b -> b) -> Int16 -> Int16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

Num Int16

Since: 2.1

Ord Int16

Since: 2.1

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

(>=) :: Int16 -> Int16 -> Bool #

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Read Int16

Since: 2.1

Real Int16

Since: 2.1

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: 2.1

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16

Since: 2.1

PrintfArg Int16

Since: 2.1

Storable Int16

Since: 2.1

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: 2.1

FiniteBits Int16

Since: 4.6.0.0

NormalForm Int16 

Methods

toNormalForm :: Int16 -> () #

PrimType Int16 
PrimMemoryComparable Int16 
Multiplicative Int16 

Methods

midentity :: Int16 #

(*) :: Int16 -> Int16 -> Int16 #

(^) :: (IsNatural n, IDivisible n) => Int16 -> n -> Int16 #

IDivisible Int16 

Methods

div :: Int16 -> Int16 -> Int16 #

mod :: Int16 -> Int16 -> Int16 #

divMod :: Int16 -> Int16 -> (Int16, Int16) #

Additive Int16 

Methods

azero :: Int16 #

(+) :: Int16 -> Int16 -> Int16 #

scale :: IsNatural n => n -> Int16 -> Int16 #

Subtractive Int16 

Associated Types

type Difference Int16 :: * #

Methods

(-) :: Int16 -> Int16 -> Difference Int16 #

IsIntegral Int16 

Methods

toInteger :: Int16 -> Integer #

Integral Int16 

Methods

fromInteger :: Integer -> Int16 #

HasNegation Int16 

Methods

negate :: Int16 -> Int16 #

Signed Int16 Source # 
StorableFixed Int16 Source # 

Methods

size :: proxy Int16 -> CountOf Word8 Source #

alignment :: proxy Int16 -> CountOf Word8 Source #

Storable Int16 Source # 

Methods

peek :: Ptr Int16 -> IO Int16 Source #

poke :: Ptr Int16 -> Int16 -> IO () Source #

Arbitrary Int16 Source # 
Hashable Int16 Source # 

Methods

hashMix :: Hasher st => Int16 -> st -> st Source #

IntegralDownsize Int Int16 
IntegralDownsize Int64 Int16 
IntegralDownsize Integer Int16 
IntegralUpsize Int8 Int16 

Methods

integralUpsize :: Int8 -> Int16 #

IntegralUpsize Int16 Int 

Methods

integralUpsize :: Int16 -> Int #

IntegralUpsize Int16 Int32 
IntegralUpsize Int16 Int64 
IntegralUpsize Word8 Int16 
IntegralCast Int16 Word16 

Methods

integralCast :: Int16 -> Word16 #

IntegralCast Word16 Int16 

Methods

integralCast :: Word16 -> Int16 #

type Difference Int16 
type NatNumMaxBound Int16 
type NatNumMaxBound Int16 = 32767

data Int32 :: * #

32-bit signed integer type

Instances

Bounded Int32

Since: 2.1

Enum Int32

Since: 2.1

Eq Int32

Since: 2.1

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Integral Int32

Since: 2.1

Data Int32

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 #

toConstr :: Int32 -> Constr #

dataTypeOf :: Int32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) #

gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

Num Int32

Since: 2.1

Ord Int32

Since: 2.1

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

(>=) :: Int32 -> Int32 -> Bool #

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32

Since: 2.1

Real Int32

Since: 2.1

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: 2.1

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: 2.1

PrintfArg Int32

Since: 2.1

Storable Int32

Since: 2.1

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: 2.1

FiniteBits Int32

Since: 4.6.0.0

NormalForm Int32 

Methods

toNormalForm :: Int32 -> () #

PrimType Int32 
PrimMemoryComparable Int32 
Multiplicative Int32 

Methods

midentity :: Int32 #

(*) :: Int32 -> Int32 -> Int32 #

(^) :: (IsNatural n, IDivisible n) => Int32 -> n -> Int32 #

IDivisible Int32 

Methods

div :: Int32 -> Int32 -> Int32 #

mod :: Int32 -> Int32 -> Int32 #

divMod :: Int32 -> Int32 -> (Int32, Int32) #

Additive Int32 

Methods

azero :: Int32 #

(+) :: Int32 -> Int32 -> Int32 #

scale :: IsNatural n => n -> Int32 -> Int32 #

Subtractive Int32 

Associated Types

type Difference Int32 :: * #

Methods

(-) :: Int32 -> Int32 -> Difference Int32 #

IsIntegral Int32 

Methods

toInteger :: Int32 -> Integer #

Integral Int32 

Methods

fromInteger :: Integer -> Int32 #

HasNegation Int32 

Methods

negate :: Int32 -> Int32 #

Signed Int32 Source # 
StorableFixed Int32 Source # 

Methods

size :: proxy Int32 -> CountOf Word8 Source #

alignment :: proxy Int32 -> CountOf Word8 Source #

Storable Int32 Source # 

Methods

peek :: Ptr Int32 -> IO Int32 Source #

poke :: Ptr Int32 -> Int32 -> IO () Source #

Arbitrary Int32 Source # 
Hashable Int32 Source # 

Methods

hashMix :: Hasher st => Int32 -> st -> st Source #

IntegralDownsize Int Int32 
IntegralDownsize Int64 Int32 
IntegralDownsize Integer Int32 
IntegralUpsize Int8 Int32 

Methods

integralUpsize :: Int8 -> Int32 #

IntegralUpsize Int16 Int32 
IntegralUpsize Int32 Int 

Methods

integralUpsize :: Int32 -> Int #

IntegralUpsize Int32 Int64 
IntegralUpsize Word8 Int32 
IntegralCast Int32 Word32 

Methods

integralCast :: Int32 -> Word32 #

IntegralCast Word32 Int32 

Methods

integralCast :: Word32 -> Int32 #

type Difference Int32 
type NatNumMaxBound Int32 
type NatNumMaxBound Int32 = 2147483647

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64

Since: 2.1

Enum Int64

Since: 2.1

Eq Int64

Since: 2.1

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64

Since: 2.1

Data Int64

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 #

toConstr :: Int64 -> Constr #

dataTypeOf :: Int64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) #

gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

Num Int64

Since: 2.1

Ord Int64

Since: 2.1

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64

Since: 2.1

Real Int64

Since: 2.1

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: 2.1

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: 2.1

PrintfArg Int64

Since: 2.1

Storable Int64

Since: 2.1

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: 2.1

FiniteBits Int64

Since: 4.6.0.0

NormalForm Int64 

Methods

toNormalForm :: Int64 -> () #

PrimType Int64 
PrimMemoryComparable Int64 
Multiplicative Int64 

Methods

midentity :: Int64 #

(*) :: Int64 -> Int64 -> Int64 #

(^) :: (IsNatural n, IDivisible n) => Int64 -> n -> Int64 #

IDivisible Int64 

Methods

div :: Int64 -> Int64 -> Int64 #

mod :: Int64 -> Int64 -> Int64 #

divMod :: Int64 -> Int64 -> (Int64, Int64) #

Additive Int64 

Methods

azero :: Int64 #

(+) :: Int64 -> Int64 -> Int64 #

scale :: IsNatural n => n -> Int64 -> Int64 #

Subtractive Int64 

Associated Types

type Difference Int64 :: * #

Methods

(-) :: Int64 -> Int64 -> Difference Int64 #

IsIntegral Int64 

Methods

toInteger :: Int64 -> Integer #

Integral Int64 

Methods

fromInteger :: Integer -> Int64 #

HasNegation Int64 

Methods

negate :: Int64 -> Int64 #

Signed Int64 Source # 
StorableFixed Int64 Source # 

Methods

size :: proxy Int64 -> CountOf Word8 Source #

alignment :: proxy Int64 -> CountOf Word8 Source #

Storable Int64 Source # 

Methods

peek :: Ptr Int64 -> IO Int64 Source #

poke :: Ptr Int64 -> Int64 -> IO () Source #

Arbitrary Int64 Source # 
Hashable Int64 Source # 

Methods

hashMix :: Hasher st => Int64 -> st -> st Source #

IntegralDownsize Int64 Int 
IntegralDownsize Int64 Int8 
IntegralDownsize Int64 Int16 
IntegralDownsize Int64 Int32 
IntegralDownsize Integer Int64 
IntegralUpsize Int Int64 

Methods

integralUpsize :: Int -> Int64 #

IntegralUpsize Int8 Int64 

Methods

integralUpsize :: Int8 -> Int64 #

IntegralUpsize Int16 Int64 
IntegralUpsize Int32 Int64 
IntegralUpsize Word8 Int64 
IntegralCast Int64 Word64 

Methods

integralCast :: Int64 -> Word64 #

IntegralCast Word64 Int64 

Methods

integralCast :: Word64 -> Int64 #

type Difference Int64 
type NatNumMaxBound Int64 
type NatNumMaxBound Int64 = 9223372036854775807

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8

Since: 2.1

Enum Word8

Since: 2.1

Eq Word8

Since: 2.1

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: 2.1

Data Word8

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 #

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word8) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) #

gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

Num Word8

Since: 2.1

Ord Word8

Since: 2.1

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: 2.1

Real Word8

Since: 2.1

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: 2.1

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: 2.1

PrintfArg Word8

Since: 2.1

Storable Word8

Since: 2.1

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8

Since: 2.1

FiniteBits Word8

Since: 4.6.0.0

NormalForm Word8 

Methods

toNormalForm :: Word8 -> () #

PrimType Word8 
PrimMemoryComparable Word8 
Multiplicative Word8 

Methods

midentity :: Word8 #

(*) :: Word8 -> Word8 -> Word8 #

(^) :: (IsNatural n, IDivisible n) => Word8 -> n -> Word8 #

IDivisible Word8 

Methods

div :: Word8 -> Word8 -> Word8 #

mod :: Word8 -> Word8 -> Word8 #

divMod :: Word8 -> Word8 -> (Word8, Word8) #

Additive Word8 

Methods

azero :: Word8 #

(+) :: Word8 -> Word8 -> Word8 #

scale :: IsNatural n => n -> Word8 -> Word8 #

Subtractive Word8 

Associated Types

type Difference Word8 :: * #

Methods

(-) :: Word8 -> Word8 -> Difference Word8 #

IsIntegral Word8 

Methods

toInteger :: Word8 -> Integer #

IsNatural Word8 

Methods

toNatural :: Word8 -> Natural #

Integral Word8 

Methods

fromInteger :: Integer -> Word8 #

HasNegation Word8 

Methods

negate :: Word8 -> Word8 #

StorableFixed Word8 Source # 

Methods

size :: proxy Word8 -> CountOf Word8 Source #

alignment :: proxy Word8 -> CountOf Word8 Source #

Storable Word8 Source # 

Methods

peek :: Ptr Word8 -> IO Word8 Source #

poke :: Ptr Word8 -> Word8 -> IO () Source #

Arbitrary Word8 Source # 
Hashable Word8 Source # 

Methods

hashMix :: Hasher st => Word8 -> st -> st Source #

IntegralDownsize Integer Word8 
IntegralDownsize Natural Word8 
IntegralDownsize Word Word8 
IntegralDownsize Word16 Word8 
IntegralDownsize Word32 Word8 
IntegralDownsize Word64 Word8 
IntegralUpsize Word8 Int 

Methods

integralUpsize :: Word8 -> Int #

IntegralUpsize Word8 Int16 
IntegralUpsize Word8 Int32 
IntegralUpsize Word8 Int64 
IntegralUpsize Word8 Word 

Methods

integralUpsize :: Word8 -> Word #

IntegralUpsize Word8 Word16 
IntegralUpsize Word8 Word32 
IntegralUpsize Word8 Word64 
IntegralCast Int8 Word8 

Methods

integralCast :: Int8 -> Word8 #

IntegralCast Word8 Int8 

Methods

integralCast :: Word8 -> Int8 #

type Difference Word8 
type NatNumMaxBound Word8 

data Word16 :: * #

16-bit unsigned integer type

Instances

Bounded Word16

Since: 2.1

Enum Word16

Since: 2.1

Eq Word16

Since: 2.1

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16

Since: 2.1

Data Word16

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word16 -> c Word16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 #

toConstr :: Word16 -> Constr #

dataTypeOf :: Word16 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word16) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word16) #

gmapT :: (forall b. Data b => b -> b) -> Word16 -> Word16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

Num Word16

Since: 2.1

Ord Word16

Since: 2.1

Read Word16

Since: 2.1

Real Word16

Since: 2.1

Show Word16

Since: 2.1

Ix Word16

Since: 2.1

PrintfArg Word16

Since: 2.1

Storable Word16

Since: 2.1

Bits Word16

Since: 2.1

FiniteBits Word16

Since: 4.6.0.0

NormalForm Word16 

Methods

toNormalForm :: Word16 -> () #

PrimType Word16 
PrimMemoryComparable Word16 
Multiplicative Word16 

Methods

midentity :: Word16 #

(*) :: Word16 -> Word16 -> Word16 #

(^) :: (IsNatural n, IDivisible n) => Word16 -> n -> Word16 #

IDivisible Word16 

Methods

div :: Word16 -> Word16 -> Word16 #

mod :: Word16 -> Word16 -> Word16 #

divMod :: Word16 -> Word16 -> (Word16, Word16) #

Additive Word16 

Methods

azero :: Word16 #

(+) :: Word16 -> Word16 -> Word16 #

scale :: IsNatural n => n -> Word16 -> Word16 #

Subtractive Word16 

Associated Types

type Difference Word16 :: * #

IsIntegral Word16 

Methods

toInteger :: Word16 -> Integer #

IsNatural Word16 

Methods

toNatural :: Word16 -> Natural #

ByteSwap Word16 

Methods

byteSwap :: Word16 -> Word16

Integral Word16 
HasNegation Word16 

Methods

negate :: Word16 -> Word16 #

StorableFixed Word16 Source # 
Storable Word16 Source # 
Arbitrary Word16 Source # 
Hashable Word16 Source # 

Methods

hashMix :: Hasher st => Word16 -> st -> st Source #

IntegralDownsize Integer Word16 
IntegralDownsize Natural Word16 
IntegralDownsize Word Word16 
IntegralDownsize Word16 Word8 
IntegralDownsize Word32 Word16 
IntegralDownsize Word64 Word16 
IntegralUpsize Word8 Word16 
IntegralUpsize Word16 Word 
IntegralUpsize Word16 Word32 
IntegralUpsize Word16 Word64 
IntegralCast Int16 Word16 

Methods

integralCast :: Int16 -> Word16 #

IntegralCast Word16 Int16 

Methods

integralCast :: Word16 -> Int16 #

StorableFixed (LE Word16) Source # 

Methods

size :: proxy (LE Word16) -> CountOf Word8 Source #

alignment :: proxy (LE Word16) -> CountOf Word8 Source #

StorableFixed (BE Word16) Source # 

Methods

size :: proxy (BE Word16) -> CountOf Word8 Source #

alignment :: proxy (BE Word16) -> CountOf Word8 Source #

Storable (LE Word16) Source # 

Methods

peek :: Ptr (LE Word16) -> IO (LE Word16) Source #

poke :: Ptr (LE Word16) -> LE Word16 -> IO () Source #

Storable (BE Word16) Source # 

Methods

peek :: Ptr (BE Word16) -> IO (BE Word16) Source #

poke :: Ptr (BE Word16) -> BE Word16 -> IO () Source #

type Difference Word16 
type NatNumMaxBound Word16 
type NatNumMaxBound Word16 = 65535

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32

Since: 2.1

Enum Word32

Since: 2.1

Eq Word32

Since: 2.1

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32

Since: 2.1

Data Word32

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32

Since: 2.1

Ord Word32

Since: 2.1

Read Word32

Since: 2.1

Real Word32

Since: 2.1

Show Word32

Since: 2.1

Ix Word32

Since: 2.1

PrintfArg Word32

Since: 2.1

Storable Word32

Since: 2.1

Bits Word32

Since: 2.1

FiniteBits Word32

Since: 4.6.0.0

NormalForm Word32 

Methods

toNormalForm :: Word32 -> () #

PrimType Word32 
PrimMemoryComparable Word32 
Multiplicative Word32 

Methods

midentity :: Word32 #

(*) :: Word32 -> Word32 -> Word32 #

(^) :: (IsNatural n, IDivisible n) => Word32 -> n -> Word32 #

IDivisible Word32 

Methods

div :: Word32 -> Word32 -> Word32 #

mod :: Word32 -> Word32 -> Word32 #

divMod :: Word32 -> Word32 -> (Word32, Word32) #

Additive Word32 

Methods

azero :: Word32 #

(+) :: Word32 -> Word32 -> Word32 #

scale :: IsNatural n => n -> Word32 -> Word32 #

Subtractive Word32 

Associated Types

type Difference Word32 :: * #

IsIntegral Word32 

Methods

toInteger :: Word32 -> Integer #

IsNatural Word32 

Methods

toNatural :: Word32 -> Natural #

ByteSwap Word32 

Methods

byteSwap :: Word32 -> Word32

Integral Word32 
HasNegation Word32 

Methods

negate :: Word32 -> Word32 #

StorableFixed Word32 Source # 
Storable Word32 Source # 
Arbitrary Word32 Source # 
Hashable Word32 Source # 

Methods

hashMix :: Hasher st => Word32 -> st -> st Source #

IntegralDownsize Integer Word32 
IntegralDownsize Natural Word32 
IntegralDownsize Word Word32 
IntegralDownsize Word32 Word8 
IntegralDownsize Word32 Word16 
IntegralDownsize Word64 Word32 
IntegralUpsize Word8 Word32 
IntegralUpsize Word16 Word32 
IntegralUpsize Word32 Word 
IntegralUpsize Word32 Word64 
IntegralCast Int32 Word32 

Methods

integralCast :: Int32 -> Word32 #

IntegralCast Word32 Int32 

Methods

integralCast :: Word32 -> Int32 #

StorableFixed (LE Word32) Source # 

Methods

size :: proxy (LE Word32) -> CountOf Word8 Source #

alignment :: proxy (LE Word32) -> CountOf Word8 Source #

StorableFixed (BE Word32) Source # 

Methods

size :: proxy (BE Word32) -> CountOf Word8 Source #

alignment :: proxy (BE Word32) -> CountOf Word8 Source #

Storable (LE Word32) Source # 

Methods

peek :: Ptr (LE Word32) -> IO (LE Word32) Source #

poke :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

Storable (BE Word32) Source # 

Methods

peek :: Ptr (BE Word32) -> IO (BE Word32) Source #

poke :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

type Difference Word32 
type NatNumMaxBound Word32 
type NatNumMaxBound Word32 = 4294967295

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64

Since: 2.1

Enum Word64

Since: 2.1

Eq Word64

Since: 2.1

Methods

(==) :: Word64 -> Word64 -> Bool #

(/=) :: Word64 -> Word64 -> Bool #

Integral Word64

Since: 2.1

Data Word64

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 #

toConstr :: Word64 -> Constr #

dataTypeOf :: Word64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) #

gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 #

Num Word64

Since: 2.1

Ord Word64

Since: 2.1

Read Word64

Since: 2.1

Real Word64

Since: 2.1

Show Word64

Since: 2.1

Ix Word64

Since: 2.1

PrintfArg Word64

Since: 2.1

Storable Word64

Since: 2.1

Bits Word64

Since: 2.1

FiniteBits Word64

Since: 4.6.0.0

NormalForm Word64 

Methods

toNormalForm :: Word64 -> () #

PrimType Word64 
PrimMemoryComparable Word64 
Multiplicative Word64 

Methods

midentity :: Word64 #

(*) :: Word64 -> Word64 -> Word64 #

(^) :: (IsNatural n, IDivisible n) => Word64 -> n -> Word64 #

IDivisible Word64 

Methods

div :: Word64 -> Word64 -> Word64 #

mod :: Word64 -> Word64 -> Word64 #

divMod :: Word64 -> Word64 -> (Word64, Word64) #

Additive Word64 

Methods

azero :: Word64 #

(+) :: Word64 -> Word64 -> Word64 #

scale :: IsNatural n => n -> Word64 -> Word64 #

Subtractive Word64 

Associated Types

type Difference Word64 :: * #

IsIntegral Word64 

Methods

toInteger :: Word64 -> Integer #

IsNatural Word64 

Methods

toNatural :: Word64 -> Natural #

ByteSwap Word64 

Methods

byteSwap :: Word64 -> Word64

Integral Word64 
HasNegation Word64 

Methods

negate :: Word64 -> Word64 #

StorableFixed Word64 Source # 
Storable Word64 Source # 
Arbitrary Word64 Source # 
Hashable Word64 Source # 

Methods

hashMix :: Hasher st => Word64 -> st -> st Source #

IntegralDownsize Integer Word64 
IntegralDownsize Natural Word64 
IntegralDownsize Word64 Word8 
IntegralDownsize Word64 Word16 
IntegralDownsize Word64 Word32 
IntegralUpsize Word Word64 
IntegralUpsize Word8 Word64 
IntegralUpsize Word16 Word64 
IntegralUpsize Word32 Word64 
IntegralCast Int64 Word64 

Methods

integralCast :: Int64 -> Word64 #

IntegralCast Word64 Int64 

Methods

integralCast :: Word64 -> Int64 #

StorableFixed (LE Word64) Source # 

Methods

size :: proxy (LE Word64) -> CountOf Word8 Source #

alignment :: proxy (LE Word64) -> CountOf Word8 Source #

StorableFixed (BE Word64) Source # 

Methods

size :: proxy (BE Word64) -> CountOf Word8 Source #

alignment :: proxy (BE Word64) -> CountOf Word8 Source #

Storable (LE Word64) Source # 

Methods

peek :: Ptr (LE Word64) -> IO (LE Word64) Source #

poke :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

Storable (BE Word64) Source # 

Methods

peek :: Ptr (BE Word64) -> IO (BE Word64) Source #

poke :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

type Difference Word64 
type NatNumMaxBound Word64 
type NatNumMaxBound Word64 = 18446744073709551615

data Word :: * #

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word

Since: 2.1

Enum Word

Since: 2.1

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word

Since: 2.1

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word #

toConstr :: Word -> Constr #

dataTypeOf :: Word -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) #

gmapT :: (forall b. Data b => b -> b) -> Word -> Word #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

Num Word

Since: 2.1

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

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

Since: 4.5.0.0

Real Word

Since: 2.1

Methods

toRational :: Word -> Rational #

Show Word

Since: 2.1

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word

Since: 4.6.0.0

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int

PrintfArg Word

Since: 2.1

Storable Word

Since: 2.1

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Bits Word

Since: 2.1

FiniteBits Word

Since: 4.6.0.0

NormalForm Word 

Methods

toNormalForm :: Word -> () #

PrimType Word 
PrimMemoryComparable Word 
Multiplicative Word 

Methods

midentity :: Word #

(*) :: Word -> Word -> Word #

(^) :: (IsNatural n, IDivisible n) => Word -> n -> Word #

IDivisible Word 

Methods

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

divMod :: Word -> Word -> (Word, Word) #

Additive Word 

Methods

azero :: Word #

(+) :: Word -> Word -> Word #

scale :: IsNatural n => n -> Word -> Word #

Subtractive Word 

Associated Types

type Difference Word :: * #

Methods

(-) :: Word -> Word -> Difference Word #

IsIntegral Word 

Methods

toInteger :: Word -> Integer #

IsNatural Word 

Methods

toNatural :: Word -> Natural #

Integral Word 

Methods

fromInteger :: Integer -> Word #

HasNegation Word 

Methods

negate :: Word -> Word #

Arbitrary Word Source # 
IntegralDownsize Word Word8 
IntegralDownsize Word Word16 
IntegralDownsize Word Word32 
IntegralUpsize Word Word64 
IntegralUpsize Word8 Word 

Methods

integralUpsize :: Word8 -> Word #

IntegralUpsize Word16 Word 
IntegralUpsize Word32 Word 
IntegralCast Int Word 

Methods

integralCast :: Int -> Word #

IntegralCast Word Int 

Methods

integralCast :: Word -> Int #

IntegralCast Word (Offset ty) 

Methods

integralCast :: Word -> Offset ty #

IntegralCast Word (CountOf ty) 

Methods

integralCast :: Word -> CountOf ty #

Generic1 k (URec k Word) 

Associated Types

type Rep1 (URec k Word) (f :: URec k Word -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Word) f a #

to1 :: Rep1 (URec k Word) f a -> f a #

Functor (URec * Word) 

Methods

fmap :: (a -> b) -> URec * Word a -> URec * Word b #

(<$) :: a -> URec * Word b -> URec * Word a #

Foldable (URec * Word) 

Methods

fold :: Monoid m => URec * Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Word a -> m #

foldr :: (a -> b -> b) -> b -> URec * Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Word a -> b #

foldl :: (b -> a -> b) -> b -> URec * Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Word a -> b #

foldr1 :: (a -> a -> a) -> URec * Word a -> a #

foldl1 :: (a -> a -> a) -> URec * Word a -> a #

toList :: URec * Word a -> [a] #

null :: URec * Word a -> Bool #

length :: URec * Word a -> Int #

elem :: Eq a => a -> URec * Word a -> Bool #

maximum :: Ord a => URec * Word a -> a #

minimum :: Ord a => URec * Word a -> a #

sum :: Num a => URec * Word a -> a #

product :: Num a => URec * Word a -> a #

Traversable (URec * Word) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Word a -> f (URec * Word b) #

sequenceA :: Applicative f => URec * Word (f a) -> f (URec * Word a) #

mapM :: Monad m => (a -> m b) -> URec * Word a -> m (URec * Word b) #

sequence :: Monad m => URec * Word (m a) -> m (URec * Word a) #

Eq (URec k Word p) 

Methods

(==) :: URec k Word p -> URec k Word p -> Bool #

(/=) :: URec k Word p -> URec k Word p -> Bool #

Ord (URec k Word p) 

Methods

compare :: URec k Word p -> URec k Word p -> Ordering #

(<) :: URec k Word p -> URec k Word p -> Bool #

(<=) :: URec k Word p -> URec k Word p -> Bool #

(>) :: URec k Word p -> URec k Word p -> Bool #

(>=) :: URec k Word p -> URec k Word p -> Bool #

max :: URec k Word p -> URec k Word p -> URec k Word p #

min :: URec k Word p -> URec k Word p -> URec k Word p #

Show (URec k Word p) 

Methods

showsPrec :: Int -> URec k Word p -> ShowS #

show :: URec k Word p -> String #

showList :: [URec k Word p] -> ShowS #

Generic (URec k Word p) 

Associated Types

type Rep (URec k Word p) :: * -> * #

Methods

from :: URec k Word p -> Rep (URec k Word p) x #

to :: Rep (URec k Word p) x -> URec k Word p #

type Difference Word 
type NatNumMaxBound Word 
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 Word128 :: * #

128 bits Word

Instances

Bounded Word128 
Enum Word128 
Eq Word128 

Methods

(==) :: Word128 -> Word128 -> Bool #

(/=) :: Word128 -> Word128 -> Bool #

Num Word128 
Ord Word128 
Show Word128 
Storable Word128 
Bits Word128 
NormalForm Word128 

Methods

toNormalForm :: Word128 -> () #

PrimType Word128 
PrimMemoryComparable Word128 
Multiplicative Word128 
IDivisible Word128 
Additive Word128 

Methods

azero :: Word128 #

(+) :: Word128 -> Word128 -> Word128 #

scale :: IsNatural n => n -> Word128 -> Word128 #

Subtractive Word128 

Associated Types

type Difference Word128 :: * #

IsIntegral Word128 

Methods

toInteger :: Word128 -> Integer #

IsNatural Word128 

Methods

toNatural :: Word128 -> Natural #

Integral Word128 
HasNegation Word128 

Methods

negate :: Word128 -> Word128 #

StorableFixed Word128 Source # 
Storable Word128 Source # 
Arbitrary Word128 Source # 
Hashable Word128 Source # 

Methods

hashMix :: Hasher st => Word128 -> st -> st Source #

StorableFixed (LE Word128) Source # 

Methods

size :: proxy (LE Word128) -> CountOf Word8 Source #

alignment :: proxy (LE Word128) -> CountOf Word8 Source #

StorableFixed (BE Word128) Source # 

Methods

size :: proxy (BE Word128) -> CountOf Word8 Source #

alignment :: proxy (BE Word128) -> CountOf Word8 Source #

Storable (LE Word128) Source # 

Methods

peek :: Ptr (LE Word128) -> IO (LE Word128) Source #

poke :: Ptr (LE Word128) -> LE Word128 -> IO () Source #

Storable (BE Word128) Source # 

Methods

peek :: Ptr (BE Word128) -> IO (BE Word128) Source #

poke :: Ptr (BE Word128) -> BE Word128 -> IO () Source #

type Difference Word128 
type NatNumMaxBound Word128 
type NatNumMaxBound Word128 = 340282366920938463463374607431768211455

data Word256 :: * #

256 bits Word

Instances

Bounded Word256 
Enum Word256 
Eq Word256 

Methods

(==) :: Word256 -> Word256 -> Bool #

(/=) :: Word256 -> Word256 -> Bool #

Num Word256 
Ord Word256 
Show Word256 
Storable Word256 
Bits Word256 
NormalForm Word256 

Methods

toNormalForm :: Word256 -> () #

PrimType Word256 
PrimMemoryComparable Word256 
Multiplicative Word256 
IDivisible Word256 
Additive Word256 

Methods

azero :: Word256 #

(+) :: Word256 -> Word256 -> Word256 #

scale :: IsNatural n => n -> Word256 -> Word256 #

Subtractive Word256 

Associated Types

type Difference Word256 :: * #

IsIntegral Word256 

Methods

toInteger :: Word256 -> Integer #

IsNatural Word256 

Methods

toNatural :: Word256 -> Natural #

Integral Word256 
HasNegation Word256 

Methods

negate :: Word256 -> Word256 #

StorableFixed Word256 Source # 
Storable Word256 Source # 
Arbitrary Word256 Source # 
Hashable Word256 Source # 

Methods

hashMix :: Hasher st => Word256 -> st -> st Source #

StorableFixed (LE Word256) Source # 

Methods

size :: proxy (LE Word256) -> CountOf Word8 Source #

alignment :: proxy (LE Word256) -> CountOf Word8 Source #

StorableFixed (BE Word256) Source # 

Methods

size :: proxy (BE Word256) -> CountOf Word8 Source #

alignment :: proxy (BE Word256) -> CountOf Word8 Source #

Storable (LE Word256) Source # 

Methods

peek :: Ptr (LE Word256) -> IO (LE Word256) Source #

poke :: Ptr (LE Word256) -> LE Word256 -> IO () Source #

Storable (BE Word256) Source # 

Methods

peek :: Ptr (BE Word256) -> IO (BE Word256) Source #

poke :: Ptr (BE Word256) -> BE Word256 -> IO () Source #

type Difference Word256 
type NatNumMaxBound Word256 
type NatNumMaxBound Word256 = 115792089237316195423570985008687907853269984665640564039457584007913129639935

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.

Instances

Bounded Int

Since: 2.1

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: 2.1

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 

Methods

(==) :: Int -> Int -> Bool #

(/=) :: Int -> Int -> Bool #

Integral Int

Since: 2.0.1

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int #

toConstr :: Int -> Constr #

dataTypeOf :: Int -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) #

gmapT :: (forall b. Data b => b -> b) -> Int -> Int #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int #

Num Int

Since: 2.1

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

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

Since: 2.1

Real Int

Since: 2.0.1

Methods

toRational :: Int -> Rational #

Show Int

Since: 2.1

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int

Since: 2.1

Methods

range :: (Int, Int) -> [Int] #

index :: (Int, Int) -> Int -> Int #

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool #

rangeSize :: (Int, Int) -> Int #

unsafeRangeSize :: (Int, Int) -> Int

PrintfArg Int

Since: 2.1

Storable Int

Since: 2.1

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Bits Int

Since: 2.1

Methods

(.&.) :: Int -> Int -> Int #

(.|.) :: Int -> Int -> Int #

xor :: Int -> Int -> Int #

complement :: Int -> Int #

shift :: Int -> Int -> Int #

rotate :: Int -> Int -> Int #

zeroBits :: Int #

bit :: Int -> Int #

setBit :: Int -> Int -> Int #

clearBit :: Int -> Int -> Int #

complementBit :: Int -> Int -> Int #

testBit :: Int -> Int -> Bool #

bitSizeMaybe :: Int -> Maybe Int #

bitSize :: Int -> Int #

isSigned :: Int -> Bool #

shiftL :: Int -> Int -> Int #

unsafeShiftL :: Int -> Int -> Int #

shiftR :: Int -> Int -> Int #

unsafeShiftR :: Int -> Int -> Int #

rotateL :: Int -> Int -> Int #

rotateR :: Int -> Int -> Int #

popCount :: Int -> Int #

FiniteBits Int

Since: 4.6.0.0

NormalForm Int 

Methods

toNormalForm :: Int -> () #

PrimType Int 
PrimMemoryComparable Int 
Multiplicative Int 

Methods

midentity :: Int #

(*) :: Int -> Int -> Int #

(^) :: (IsNatural n, IDivisible n) => Int -> n -> Int #

IDivisible Int 

Methods

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

divMod :: Int -> Int -> (Int, Int) #

Additive Int 

Methods

azero :: Int #

(+) :: Int -> Int -> Int #

scale :: IsNatural n => n -> Int -> Int #

Subtractive Int 

Associated Types

type Difference Int :: * #

Methods

(-) :: Int -> Int -> Difference Int #

IsIntegral Int 

Methods

toInteger :: Int -> Integer #

Integral Int 

Methods

fromInteger :: Integer -> Int #

HasNegation Int 

Methods

negate :: Int -> Int #

Signed Int Source # 

Methods

abs :: Int -> Int Source #

signum :: Int -> Sign Source #

Arbitrary Int Source # 
IntegralDownsize Int Int8 
IntegralDownsize Int Int16 
IntegralDownsize Int Int32 
IntegralDownsize Int64 Int 
IntegralUpsize Int Int64 

Methods

integralUpsize :: Int -> Int64 #

IntegralUpsize Int8 Int 

Methods

integralUpsize :: Int8 -> Int #

IntegralUpsize Int16 Int 

Methods

integralUpsize :: Int16 -> Int #

IntegralUpsize Int32 Int 

Methods

integralUpsize :: Int32 -> Int #

IntegralUpsize Word8 Int 

Methods

integralUpsize :: Word8 -> Int #

IntegralCast Int Word 

Methods

integralCast :: Int -> Word #

IntegralCast Word Int 

Methods

integralCast :: Word -> Int #

IntegralCast Int (Offset ty) 

Methods

integralCast :: Int -> Offset ty #

IntegralCast Int (CountOf ty) 

Methods

integralCast :: Int -> CountOf ty #

Generic1 k (URec k Int) 

Associated Types

type Rep1 (URec k Int) (f :: URec k Int -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Int) f a #

to1 :: Rep1 (URec k Int) f a -> f a #

Functor (URec * Int) 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b #

(<$) :: a -> URec * Int b -> URec * Int a #

Foldable (URec * Int) 

Methods

fold :: Monoid m => URec * Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m #

foldr :: (a -> b -> b) -> b -> URec * Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b #

foldl :: (b -> a -> b) -> b -> URec * Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b #

foldr1 :: (a -> a -> a) -> URec * Int a -> a #

foldl1 :: (a -> a -> a) -> URec * Int a -> a #

toList :: URec * Int a -> [a] #

null :: URec * Int a -> Bool #

length :: URec * Int a -> Int #

elem :: Eq a => a -> URec * Int a -> Bool #

maximum :: Ord a => URec * Int a -> a #

minimum :: Ord a => URec * Int a -> a #

sum :: Num a => URec * Int a -> a #

product :: Num a => URec * Int a -> a #

Traversable (URec * Int) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) #

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) #

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) #

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) #

Eq (URec k Int p) 

Methods

(==) :: URec k Int p -> URec k Int p -> Bool #

(/=) :: URec k Int p -> URec k Int p -> Bool #

Ord (URec k Int p) 

Methods

compare :: URec k Int p -> URec k Int p -> Ordering #

(<) :: URec k Int p -> URec k Int p -> Bool #

(<=) :: URec k Int p -> URec k Int p -> Bool #

(>) :: URec k Int p -> URec k Int p -> Bool #

(>=) :: URec k Int p -> URec k Int p -> Bool #

max :: URec k Int p -> URec k Int p -> URec k Int p #

min :: URec k Int p -> URec k Int p -> URec k Int p #

Show (URec k Int p) 

Methods

showsPrec :: Int -> URec k Int p -> ShowS #

show :: URec k Int p -> String #

showList :: [URec k Int p] -> ShowS #

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

from :: URec k Int p -> Rep (URec k Int p) x #

to :: Rep (URec k Int p) x -> URec k Int p #

type Difference Int 
type NatNumMaxBound Int 
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 Integer :: * #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances

Enum Integer

Since: 2.1

Eq Integer 

Methods

(==) :: Integer -> Integer -> Bool #

(/=) :: Integer -> Integer -> Bool #

Integral Integer

Since: 2.0.1

Data Integer

Since: 4.0.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer #

toConstr :: Integer -> Constr #

dataTypeOf :: Integer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Integer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) #

gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r #

gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer #

Num Integer

Since: 2.1

Ord Integer 
Read Integer

Since: 2.1

Real Integer

Since: 2.0.1

Show Integer

Since: 2.1

Ix Integer

Since: 2.1

PrintfArg Integer

Since: 2.1

Bits Integer

Since: 2.1

NormalForm Integer 

Methods

toNormalForm :: Integer -> () #

Multiplicative Integer 
Multiplicative Rational 
IDivisible Integer 
Divisible Rational 

Methods

(/) :: Rational -> Rational -> Rational #

Additive Integer 

Methods

azero :: Integer #

(+) :: Integer -> Integer -> Integer #

scale :: IsNatural n => n -> Integer -> Integer #

Subtractive Integer 

Associated Types

type Difference Integer :: * #

IsIntegral Integer 

Methods

toInteger :: Integer -> Integer #

Integral Integer 
Fractional Rational 
HasNegation Integer 

Methods

negate :: Integer -> Integer #

IntegralRounding Rational Source # 
Signed Integer Source # 
Arbitrary Integer Source # 
Hashable Integer Source # 

Methods

hashMix :: Hasher st => Integer -> st -> st Source #

IntegralDownsize Integer Int8 
IntegralDownsize Integer Int16 
IntegralDownsize Integer Int32 
IntegralDownsize Integer Int64 
IntegralDownsize Integer Natural 
IntegralDownsize Integer Word8 
IntegralDownsize Integer Word16 
IntegralDownsize Integer Word32 
IntegralDownsize Integer Word64 
IsIntegral a => IntegralUpsize a Integer 

Methods

integralUpsize :: a -> Integer #

type Difference Integer 

data Natural :: * #

Type representing arbitrary-precision non-negative integers.

Operations whose result would be negative throw (Underflow :: ArithException).

Since: 4.8.0.0

Instances

Enum Natural

Since: 4.8.0.0

Eq Natural 

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Integral Natural

Since: 4.8.0.0

Data Natural

Since: 4.8.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural #

toConstr :: Natural -> Constr #

dataTypeOf :: Natural -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Natural) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) #

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r #

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

Num Natural

Since: 4.8.0.0

Ord Natural 
Read Natural

Since: 4.8.0.0

Real Natural

Since: 4.8.0.0

Show Natural

Since: 4.8.0.0

Ix Natural

Since: 4.8.0.0

PrintfArg Natural

Since: 4.8.0.0

Bits Natural

Since: 4.8.0.0

NormalForm Natural 

Methods

toNormalForm :: Natural -> () #

Multiplicative Natural 
IDivisible Natural 
Additive Natural 

Methods

azero :: Natural #

(+) :: Natural -> Natural -> Natural #

scale :: IsNatural n => n -> Natural -> Natural #

Subtractive Natural 

Associated Types

type Difference Natural :: * #

IsIntegral Natural 

Methods

toInteger :: Natural -> Integer #

IsNatural Natural 

Methods

toNatural :: Natural -> Natural #

Integral Natural 
Arbitrary Natural Source # 
Hashable Natural Source # 

Methods

hashMix :: Hasher st => Natural -> st -> st Source #

IntegralDownsize Integer Natural 
IntegralDownsize Natural Word8 
IntegralDownsize Natural Word16 
IntegralDownsize Natural Word32 
IntegralDownsize Natural Word64 
IsNatural a => IntegralUpsize a Natural 

Methods

integralUpsize :: a -> Natural #

type Difference Natural 

type Rational = Ratio Integer #

Arbitrary-precision rational numbers, represented as a ratio of two Integer values. A rational number may be constructed using the % operator.

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.

Instances

Eq Float 

Methods

(==) :: Float -> Float -> Bool #

(/=) :: Float -> Float -> Bool #

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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float #

toConstr :: Float -> Constr #

dataTypeOf :: Float -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Float) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) #

gmapT :: (forall b. Data b => b -> b) -> Float -> Float #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r #

gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float #

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

Since: 2.1

RealFloat Float

Since: 2.1

PrintfArg Float

Since: 2.1

Storable Float

Since: 2.1

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

NormalForm Float 

Methods

toNormalForm :: Float -> () #

PrimType Float 
Multiplicative Float 

Methods

midentity :: Float #

(*) :: Float -> Float -> Float #

(^) :: (IsNatural n, IDivisible n) => Float -> n -> Float #

Divisible Float 

Methods

(/) :: Float -> Float -> Float #

Additive Float 

Methods

azero :: Float #

(+) :: Float -> Float -> Float #

scale :: IsNatural n => n -> Float -> Float #

Subtractive Float 

Associated Types

type Difference Float :: * #

Methods

(-) :: Float -> Float -> Difference Float #

Integral Float 

Methods

fromInteger :: Integer -> Float #

Fractional Float 
HasNegation Float 

Methods

negate :: Float -> Float #

Trigonometry Float Source # 
FloatingPoint Float Source # 
IntegralRounding Float Source # 
Signed Float Source # 
StorableFixed Float Source # 

Methods

size :: proxy Float -> CountOf Word8 Source #

alignment :: proxy Float -> CountOf Word8 Source #

Storable Float Source # 

Methods

peek :: Ptr Float -> IO Float Source #

poke :: Ptr Float -> Float -> IO () Source #

Arbitrary Float Source # 
Generic1 k (URec k Float) 

Associated Types

type Rep1 (URec k Float) (f :: URec k Float -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Float) f a #

to1 :: Rep1 (URec k Float) f a -> f a #

Functor (URec * Float) 

Methods

fmap :: (a -> b) -> URec * Float a -> URec * Float b #

(<$) :: a -> URec * Float b -> URec * Float a #

Foldable (URec * Float) 

Methods

fold :: Monoid m => URec * Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Float a -> m #

foldr :: (a -> b -> b) -> b -> URec * Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Float a -> b #

foldl :: (b -> a -> b) -> b -> URec * Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Float a -> b #

foldr1 :: (a -> a -> a) -> URec * Float a -> a #

foldl1 :: (a -> a -> a) -> URec * Float a -> a #

toList :: URec * Float a -> [a] #

null :: URec * Float a -> Bool #

length :: URec * Float a -> Int #

elem :: Eq a => a -> URec * Float a -> Bool #

maximum :: Ord a => URec * Float a -> a #

minimum :: Ord a => URec * Float a -> a #

sum :: Num a => URec * Float a -> a #

product :: Num a => URec * Float a -> a #

Traversable (URec * Float) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Float a -> f (URec * Float b) #

sequenceA :: Applicative f => URec * Float (f a) -> f (URec * Float a) #

mapM :: Monad m => (a -> m b) -> URec * Float a -> m (URec * Float b) #

sequence :: Monad m => URec * Float (m a) -> m (URec * Float a) #

Eq (URec k Float p) 

Methods

(==) :: URec k Float p -> URec k Float p -> Bool #

(/=) :: URec k Float p -> URec k Float p -> Bool #

Ord (URec k Float p) 

Methods

compare :: URec k Float p -> URec k Float p -> Ordering #

(<) :: URec k Float p -> URec k Float p -> Bool #

(<=) :: URec k Float p -> URec k Float p -> Bool #

(>) :: URec k Float p -> URec k Float p -> Bool #

(>=) :: URec k Float p -> URec k Float p -> Bool #

max :: URec k Float p -> URec k Float p -> URec k Float p #

min :: URec k Float p -> URec k Float p -> URec k Float p #

Show (URec k Float p) 

Methods

showsPrec :: Int -> URec k Float p -> ShowS #

show :: URec k Float p -> String #

showList :: [URec k Float p] -> ShowS #

Generic (URec k Float p) 

Associated Types

type Rep (URec k Float p) :: * -> * #

Methods

from :: URec k Float p -> Rep (URec k Float p) x #

to :: Rep (URec k Float p) x -> URec k Float p #

type Difference Float 
data URec k Float

Used for marking occurrences of Float#

Since: 4.9.0.0

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 :: * #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Eq Double 

Methods

(==) :: Double -> Double -> Bool #

(/=) :: Double -> Double -> Bool #

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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double #

toConstr :: Double -> Constr #

dataTypeOf :: Double -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Double) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) #

gmapT :: (forall b. Data b => b -> b) -> Double -> Double #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r #

gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double #

Ord Double 
Read Double

Since: 2.1

RealFloat Double

Since: 2.1

PrintfArg Double

Since: 2.1

Storable Double

Since: 2.1

NormalForm Double 

Methods

toNormalForm :: Double -> () #

PrimType Double 
Multiplicative Double 

Methods

midentity :: Double #

(*) :: Double -> Double -> Double #

(^) :: (IsNatural n, IDivisible n) => Double -> n -> Double #

Divisible Double 

Methods

(/) :: Double -> Double -> Double #

Additive Double 

Methods

azero :: Double #

(+) :: Double -> Double -> Double #

scale :: IsNatural n => n -> Double -> Double #

Subtractive Double 

Associated Types

type Difference Double :: * #

Integral Double 
Fractional Double 
HasNegation Double 

Methods

negate :: Double -> Double #

Trigonometry Double Source # 
FloatingPoint Double Source # 
IntegralRounding Double Source # 
Signed Double Source # 
StorableFixed Double Source # 
Storable Double Source # 
Arbitrary Double Source # 
Generic1 k (URec k Double) 

Associated Types

type Rep1 (URec k Double) (f :: URec k Double -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Double) f a #

to1 :: Rep1 (URec k Double) f a -> f a #

Functor (URec * Double) 

Methods

fmap :: (a -> b) -> URec * Double a -> URec * Double b #

(<$) :: a -> URec * Double b -> URec * Double a #

Foldable (URec * Double) 

Methods

fold :: Monoid m => URec * Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Double a -> m #

foldr :: (a -> b -> b) -> b -> URec * Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Double a -> b #

foldl :: (b -> a -> b) -> b -> URec * Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Double a -> b #

foldr1 :: (a -> a -> a) -> URec * Double a -> a #

foldl1 :: (a -> a -> a) -> URec * Double a -> a #

toList :: URec * Double a -> [a] #

null :: URec * Double a -> Bool #

length :: URec * Double a -> Int #

elem :: Eq a => a -> URec * Double a -> Bool #

maximum :: Ord a => URec * Double a -> a #

minimum :: Ord a => URec * Double a -> a #

sum :: Num a => URec * Double a -> a #

product :: Num a => URec * Double a -> a #

Traversable (URec * Double) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Double a -> f (URec * Double b) #

sequenceA :: Applicative f => URec * Double (f a) -> f (URec * Double a) #

mapM :: Monad m => (a -> m b) -> URec * Double a -> m (URec * Double b) #

sequence :: Monad m => URec * Double (m a) -> m (URec * Double a) #

Eq (URec k Double p) 

Methods

(==) :: URec k Double p -> URec k Double p -> Bool #

(/=) :: URec k Double p -> URec k Double p -> Bool #

Ord (URec k Double p) 

Methods

compare :: URec k Double p -> URec k Double p -> Ordering #

(<) :: URec k Double p -> URec k Double p -> Bool #

(<=) :: URec k Double p -> URec k Double p -> Bool #

(>) :: URec k Double p -> URec k Double p -> Bool #

(>=) :: URec k Double p -> URec k Double p -> Bool #

max :: URec k Double p -> URec k Double p -> URec k Double p #

min :: URec k Double p -> URec k Double p -> URec k Double p #

Show (URec k Double p) 

Methods

showsPrec :: Int -> URec k Double p -> ShowS #

show :: URec k Double p -> String #

showList :: [URec k Double p] -> ShowS #

Generic (URec k Double p) 

Associated Types

type Rep (URec k Double p) :: * -> * #

Methods

from :: URec k Double p -> Rep (URec k Double p) x #

to :: Rep (URec k Double p) x -> URec k Double p #

type Difference Double 
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 *)))

newtype CountOf ty :: * -> * #

CountOf of a data structure.

More specifically, it represents the number of elements of type ty that fit into the data structure.

>>> length (fromList ['a', 'b', 'c', '🌟']) :: CountOf Char
CountOf 4

Same caveats as Offset apply here.

Constructors

CountOf Int 

Instances

IntegralCast Int (CountOf ty) 

Methods

integralCast :: Int -> CountOf ty #

IntegralCast Word (CountOf ty) 

Methods

integralCast :: Word -> CountOf ty #

Enum (CountOf ty) 

Methods

succ :: CountOf ty -> CountOf ty #

pred :: CountOf ty -> CountOf ty #

toEnum :: Int -> CountOf ty #

fromEnum :: CountOf ty -> Int #

enumFrom :: CountOf ty -> [CountOf ty] #

enumFromThen :: CountOf ty -> CountOf ty -> [CountOf ty] #

enumFromTo :: CountOf ty -> CountOf ty -> [CountOf ty] #

enumFromThenTo :: CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty] #

Eq (CountOf ty) 

Methods

(==) :: CountOf ty -> CountOf ty -> Bool #

(/=) :: CountOf ty -> CountOf ty -> Bool #

Num (CountOf ty) 

Methods

(+) :: CountOf ty -> CountOf ty -> CountOf ty #

(-) :: CountOf ty -> CountOf ty -> CountOf ty #

(*) :: CountOf ty -> CountOf ty -> CountOf ty #

negate :: CountOf ty -> CountOf ty #

abs :: CountOf ty -> CountOf ty #

signum :: CountOf ty -> CountOf ty #

fromInteger :: Integer -> CountOf ty #

Ord (CountOf ty) 

Methods

compare :: CountOf ty -> CountOf ty -> Ordering #

(<) :: CountOf ty -> CountOf ty -> Bool #

(<=) :: CountOf ty -> CountOf ty -> Bool #

(>) :: CountOf ty -> CountOf ty -> Bool #

(>=) :: CountOf ty -> CountOf ty -> Bool #

max :: CountOf ty -> CountOf ty -> CountOf ty #

min :: CountOf ty -> CountOf ty -> CountOf ty #

Show (CountOf ty) 

Methods

showsPrec :: Int -> CountOf ty -> ShowS #

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Semigroup (CountOf ty) 

Methods

(<>) :: CountOf ty -> CountOf ty -> CountOf ty #

sconcat :: NonEmpty (CountOf ty) -> CountOf ty #

stimes :: Integral b => b -> CountOf ty -> CountOf ty #

Monoid (CountOf ty) 

Methods

mempty :: CountOf ty #

mappend :: CountOf ty -> CountOf ty -> CountOf ty #

mconcat :: [CountOf ty] -> CountOf ty #

NormalForm (CountOf a) 

Methods

toNormalForm :: CountOf a -> () #

Additive (CountOf ty) 

Methods

azero :: CountOf ty #

(+) :: CountOf ty -> CountOf ty -> CountOf ty #

scale :: IsNatural n => n -> CountOf ty -> CountOf ty #

Subtractive (CountOf ty) 

Associated Types

type Difference (CountOf ty) :: * #

Methods

(-) :: CountOf ty -> CountOf ty -> Difference (CountOf ty) #

IsIntegral (CountOf ty) 

Methods

toInteger :: CountOf ty -> Integer #

IsNatural (CountOf ty) 

Methods

toNatural :: CountOf ty -> Natural #

Integral (CountOf ty) 

Methods

fromInteger :: Integer -> CountOf ty #

Arbitrary (CountOf ty) Source # 

Methods

arbitrary :: Gen (CountOf ty) Source #

type Difference (CountOf ty) 
type Difference (CountOf ty) = Maybe (CountOf ty)
type NatNumMaxBound (CountOf x) 

newtype Offset ty :: * -> * #

Offset in a data structure consisting of elements of type ty.

Int is a terrible backing type which is hard to get away from, considering that GHC/Haskell are mostly using this for offset. Trying to bring some sanity by a lightweight wrapping.

Constructors

Offset Int 

Instances

IntegralCast Int (Offset ty) 

Methods

integralCast :: Int -> Offset ty #

IntegralCast Word (Offset ty) 

Methods

integralCast :: Word -> Offset ty #

Enum (Offset ty) 

Methods

succ :: Offset ty -> Offset ty #

pred :: Offset ty -> Offset ty #

toEnum :: Int -> Offset ty #

fromEnum :: Offset ty -> Int #

enumFrom :: Offset ty -> [Offset ty] #

enumFromThen :: Offset ty -> Offset ty -> [Offset ty] #

enumFromTo :: Offset ty -> Offset ty -> [Offset ty] #

enumFromThenTo :: Offset ty -> Offset ty -> Offset ty -> [Offset ty] #

Eq (Offset ty) 

Methods

(==) :: Offset ty -> Offset ty -> Bool #

(/=) :: Offset ty -> Offset ty -> Bool #

Num (Offset ty) 

Methods

(+) :: Offset ty -> Offset ty -> Offset ty #

(-) :: Offset ty -> Offset ty -> Offset ty #

(*) :: Offset ty -> Offset ty -> Offset ty #

negate :: Offset ty -> Offset ty #

abs :: Offset ty -> Offset ty #

signum :: Offset ty -> Offset ty #

fromInteger :: Integer -> Offset ty #

Ord (Offset ty) 

Methods

compare :: Offset ty -> Offset ty -> Ordering #

(<) :: Offset ty -> Offset ty -> Bool #

(<=) :: Offset ty -> Offset ty -> Bool #

(>) :: Offset ty -> Offset ty -> Bool #

(>=) :: Offset ty -> Offset ty -> Bool #

max :: Offset ty -> Offset ty -> Offset ty #

min :: Offset ty -> Offset ty -> Offset ty #

Show (Offset ty) 

Methods

showsPrec :: Int -> Offset ty -> ShowS #

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

NormalForm (Offset a) 

Methods

toNormalForm :: Offset a -> () #

Additive (Offset ty) 

Methods

azero :: Offset ty #

(+) :: Offset ty -> Offset ty -> Offset ty #

scale :: IsNatural n => n -> Offset ty -> Offset ty #

Subtractive (Offset ty) 

Associated Types

type Difference (Offset ty) :: * #

Methods

(-) :: Offset ty -> Offset ty -> Difference (Offset ty) #

IsIntegral (Offset ty) 

Methods

toInteger :: Offset ty -> Integer #

IsNatural (Offset ty) 

Methods

toNatural :: Offset ty -> Natural #

Integral (Offset ty) 

Methods

fromInteger :: Integer -> Offset ty #

type Difference (Offset ty) 
type Difference (Offset ty) = CountOf ty
type NatNumMaxBound (Offset x) 

Collection types

data UArray ty :: * -> * #

An array of type built on top of GHC primitive.

The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface

Instances

PrimType ty => IsList (UArray ty) 

Associated Types

type Item (UArray ty) :: * #

Methods

fromList :: [Item (UArray ty)] -> UArray ty #

fromListN :: Int -> [Item (UArray ty)] -> UArray ty #

toList :: UArray ty -> [Item (UArray ty)] #

(PrimType ty, Eq ty) => Eq (UArray ty) 

Methods

(==) :: UArray ty -> UArray ty -> Bool #

(/=) :: UArray ty -> UArray ty -> Bool #

Data ty => Data (UArray ty) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UArray ty -> c (UArray ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray ty) #

toConstr :: UArray ty -> Constr #

dataTypeOf :: UArray ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (UArray ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UArray ty)) #

gmapT :: (forall b. Data b => b -> b) -> UArray ty -> UArray ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UArray ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> UArray ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UArray ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UArray ty -> m (UArray ty) #

(PrimType ty, Ord ty) => Ord (UArray ty) 

Methods

compare :: UArray ty -> UArray ty -> Ordering #

(<) :: UArray ty -> UArray ty -> Bool #

(<=) :: UArray ty -> UArray ty -> Bool #

(>) :: UArray ty -> UArray ty -> Bool #

(>=) :: UArray ty -> UArray ty -> Bool #

max :: UArray ty -> UArray ty -> UArray ty #

min :: UArray ty -> UArray ty -> UArray ty #

(PrimType ty, Show ty) => Show (UArray ty) 

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Semigroup (UArray ty) 

Methods

(<>) :: UArray ty -> UArray ty -> UArray ty #

sconcat :: NonEmpty (UArray ty) -> UArray ty #

stimes :: Integral b => b -> UArray ty -> UArray ty #

PrimType ty => Monoid (UArray ty) 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

NormalForm (UArray ty) 

Methods

toNormalForm :: UArray ty -> () #

PrimType ty => Copy (UArray ty) Source # 

Methods

copy :: UArray ty -> UArray ty Source #

PrimType ty => Collection (UArray ty) Source # 

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> CountOf (Element (UArray ty)) Source #

elem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

minimum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

any :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

all :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

PrimType ty => Buildable (UArray ty) Source # 

Associated Types

type Mutable (UArray ty) :: * -> * Source #

type Step (UArray ty) :: * Source #

Methods

append :: PrimMonad prim => Element (UArray ty) -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () -> prim (Either err (UArray ty)) Source #

PrimType ty => Fold1able (UArray ty) Source # 

Methods

foldl1' :: (Element (UArray ty) -> Element (UArray ty) -> Element (UArray ty)) -> NonEmpty (UArray ty) -> Element (UArray ty) Source #

foldr1 :: (Element (UArray ty) -> Element (UArray ty) -> Element (UArray ty)) -> NonEmpty (UArray ty) -> Element (UArray ty) Source #

PrimType ty => Foldable (UArray ty) Source # 

Methods

foldl' :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => IndexedCollection (UArray ty) Source # 

Methods

(!) :: UArray ty -> Offset (Element (UArray ty)) -> Maybe (Element (UArray ty)) Source #

findIndex :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Offset (Element (UArray ty))) Source #

PrimType ty => InnerFunctor (UArray ty) Source # 

Methods

imap :: (Element (UArray ty) -> Element (UArray ty)) -> UArray ty -> UArray ty Source #

PrimType ty => Sequential (UArray ty) Source # 

Methods

take :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

splitOn :: (Element (UArray ty) -> Bool) -> UArray ty -> [UArray ty] Source #

break :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakElem :: Element (UArray ty) -> UArray ty -> (UArray ty, UArray ty) Source #

takeWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

dropWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

intersperse :: Element (UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element (UArray ty) -> UArray ty -> Element (UArray ty) Source #

span :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

spanEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

filter :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

partition :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe (Element (UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe (UArray ty, Element (UArray ty)) Source #

snoc :: UArray ty -> Element (UArray ty) -> UArray ty Source #

cons :: Element (UArray ty) -> UArray ty -> UArray ty Source #

find :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Element (UArray ty)) Source #

sortBy :: (Element (UArray ty) -> Element (UArray ty) -> Ordering) -> UArray ty -> UArray ty Source #

singleton :: Element (UArray ty) -> UArray ty Source #

head :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

last :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

tail :: NonEmpty (UArray ty) -> UArray ty Source #

init :: NonEmpty (UArray ty) -> UArray ty Source #

replicate :: CountOf (Element (UArray ty)) -> Element (UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

stripPrefix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

PrimType ty => Zippable (UArray ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (UArray ty)) -> a -> b -> UArray ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (UArray ty)) -> a -> b -> c -> UArray ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (UArray ty)) -> a -> b -> c -> d -> UArray ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (UArray ty)) -> a -> b -> c -> d -> e -> UArray ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> UArray ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> g -> UArray ty Source #

PrimType a => Hashable (UArray a) Source # 

Methods

hashMix :: Hasher st => UArray a -> st -> st Source #

type Item (UArray ty) 
type Item (UArray ty) = ty
type Element (UArray ty) Source # 
type Element (UArray ty) = ty
type Mutable (UArray ty) Source # 
type Mutable (UArray ty) = MUArray ty
type Step (UArray ty) Source # 
type Step (UArray ty) = ty

class Eq ty => PrimType ty #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Instances

PrimType Char 
PrimType Double 
PrimType Float 
PrimType Int 
PrimType Int8 
PrimType Int16 
PrimType Int32 
PrimType Int64 
PrimType Word 
PrimType Word8 
PrimType Word16 
PrimType Word32 
PrimType Word64 
PrimType CChar 
PrimType CUChar 
PrimType Word256 
PrimType Word128 
PrimType Char7 
PrimType Seconds # 
PrimType NanoSeconds # 
PrimType a => PrimType (LE a) 

Methods

primSizeInBytes :: Proxy * (LE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (LE a) -> Int #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () #

PrimType a => PrimType (BE a) 

Methods

primSizeInBytes :: Proxy * (BE a) -> CountOf Word8 #

primShiftToBytes :: Proxy * (BE a) -> Int #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () #

data Array a :: * -> * #

Array of a

Instances

Functor Array 

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

Mappable Array Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) Source #

sequenceA :: Applicative f => Array (f a) -> f (Array a) Source #

mapM :: (Applicative m, Monad m) => (a -> m b) -> Array a -> m (Array b) Source #

sequence :: (Applicative m, Monad m) => Array (m a) -> m (Array a) Source #

IsList (Array ty) 

Associated Types

type Item (Array ty) :: * #

Methods

fromList :: [Item (Array ty)] -> Array ty #

fromListN :: Int -> [Item (Array ty)] -> Array ty #

toList :: Array ty -> [Item (Array ty)] #

Eq a => Eq (Array a) 

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

Data ty => Data (Array ty) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array ty -> c (Array ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array ty) #

toConstr :: Array ty -> Constr #

dataTypeOf :: Array ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Array ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array ty)) #

gmapT :: (forall b. Data b => b -> b) -> Array ty -> Array ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Array ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Array ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array ty -> m (Array ty) #

Ord a => Ord (Array a) 

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

Show a => Show (Array a) 

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Semigroup (Array a) 

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

NormalForm a => NormalForm (Array a) 

Methods

toNormalForm :: Array a -> () #

Copy (Array ty) Source # 

Methods

copy :: Array ty -> Array ty Source #

Collection (Array ty) Source # 

Methods

null :: Array ty -> Bool Source #

length :: Array ty -> CountOf (Element (Array ty)) Source #

elem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

any :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

all :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

Buildable (Array ty) Source # 

Associated Types

type Mutable (Array ty) :: * -> * Source #

type Step (Array ty) :: * Source #

Methods

append :: PrimMonad prim => Element (Array ty) -> Builder (Array ty) (Mutable (Array ty)) (Step (Array ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder (Array ty) (Mutable (Array ty)) (Step (Array ty)) prim err () -> prim (Either err (Array ty)) Source #

Fold1able (Array ty) Source # 

Methods

foldl1' :: (Element (Array ty) -> Element (Array ty) -> Element (Array ty)) -> NonEmpty (Array ty) -> Element (Array ty) Source #

foldr1 :: (Element (Array ty) -> Element (Array ty) -> Element (Array ty)) -> NonEmpty (Array ty) -> Element (Array ty) Source #

Foldable (Array ty) Source # 

Methods

foldl' :: (a -> Element (Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

IndexedCollection (Array ty) Source # 

Methods

(!) :: Array ty -> Offset (Element (Array ty)) -> Maybe (Element (Array ty)) Source #

findIndex :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Offset (Element (Array ty))) Source #

InnerFunctor (Array ty) Source # 

Methods

imap :: (Element (Array ty) -> Element (Array ty)) -> Array ty -> Array ty Source #

Sequential (Array ty) Source # 

Methods

take :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

revSplitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

splitOn :: (Element (Array ty) -> Bool) -> Array ty -> [Array ty] Source #

break :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakEnd :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakElem :: Element (Array ty) -> Array ty -> (Array ty, Array ty) Source #

takeWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

dropWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

intersperse :: Element (Array ty) -> Array ty -> Array ty Source #

intercalate :: Element (Array ty) -> Array ty -> Element (Array ty) Source #

span :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

spanEnd :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

filter :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

partition :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe (Element (Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe (Array ty, Element (Array ty)) Source #

snoc :: Array ty -> Element (Array ty) -> Array ty Source #

cons :: Element (Array ty) -> Array ty -> Array ty Source #

find :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Element (Array ty)) Source #

sortBy :: (Element (Array ty) -> Element (Array ty) -> Ordering) -> Array ty -> Array ty Source #

singleton :: Element (Array ty) -> Array ty Source #

head :: NonEmpty (Array ty) -> Element (Array ty) Source #

last :: NonEmpty (Array ty) -> Element (Array ty) Source #

tail :: NonEmpty (Array ty) -> Array ty Source #

init :: NonEmpty (Array ty) -> Array ty Source #

replicate :: CountOf (Element (Array ty)) -> Element (Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

isInfixOf :: Array ty -> Array ty -> Bool Source #

stripPrefix :: Array ty -> Array ty -> Maybe (Array ty) Source #

stripSuffix :: Array ty -> Array ty -> Maybe (Array ty) Source #

BoxedZippable (Array ty) Source # 

Methods

zip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => a -> b -> Array ty Source #

zip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => a -> b -> c -> Array ty Source #

zip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> Array ty Source #

zip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> Array ty Source #

zip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> Array ty Source #

zip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> Array ty Source #

unzip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => Array ty -> (a, b) Source #

unzip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => Array ty -> (a, b, c) Source #

unzip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => Array ty -> (a, b, c, d) Source #

unzip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => Array ty -> (a, b, c, d, e) Source #

unzip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => Array ty -> (a, b, c, d, e, f) Source #

unzip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => Array ty -> (a, b, c, d, e, f, g) Source #

Zippable (Array ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (Array ty)) -> a -> b -> Array ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (Array ty)) -> a -> b -> c -> Array ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (Array ty)) -> a -> b -> c -> d -> Array ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (Array ty)) -> a -> b -> c -> d -> e -> Array ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> Array ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> g -> Array ty Source #

Hashable a => Hashable (Array a) Source # 

Methods

hashMix :: Hasher st => Array a -> st -> st Source #

type Item (Array ty) 
type Item (Array ty) = ty
type Element (Array ty) Source # 
type Element (Array ty) = ty
type Mutable (Array ty) Source # 
type Mutable (Array ty) = MArray ty
type Step (Array ty) Source # 
type Step (Array ty) = ty

data String :: * #

Opaque packed array of characters in the UTF8 encoding

Instances

IsList String 

Associated Types

type Item String :: * #

Eq String 

Methods

(==) :: String -> String -> Bool #

(/=) :: String -> String -> Bool #

Data String 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> String -> c String #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c String #

toConstr :: String -> Constr #

dataTypeOf :: String -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c String) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c String) #

gmapT :: (forall b. Data b => b -> b) -> String -> String #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> String -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> String -> r #

gmapQ :: (forall d. Data d => d -> u) -> String -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> String -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> String -> m String #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> String -> m String #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> String -> m String #

Ord String 
Show String 
IsString String 

Methods

fromString :: String -> String #

Semigroup String 
Monoid String 
NormalForm String 

Methods

toNormalForm :: String -> () #

Copy String Source # 

Methods

copy :: String -> String Source #

Collection String Source # 
Buildable String Source # 

Associated Types

type Mutable String :: * -> * Source #

type Step String :: * Source #

Methods

append :: PrimMonad prim => Element String -> Builder String (Mutable String) (Step String) prim err () Source #

build :: PrimMonad prim => Int -> Builder String (Mutable String) (Step String) prim err () -> prim (Either err String) Source #

IndexedCollection String Source # 
InnerFunctor String Source # 
Sequential String Source # 

Methods

take :: CountOf (Element String) -> String -> String Source #

revTake :: CountOf (Element String) -> String -> String Source #

drop :: CountOf (Element String) -> String -> String Source #

revDrop :: CountOf (Element String) -> String -> String Source #

splitAt :: CountOf (Element String) -> String -> (String, String) Source #

revSplitAt :: CountOf (Element String) -> String -> (String, String) Source #

splitOn :: (Element String -> Bool) -> String -> [String] Source #

break :: (Element String -> Bool) -> String -> (String, String) Source #

breakEnd :: (Element String -> Bool) -> String -> (String, String) Source #

breakElem :: Element String -> String -> (String, String) Source #

takeWhile :: (Element String -> Bool) -> String -> String Source #

dropWhile :: (Element String -> Bool) -> String -> String Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: (Element String -> Bool) -> String -> (String, String) Source #

spanEnd :: (Element String -> Bool) -> String -> (String, String) Source #

filter :: (Element String -> Bool) -> String -> String Source #

partition :: (Element String -> Bool) -> String -> (String, String) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe (Element String, String) Source #

unsnoc :: String -> Maybe (String, Element String) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: (Element String -> Bool) -> String -> Maybe (Element String) Source #

sortBy :: (Element String -> Element String -> Ordering) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

replicate :: CountOf (Element String) -> Element String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Zippable String Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element String) -> a -> b -> String Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element String) -> a -> b -> c -> String Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element String) -> a -> b -> c -> d -> String Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element String) -> a -> b -> c -> d -> e -> String Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element String) -> a -> b -> c -> d -> e -> f -> String Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element String) -> a -> b -> c -> d -> e -> f -> g -> String Source #

ParserSource String Source # 
Arbitrary String Source # 
Hashable String Source # 

Methods

hashMix :: Hasher st => String -> st -> st Source #

IsProperty (String, Bool) Source # 
type Item String 
type Element String Source # 
type Mutable String Source # 
type Step String Source # 
type Chunk String Source # 

Numeric functions

(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 #

raise a number to an integral power

fromIntegral :: (Integral a, Num b) => a -> b #

general coercion from integral types

realToFrac :: (Real a, Fractional b) => a -> b #

general coercion to fractional types

Monoids

class Semigroup a #

The class of semigroups (types with an associative binary operation).

Since: 4.9.0.0

Instances

Semigroup Ordering

Since: 4.9.0.0

Semigroup ()

Since: 4.9.0.0

Methods

(<>) :: () -> () -> () #

sconcat :: NonEmpty () -> () #

stimes :: Integral b => b -> () -> () #

Semigroup Void

Since: 4.9.0.0

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Semigroup Event

Since: 4.10.0.0

Methods

(<>) :: Event -> Event -> Event #

sconcat :: NonEmpty Event -> Event #

stimes :: Integral b => b -> Event -> Event #

Semigroup Lifetime

Since: 4.10.0.0

Semigroup All

Since: 4.9.0.0

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Semigroup Any

Since: 4.9.0.0

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Semigroup String 
Semigroup AsciiString 
Semigroup Bitmap # 
Semigroup Builder # 
Semigroup FileName # 
Semigroup [a]

Since: 4.9.0.0

Methods

(<>) :: [a] -> [a] -> [a] #

sconcat :: NonEmpty [a] -> [a] #

stimes :: Integral b => b -> [a] -> [a] #

Semigroup a => Semigroup (Maybe a)

Since: 4.9.0.0

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Semigroup (IO a)

Since: 4.10.0.0

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

Ord a => Semigroup (Min a)

Since: 4.9.0.0

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

Ord a => Semigroup (Max a)

Since: 4.9.0.0

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

Semigroup (First a)

Since: 4.9.0.0

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: 4.9.0.0

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid m => Semigroup (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Semigroup (Option a)

Since: 4.9.0.0

Methods

(<>) :: Option a -> Option a -> Option a #

sconcat :: NonEmpty (Option a) -> Option a #

stimes :: Integral b => b -> Option a -> Option a #

Semigroup (NonEmpty a)

Since: 4.9.0.0

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Semigroup a => Semigroup (Identity a)

Since: 4.9.0.0

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Semigroup a => Semigroup (Dual a)

Since: 4.9.0.0

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Semigroup (Endo a)

Since: 4.9.0.0

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Num a => Semigroup (Sum a)

Since: 4.9.0.0

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Semigroup (Product a)

Since: 4.9.0.0

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Semigroup (First a)

Since: 4.9.0.0

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: 4.9.0.0

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Semigroup (Array a) 

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

PrimType ty => Semigroup (UArray ty) 

Methods

(<>) :: UArray ty -> UArray ty -> UArray ty #

sconcat :: NonEmpty (UArray ty) -> UArray ty #

stimes :: Integral b => b -> UArray ty -> UArray ty #

PrimType ty => Semigroup (Block ty) 

Methods

(<>) :: Block ty -> Block ty -> Block ty #

sconcat :: NonEmpty (Block ty) -> Block ty #

stimes :: Integral b => b -> Block ty -> Block ty #

Semigroup (CountOf ty) 

Methods

(<>) :: CountOf ty -> CountOf ty -> CountOf ty #

sconcat :: NonEmpty (CountOf ty) -> CountOf ty #

stimes :: Integral b => b -> CountOf ty -> CountOf ty #

Semigroup (DList a) # 

Methods

(<>) :: DList a -> DList a -> DList a #

sconcat :: NonEmpty (DList a) -> DList a #

stimes :: Integral b => b -> DList a -> DList a #

Semigroup (ChunkedUArray a) # 
Semigroup b => Semigroup (a -> b)

Since: 4.9.0.0

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b #

sconcat :: NonEmpty (a -> b) -> a -> b #

stimes :: Integral b => b -> (a -> b) -> a -> b #

Semigroup (Either a b)

Since: 4.9.0.0

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b => b -> Either a b -> Either a b #

(Semigroup a, Semigroup b) => Semigroup (a, b)

Since: 4.9.0.0

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) #

sconcat :: NonEmpty (a, b) -> (a, b) #

stimes :: Integral b => b -> (a, b) -> (a, b) #

Semigroup (Proxy k s)

Since: 4.9.0.0

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) #

stimes :: Integral b => b -> (a, b, c) -> (a, b, c) #

Semigroup a => Semigroup (Const k a b)

Since: 4.9.0.0

Methods

(<>) :: Const k a b -> Const k a b -> Const k a b #

sconcat :: NonEmpty (Const k a b) -> Const k a b #

stimes :: Integral b => b -> Const k a b -> Const k a b #

Alternative f => Semigroup (Alt * f a)

Since: 4.9.0.0

Methods

(<>) :: Alt * f a -> Alt * f a -> Alt * f a #

sconcat :: NonEmpty (Alt * f a) -> Alt * f a #

stimes :: Integral b => b -> Alt * f a -> Alt * f a #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) #

stimes :: Integral b => b -> (a, b, c, d) -> (a, b, c, d) #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) #

stimes :: Integral b => b -> (a, b, c, d, e) -> (a, b, c, d, e) #

class Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

mconcat :: [a] -> a #

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering

Since: 2.1

Monoid ()

Since: 2.1

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid EventLifetime

Since: 4.8.0.0

Methods

mempty :: EventLifetime #

mappend :: EventLifetime -> EventLifetime -> EventLifetime #

mconcat :: [EventLifetime] -> EventLifetime #

Monoid Event

Since: 4.3.1.0

Methods

mempty :: Event #

mappend :: Event -> Event -> Event #

mconcat :: [Event] -> Event #

Monoid Lifetime

mappend takes the longer of two lifetimes.

Since: 4.8.0.0

Monoid All

Since: 2.1

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: 2.1

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid String 
Monoid AsciiString 
Monoid Bitmap # 
Monoid Builder # 
Monoid FileName # 
Monoid [a]

Since: 2.1

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there used to be no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Since: 2.1

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

(Ord a, Bounded a) => Monoid (Min a)

Since: 4.9.0.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: 4.9.0.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Monoid (Option a)

Since: 4.9.0.0

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid a => Monoid (Dual a)

Since: 2.1

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: 2.1

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: 2.1

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: 2.1

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a)

Since: 2.1

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: 2.1

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

PrimType ty => Monoid (UArray ty) 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

PrimType ty => Monoid (Block ty) 

Methods

mempty :: Block ty #

mappend :: Block ty -> Block ty -> Block ty #

mconcat :: [Block ty] -> Block ty #

Monoid (CountOf ty) 

Methods

mempty :: CountOf ty #

mappend :: CountOf ty -> CountOf ty -> CountOf ty #

mconcat :: [CountOf ty] -> CountOf ty #

Monoid (DList a) # 

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

mconcat :: [DList a] -> DList a #

Monoid (ChunkedUArray a) # 
Monoid b => Monoid (a -> b)

Since: 2.1

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: 2.1

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: 2.1

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a)

Since: 4.8.0.0

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: 2.1

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: 2.1

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

Collection

class (IsList c, Item c ~ Element c) => Collection c where Source #

A set of methods for ordered colection

Minimal complete definition

null, length, (elem | notElem), minimum, maximum, all, any

Methods

null :: c -> Bool Source #

Check if a collection is empty

length :: c -> CountOf (Element c) Source #

Length of a collection (number of Element c)

elem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection contains a specific element

This is the inverse of notElem.

notElem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection does *not* contain a specific element

This is the inverse of elem.

maximum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the maximum element of a collection

minimum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the minimum element of a collection

any :: (Element c -> Bool) -> c -> Bool Source #

Determine is any elements of the collection satisfy the predicate

all :: (Element c -> Bool) -> c -> Bool Source #

Determine is all elements of the collection satisfy the predicate

Instances

Collection String Source # 
Collection AsciiString Source # 
Collection Bitmap Source # 
Collection [a] Source # 

Methods

null :: [a] -> Bool Source #

length :: [a] -> CountOf (Element [a]) Source #

elem :: (Eq a, (* ~ a) (Element [a])) => Element [a] -> [a] -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element [a])) => Element [a] -> [a] -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element [a])) => NonEmpty [a] -> Element [a] Source #

minimum :: (Ord a, (* ~ a) (Element [a])) => NonEmpty [a] -> Element [a] Source #

any :: (Element [a] -> Bool) -> [a] -> Bool Source #

all :: (Element [a] -> Bool) -> [a] -> Bool Source #

Collection (Array ty) Source # 

Methods

null :: Array ty -> Bool Source #

length :: Array ty -> CountOf (Element (Array ty)) Source #

elem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

any :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

all :: (Element (Array ty) -> Bool) -> Array ty -> Bool Source #

PrimType ty => Collection (UArray ty) Source # 

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> CountOf (Element (UArray ty)) Source #

elem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

minimum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

any :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

all :: (Element (UArray ty) -> Bool) -> UArray ty -> Bool Source #

PrimType ty => Collection (Block ty) Source # 

Methods

null :: Block ty -> Bool Source #

length :: Block ty -> CountOf (Element (Block ty)) Source #

elem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) Source #

any :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

all :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

Collection c => Collection (NonEmpty c) Source # 

Methods

null :: NonEmpty c -> Bool Source #

length :: NonEmpty c -> CountOf (Element (NonEmpty c)) Source #

elem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

minimum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

any :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source #

all :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source #

Collection (DList a) Source # 

Methods

null :: DList a -> Bool Source #

length :: DList a -> CountOf (Element (DList a)) Source #

elem :: (Eq a, (* ~ a) (Element (DList a))) => Element (DList a) -> DList a -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (DList a))) => Element (DList a) -> DList a -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (DList a))) => NonEmpty (DList a) -> Element (DList a) Source #

minimum :: (Ord a, (* ~ a) (Element (DList a))) => NonEmpty (DList a) -> Element (DList a) Source #

any :: (Element (DList a) -> Bool) -> DList a -> Bool Source #

all :: (Element (DList a) -> Bool) -> DList a -> Bool Source #

PrimType ty => Collection (ChunkedUArray ty) Source # 

and :: (Collection col, Element col ~ Bool) => col -> Bool Source #

Return True if all the elements in the collection are True

or :: (Collection col, Element col ~ Bool) => col -> Bool Source #

Return True if at least one element in the collection is True

class (IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where Source #

A set of methods for ordered colection

Methods

take :: CountOf (Element c) -> c -> c Source #

Take the first @n elements of a collection

revTake :: CountOf (Element c) -> c -> c Source #

Take the last @n elements of a collection

drop :: CountOf (Element c) -> c -> c Source #

Drop the first @n elements of a collection

revDrop :: CountOf (Element c) -> c -> c Source #

Drop the last @n elements of a collection

splitAt :: CountOf (Element c) -> c -> (c, c) Source #

Split the collection at the @n'th elements

revSplitAt :: CountOf (Element c) -> c -> (c, c) Source #

Split the collection at the @n'th elements from the end

splitOn :: (Element c -> Bool) -> c -> [c] Source #

Split on a specific elements returning a list of colletion

break :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection when the predicate return true

breakEnd :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection when the predicate return true

breakElem :: Eq (Element c) => Element c -> c -> (c, c) Source #

Split a collection when the predicate return true starting from the end of the collection

takeWhile :: (Element c -> Bool) -> c -> c Source #

Return the longest prefix in the collection that satisfy the predicate

dropWhile :: (Element c -> Bool) -> c -> c Source #

Return the longest prefix in the collection that satisfy the predicate

intersperse :: Element c -> c -> c Source #

The intersperse function takes an element and a list and `intersperses' that element between the elements of the list. For example,

intersperse ',' "abcde" == "a,b,c,d,e"

intercalate :: Monoid (Item c) => Element c -> c -> Element c Source #

intercalate xs xss is equivalent to (mconcat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

span :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection while the predicate return true

spanEnd :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection while the predicate return true starting from the end of the collection

filter :: (Element c -> Bool) -> c -> c Source #

Filter all the elements that satisfy the predicate

partition :: (Element c -> Bool) -> c -> (c, c) Source #

Partition the elements thtat satisfy the predicate and those that don't

reverse :: c -> c Source #

Reverse a collection

uncons :: c -> Maybe (Element c, c) Source #

Decompose a collection into its first element and the remaining collection. If the collection is empty, returns Nothing.

unsnoc :: c -> Maybe (c, Element c) Source #

Decompose a collection into a collection without its last element, and the last element If the collection is empty, returns Nothing.

snoc :: c -> Element c -> c Source #

Prepend an element to an ordered collection

cons :: Element c -> c -> c Source #

Append an element to an ordered collection

find :: (Element c -> Bool) -> c -> Maybe (Element c) Source #

Find an element in an ordered collection

sortBy :: (Element c -> Element c -> Ordering) -> c -> c Source #

Sort an ordered collection using the specified order function

singleton :: Element c -> c Source #

Create a collection with a single element

head :: NonEmpty c -> Element c Source #

get the first element of a non-empty collection

last :: NonEmpty c -> Element c Source #

get the last element of a non-empty collection

tail :: NonEmpty c -> c Source #

Extract the elements after the first element of a non-empty collection.

init :: NonEmpty c -> c Source #

Extract the elements before the last element of a non-empty collection.

replicate :: CountOf (Element c) -> Element c -> c Source #

Create a collection where the element in parameter is repeated N time

isPrefixOf :: Eq (Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a prefix of the second.

isPrefixOf :: Eq c => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a prefix of the second.

isSuffixOf :: Eq (Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a suffix of the second.

isSuffixOf :: Eq c => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a suffix of the second.

isInfixOf :: Eq (Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is an infix of the second.

isInfixOf :: Eq c => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is an infix of the second.

stripPrefix :: Eq (Element c) => c -> c -> Maybe c Source #

Try to strip a prefix from a collection

stripSuffix :: Eq (Element c) => c -> c -> Maybe c Source #

Try to strip a suffix from a collection

Instances

Sequential String Source # 

Methods

take :: CountOf (Element String) -> String -> String Source #

revTake :: CountOf (Element String) -> String -> String Source #

drop :: CountOf (Element String) -> String -> String Source #

revDrop :: CountOf (Element String) -> String -> String Source #

splitAt :: CountOf (Element String) -> String -> (String, String) Source #

revSplitAt :: CountOf (Element String) -> String -> (String, String) Source #

splitOn :: (Element String -> Bool) -> String -> [String] Source #

break :: (Element String -> Bool) -> String -> (String, String) Source #

breakEnd :: (Element String -> Bool) -> String -> (String, String) Source #

breakElem :: Element String -> String -> (String, String) Source #

takeWhile :: (Element String -> Bool) -> String -> String Source #

dropWhile :: (Element String -> Bool) -> String -> String Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: (Element String -> Bool) -> String -> (String, String) Source #

spanEnd :: (Element String -> Bool) -> String -> (String, String) Source #

filter :: (Element String -> Bool) -> String -> String Source #

partition :: (Element String -> Bool) -> String -> (String, String) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe (Element String, String) Source #

unsnoc :: String -> Maybe (String, Element String) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: (Element String -> Bool) -> String -> Maybe (Element String) Source #

sortBy :: (Element String -> Element String -> Ordering) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

replicate :: CountOf (Element String) -> Element String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Sequential AsciiString Source # 

Methods

take :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

revTake :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

drop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

revDrop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

splitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) Source #

revSplitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) Source #

splitOn :: (Element AsciiString -> Bool) -> AsciiString -> [AsciiString] Source #

break :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

breakEnd :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

breakElem :: Element AsciiString -> AsciiString -> (AsciiString, AsciiString) Source #

takeWhile :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString Source #

dropWhile :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString Source #

intersperse :: Element AsciiString -> AsciiString -> AsciiString Source #

intercalate :: Element AsciiString -> AsciiString -> Element AsciiString Source #

span :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

spanEnd :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

filter :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString Source #

partition :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

reverse :: AsciiString -> AsciiString Source #

uncons :: AsciiString -> Maybe (Element AsciiString, AsciiString) Source #

unsnoc :: AsciiString -> Maybe (AsciiString, Element AsciiString) Source #

snoc :: AsciiString -> Element AsciiString -> AsciiString Source #

cons :: Element AsciiString -> AsciiString -> AsciiString Source #

find :: (Element AsciiString -> Bool) -> AsciiString -> Maybe (Element AsciiString) Source #

sortBy :: (Element AsciiString -> Element AsciiString -> Ordering) -> AsciiString -> AsciiString Source #

singleton :: Element AsciiString -> AsciiString Source #

head :: NonEmpty AsciiString -> Element AsciiString Source #

last :: NonEmpty AsciiString -> Element AsciiString Source #

tail :: NonEmpty AsciiString -> AsciiString Source #

init :: NonEmpty AsciiString -> AsciiString Source #

replicate :: CountOf (Element AsciiString) -> Element AsciiString -> AsciiString Source #

isPrefixOf :: AsciiString -> AsciiString -> Bool Source #

isSuffixOf :: AsciiString -> AsciiString -> Bool Source #

isInfixOf :: AsciiString -> AsciiString -> Bool Source #

stripPrefix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

stripSuffix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

Sequential Bitmap Source # 

Methods

take :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revTake :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

drop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revDrop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

splitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

revSplitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

splitOn :: (Element Bitmap -> Bool) -> Bitmap -> [Bitmap] Source #

break :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

breakEnd :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

breakElem :: Element Bitmap -> Bitmap -> (Bitmap, Bitmap) Source #

takeWhile :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

dropWhile :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

intersperse :: Element Bitmap -> Bitmap -> Bitmap Source #

intercalate :: Element Bitmap -> Bitmap -> Element Bitmap Source #

span :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

spanEnd :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

filter :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

partition :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

reverse :: Bitmap -> Bitmap Source #

uncons :: Bitmap -> Maybe (Element Bitmap, Bitmap) Source #

unsnoc :: Bitmap -> Maybe (Bitmap, Element Bitmap) Source #

snoc :: Bitmap -> Element Bitmap -> Bitmap Source #

cons :: Element Bitmap -> Bitmap -> Bitmap Source #

find :: (Element Bitmap -> Bool) -> Bitmap -> Maybe (Element Bitmap) Source #

sortBy :: (Element Bitmap -> Element Bitmap -> Ordering) -> Bitmap -> Bitmap Source #

singleton :: Element Bitmap -> Bitmap Source #

head :: NonEmpty Bitmap -> Element Bitmap Source #

last :: NonEmpty Bitmap -> Element Bitmap Source #

tail :: NonEmpty Bitmap -> Bitmap Source #

init :: NonEmpty Bitmap -> Bitmap Source #

replicate :: CountOf (Element Bitmap) -> Element Bitmap -> Bitmap Source #

isPrefixOf :: Bitmap -> Bitmap -> Bool Source #

isSuffixOf :: Bitmap -> Bitmap -> Bool Source #

isInfixOf :: Bitmap -> Bitmap -> Bool Source #

stripPrefix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

stripSuffix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

Sequential [a] Source # 

Methods

take :: CountOf (Element [a]) -> [a] -> [a] Source #

revTake :: CountOf (Element [a]) -> [a] -> [a] Source #

drop :: CountOf (Element [a]) -> [a] -> [a] Source #

revDrop :: CountOf (Element [a]) -> [a] -> [a] Source #

splitAt :: CountOf (Element [a]) -> [a] -> ([a], [a]) Source #

revSplitAt :: CountOf (Element [a]) -> [a] -> ([a], [a]) Source #

splitOn :: (Element [a] -> Bool) -> [a] -> [[a]] Source #

break :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

breakEnd :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

breakElem :: Element [a] -> [a] -> ([a], [a]) Source #

takeWhile :: (Element [a] -> Bool) -> [a] -> [a] Source #

dropWhile :: (Element [a] -> Bool) -> [a] -> [a] Source #

intersperse :: Element [a] -> [a] -> [a] Source #

intercalate :: Element [a] -> [a] -> Element [a] Source #

span :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

spanEnd :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

filter :: (Element [a] -> Bool) -> [a] -> [a] Source #

partition :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

reverse :: [a] -> [a] Source #

uncons :: [a] -> Maybe (Element [a], [a]) Source #

unsnoc :: [a] -> Maybe ([a], Element [a]) Source #

snoc :: [a] -> Element [a] -> [a] Source #

cons :: Element [a] -> [a] -> [a] Source #

find :: (Element [a] -> Bool) -> [a] -> Maybe (Element [a]) Source #

sortBy :: (Element [a] -> Element [a] -> Ordering) -> [a] -> [a] Source #

singleton :: Element [a] -> [a] Source #

head :: NonEmpty [a] -> Element [a] Source #

last :: NonEmpty [a] -> Element [a] Source #

tail :: NonEmpty [a] -> [a] Source #

init :: NonEmpty [a] -> [a] Source #

replicate :: CountOf (Element [a]) -> Element [a] -> [a] Source #

isPrefixOf :: [a] -> [a] -> Bool Source #

isSuffixOf :: [a] -> [a] -> Bool Source #

isInfixOf :: [a] -> [a] -> Bool Source #

stripPrefix :: [a] -> [a] -> Maybe [a] Source #

stripSuffix :: [a] -> [a] -> Maybe [a] Source #

Sequential (Array ty) Source # 

Methods

take :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

revSplitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

splitOn :: (Element (Array ty) -> Bool) -> Array ty -> [Array ty] Source #

break :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakEnd :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakElem :: Element (Array ty) -> Array ty -> (Array ty, Array ty) Source #

takeWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

dropWhile :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

intersperse :: Element (Array ty) -> Array ty -> Array ty Source #

intercalate :: Element (Array ty) -> Array ty -> Element (Array ty) Source #

span :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

spanEnd :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

filter :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

partition :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe (Element (Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe (Array ty, Element (Array ty)) Source #

snoc :: Array ty -> Element (Array ty) -> Array ty Source #

cons :: Element (Array ty) -> Array ty -> Array ty Source #

find :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Element (Array ty)) Source #

sortBy :: (Element (Array ty) -> Element (Array ty) -> Ordering) -> Array ty -> Array ty Source #

singleton :: Element (Array ty) -> Array ty Source #

head :: NonEmpty (Array ty) -> Element (Array ty) Source #

last :: NonEmpty (Array ty) -> Element (Array ty) Source #

tail :: NonEmpty (Array ty) -> Array ty Source #

init :: NonEmpty (Array ty) -> Array ty Source #

replicate :: CountOf (Element (Array ty)) -> Element (Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

isInfixOf :: Array ty -> Array ty -> Bool Source #

stripPrefix :: Array ty -> Array ty -> Maybe (Array ty) Source #

stripSuffix :: Array ty -> Array ty -> Maybe (Array ty) Source #

PrimType ty => Sequential (UArray ty) Source # 

Methods

take :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

splitOn :: (Element (UArray ty) -> Bool) -> UArray ty -> [UArray ty] Source #

break :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakElem :: Element (UArray ty) -> UArray ty -> (UArray ty, UArray ty) Source #

takeWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

dropWhile :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

intersperse :: Element (UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element (UArray ty) -> UArray ty -> Element (UArray ty) Source #

span :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

spanEnd :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

filter :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

partition :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe (Element (UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe (UArray ty, Element (UArray ty)) Source #

snoc :: UArray ty -> Element (UArray ty) -> UArray ty Source #

cons :: Element (UArray ty) -> UArray ty -> UArray ty Source #

find :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Element (UArray ty)) Source #

sortBy :: (Element (UArray ty) -> Element (UArray ty) -> Ordering) -> UArray ty -> UArray ty Source #

singleton :: Element (UArray ty) -> UArray ty Source #

head :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

last :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

tail :: NonEmpty (UArray ty) -> UArray ty Source #

init :: NonEmpty (UArray ty) -> UArray ty Source #

replicate :: CountOf (Element (UArray ty)) -> Element (UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

stripPrefix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

PrimType ty => Sequential (Block ty) Source # 

Methods

take :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revTake :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

drop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revDrop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

splitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

revSplitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

splitOn :: (Element (Block ty) -> Bool) -> Block ty -> [Block ty] Source #

break :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

breakEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

breakElem :: Element (Block ty) -> Block ty -> (Block ty, Block ty) Source #

takeWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

dropWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

intersperse :: Element (Block ty) -> Block ty -> Block ty Source #

intercalate :: Element (Block ty) -> Block ty -> Element (Block ty) Source #

span :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

spanEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

filter :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

partition :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

reverse :: Block ty -> Block ty Source #

uncons :: Block ty -> Maybe (Element (Block ty), Block ty) Source #

unsnoc :: Block ty -> Maybe (Block ty, Element (Block ty)) Source #

snoc :: Block ty -> Element (Block ty) -> Block ty Source #

cons :: Element (Block ty) -> Block ty -> Block ty Source #

find :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Element (Block ty)) Source #

sortBy :: (Element (Block ty) -> Element (Block ty) -> Ordering) -> Block ty -> Block ty Source #

singleton :: Element (Block ty) -> Block ty Source #

head :: NonEmpty (Block ty) -> Element (Block ty) Source #

last :: NonEmpty (Block ty) -> Element (Block ty) Source #

tail :: NonEmpty (Block ty) -> Block ty Source #

init :: NonEmpty (Block ty) -> Block ty Source #

replicate :: CountOf (Element (Block ty)) -> Element (Block ty) -> Block ty Source #

isPrefixOf :: Block ty -> Block ty -> Bool Source #

isSuffixOf :: Block ty -> Block ty -> Bool Source #

isInfixOf :: Block ty -> Block ty -> Bool Source #

stripPrefix :: Block ty -> Block ty -> Maybe (Block ty) Source #

stripSuffix :: Block ty -> Block ty -> Maybe (Block ty) Source #

Sequential (DList a) Source # 

Methods

take :: CountOf (Element (DList a)) -> DList a -> DList a Source #

revTake :: CountOf (Element (DList a)) -> DList a -> DList a Source #

drop :: CountOf (Element (DList a)) -> DList a -> DList a Source #

revDrop :: CountOf (Element (DList a)) -> DList a -> DList a Source #

splitAt :: CountOf (Element (DList a)) -> DList a -> (DList a, DList a) Source #

revSplitAt :: CountOf (Element (DList a)) -> DList a -> (DList a, DList a) Source #

splitOn :: (Element (DList a) -> Bool) -> DList a -> [DList a] Source #

break :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

breakEnd :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

breakElem :: Element (DList a) -> DList a -> (DList a, DList a) Source #

takeWhile :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

dropWhile :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

intersperse :: Element (DList a) -> DList a -> DList a Source #

intercalate :: Element (DList a) -> DList a -> Element (DList a) Source #

span :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

spanEnd :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

filter :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

partition :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

reverse :: DList a -> DList a Source #

uncons :: DList a -> Maybe (Element (DList a), DList a) Source #

unsnoc :: DList a -> Maybe (DList a, Element (DList a)) Source #

snoc :: DList a -> Element (DList a) -> DList a Source #

cons :: Element (DList a) -> DList a -> DList a Source #

find :: (Element (DList a) -> Bool) -> DList a -> Maybe (Element (DList a)) Source #

sortBy :: (Element (DList a) -> Element (DList a) -> Ordering) -> DList a -> DList a Source #

singleton :: Element (DList a) -> DList a Source #

head :: NonEmpty (DList a) -> Element (DList a) Source #

last :: NonEmpty (DList a) -> Element (DList a) Source #

tail :: NonEmpty (DList a) -> DList a Source #

init :: NonEmpty (DList a) -> DList a Source #

replicate :: CountOf (Element (DList a)) -> Element (DList a) -> DList a Source #

isPrefixOf :: DList a -> DList a -> Bool Source #

isSuffixOf :: DList a -> DList a -> Bool Source #

isInfixOf :: DList a -> DList a -> Bool Source #

stripPrefix :: DList a -> DList a -> Maybe (DList a) Source #

stripSuffix :: DList a -> DList a -> Maybe (DList a) Source #

PrimType ty => Sequential (ChunkedUArray ty) Source # 

Methods

take :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revTake :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

drop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revDrop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

splitAt :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

revSplitAt :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

splitOn :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> [ChunkedUArray ty] Source #

break :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

breakEnd :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

breakElem :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

takeWhile :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

dropWhile :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intersperse :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intercalate :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> Element (ChunkedUArray ty) Source #

span :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

spanEnd :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

filter :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

partition :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

reverse :: ChunkedUArray ty -> ChunkedUArray ty Source #

uncons :: ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty), ChunkedUArray ty) Source #

unsnoc :: ChunkedUArray ty -> Maybe (ChunkedUArray ty, Element (ChunkedUArray ty)) Source #

snoc :: ChunkedUArray ty -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

cons :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

find :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty)) Source #

sortBy :: (Element (ChunkedUArray ty) -> Element (ChunkedUArray ty) -> Ordering) -> ChunkedUArray ty -> ChunkedUArray ty Source #

singleton :: Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

head :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

last :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

tail :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

init :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

replicate :: CountOf (Element (ChunkedUArray ty)) -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

isPrefixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isSuffixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isInfixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

stripPrefix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe (ChunkedUArray ty) Source #

stripSuffix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe (ChunkedUArray ty) Source #

data NonEmpty a :: * -> * #

NonEmpty property for any Collection

Instances

IsList c => IsList (NonEmpty c) 

Associated Types

type Item (NonEmpty c) :: * #

Methods

fromList :: [Item (NonEmpty c)] -> NonEmpty c #

fromListN :: Int -> [Item (NonEmpty c)] -> NonEmpty c #

toList :: NonEmpty c -> [Item (NonEmpty c)] #

Eq a => Eq (NonEmpty a) 

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Collection c => Collection (NonEmpty c) Source # 

Methods

null :: NonEmpty c -> Bool Source #

length :: NonEmpty c -> CountOf (Element (NonEmpty c)) Source #

elem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

minimum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

any :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source #

all :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source #

type Item (NonEmpty c) 
type Item (NonEmpty c) = Item c
type Element (NonEmpty a) Source # 
type Element (NonEmpty a) = Element a

nonEmpty :: Collection c => c -> Maybe (NonEmpty c) Source #

Smart constructor to create a NonEmpty collection

If the collection is empty, then Nothing is returned Otherwise, the collection is wrapped in the NonEmpty property

Folds

class Foldable collection where Source #

Give the ability to fold a collection on itself

Minimal complete definition

foldl', foldr

Methods

foldl' :: (a -> Element collection -> a) -> a -> collection -> a Source #

Left-associative fold of a structure.

In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.

Note that Foundation only provides foldl', a strict version of foldl because the lazy version is seldom useful.

Left-associative fold of a structure with strict application of the operator.

foldr :: (Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure.

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldr' :: (Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure, but with strict application of the operator.

Instances

Foldable Bitmap Source # 

Methods

foldl' :: (a -> Element Bitmap -> a) -> a -> Bitmap -> a Source #

foldr :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

foldr' :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

Foldable [a] Source # 

Methods

foldl' :: (a -> Element [a] -> a) -> a -> [a] -> a Source #

foldr :: (Element [a] -> a -> a) -> a -> [a] -> a Source #

foldr' :: (Element [a] -> a -> a) -> a -> [a] -> a Source #

Foldable (Array ty) Source # 

Methods

foldl' :: (a -> Element (Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

PrimType ty => Foldable (UArray ty) Source # 

Methods

foldl' :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => Foldable (Block ty) Source # 

Methods

foldl' :: (a -> Element (Block ty) -> a) -> a -> Block ty -> a Source #

foldr :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a Source #

foldr' :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a Source #

Foldable (DList a) Source # 

Methods

foldl' :: (a -> Element (DList a) -> a) -> a -> DList a -> a Source #

foldr :: (Element (DList a) -> a -> a) -> a -> DList a -> a Source #

foldr' :: (Element (DList a) -> a -> a) -> a -> DList a -> a Source #

PrimType ty => Foldable (ChunkedUArray ty) Source # 

Methods

foldl' :: (a -> Element (ChunkedUArray ty) -> a) -> a -> ChunkedUArray ty -> a Source #

foldr :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source #

foldr' :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source #

Maybe

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

The mapMaybe function is a version of map which can throw out elements. In particular, the functional argument returns something of type Maybe b. If this is Nothing, no element is added on to the result list. If it is Just b, then b is included in the result list.

Examples

Using mapMaybe f x is a shortcut for catMaybes $ map f x in most cases:

>>> import Text.Read ( readMaybe )
>>> let readMaybeInt = readMaybe :: String -> Maybe Int
>>> mapMaybe readMaybeInt ["1", "Foo", "3"]
[1,3]
>>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
[1,3]

If we map the Just constructor, the entire list should be returned:

>>> mapMaybe Just [1,2,3]
[1,2,3]

catMaybes :: [Maybe a] -> [a] #

The catMaybes function takes a list of Maybes and returns a list of all the Just values.

Examples

Basic usage:

>>> catMaybes [Just 1, Nothing, Just 3]
[1,3]

When constructing a list of Maybe values, catMaybes can be used to return all of the "success" results (if the list is the result of a map, then mapMaybe would be more appropriate):

>>> import Text.Read ( readMaybe )
>>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[Just 1,Nothing,Just 3]
>>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[1,3]

fromMaybe :: a -> Maybe a -> a #

The fromMaybe function takes a default value and and Maybe value. If the Maybe is Nothing, it returns the default values; otherwise, it returns the value contained in the Maybe.

Examples

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>> fromMaybe "" Nothing
""

Read an integer from a string using readMaybe. If we fail to parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
>>> fromMaybe 0 (readMaybe "5")
5
>>> fromMaybe 0 (readMaybe "")
0

isJust :: Maybe a -> Bool #

The isJust function returns True iff its argument is of the form Just _.

Examples

Basic usage:

>>> isJust (Just 3)
True
>>> isJust (Just ())
True
>>> isJust Nothing
False

Only the outer constructor is taken into consideration:

>>> isJust (Just Nothing)
True

isNothing :: Maybe a -> Bool #

The isNothing function returns True iff its argument is Nothing.

Examples

Basic usage:

>>> isNothing (Just 3)
False
>>> isNothing (Just ())
False
>>> isNothing Nothing
True

Only the outer constructor is taken into consideration:

>>> isNothing (Just Nothing)
False

listToMaybe :: [a] -> Maybe a #

The listToMaybe function returns Nothing on an empty list or Just a where a is the first element of the list.

Examples

Basic usage:

>>> listToMaybe []
Nothing
>>> listToMaybe [9]
Just 9
>>> listToMaybe [1,2,3]
Just 1

Composing maybeToList with listToMaybe should be the identity on singleton/empty lists:

>>> maybeToList $ listToMaybe [5]
[5]
>>> maybeToList $ listToMaybe []
[]

But not on lists with more than one element:

>>> maybeToList $ listToMaybe [1,2,3]
[1]

maybeToList :: Maybe a -> [a] #

The maybeToList function returns an empty list when given Nothing or a singleton list when not given Nothing.

Examples

Basic usage:

>>> maybeToList (Just 7)
[7]
>>> maybeToList Nothing
[]

One can use maybeToList to avoid pattern matching when combined with a function that (safely) works on lists:

>>> import Text.Read ( readMaybe )
>>> sum $ maybeToList (readMaybe "3")
3
>>> sum $ maybeToList (readMaybe "")
0

Either

partitionEithers :: [Either a b] -> ([a], [b]) #

Partitions a list of Either into two lists. All the Left elements are extracted, in order, to the first component of the output. Similarly the Right elements are extracted to the second component of the output.

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> partitionEithers list
(["foo","bar","baz"],[3,7])

The pair returned by partitionEithers x should be the same pair as (lefts x, rights x):

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> partitionEithers list == (lefts list, rights list)
True

lefts :: [Either a b] -> [a] #

Extracts from a list of Either all the Left elements. All the Left elements are extracted in order.

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> lefts list
["foo","bar","baz"]

rights :: [Either a b] -> [b] #

Extracts from a list of Either all the Right elements. All the Right elements are extracted in order.

Examples

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> rights list
[3,7]

Function

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 #

(*) `on` f = \x y -> f x * f y.

Typical usage: sortBy (compare `on` fst).

Algebraic properties:

  • (*) `on` id = (*) (if (*) ∉ {⊥, const ⊥})
  • ((*) `on` f) `on` g = (*) `on` (f . g)
  • flip on f . flip on g = flip on (g . f)

Applicative

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(<|>) :: Alternative f => forall a. f a -> f a -> f a infixl 3 #

An associative binary operation

Monad

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right Kleisli composition of monads.

Exceptions

class (Typeable * e, Show e) => Exception e where #

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving Show

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving Show

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

Methods

toException :: e -> SomeException #

fromException :: SomeException -> Maybe e #

displayException :: e -> String #

Render this exception value in a human-friendly manner.

Default implementation: show.

Since: 4.8.0.0

Instances

Exception Void

Since: 4.8.0.0

Exception PatternMatchFail

Since: 4.0

Exception RecSelError

Since: 4.0

Exception RecConError

Since: 4.0

Exception RecUpdError

Since: 4.0

Exception NoMethodError

Since: 4.0

Exception TypeError

Since: 4.9.0.0

Exception NonTermination

Since: 4.0

Exception NestedAtomically

Since: 4.0

Exception BlockedIndefinitelyOnMVar

Since: 4.1.0.0

Exception BlockedIndefinitelyOnSTM

Since: 4.1.0.0

Exception Deadlock

Since: 4.1.0.0

Exception AllocationLimitExceeded

Since: 4.8.0.0

Exception CompactionFailed

Since: 4.10.0.0

Exception AssertionFailed

Since: 4.1.0.0

Exception SomeAsyncException

Since: 4.7.0.0

Exception AsyncException

Since: 4.7.0.0

Exception ArrayException

Since: 4.1.0.0

Exception ExitCode

Since: 4.1.0.0

Exception IOException

Since: 4.1.0.0

Exception ErrorCall

Since: 4.0.0.0

Exception ArithException

Since: 4.0.0.0

Exception SomeException

Since: 3.0

Exception ASCII7_Invalid 

Methods

toException :: ASCII7_Invalid -> SomeException #

fromException :: SomeException -> Maybe ASCII7_Invalid #

displayException :: ASCII7_Invalid -> String #

Exception ISO_8859_1_Invalid 

Methods

toException :: ISO_8859_1_Invalid -> SomeException #

fromException :: SomeException -> Maybe ISO_8859_1_Invalid #

displayException :: ISO_8859_1_Invalid -> String #

Exception UTF16_Invalid 

Methods

toException :: UTF16_Invalid -> SomeException #

fromException :: SomeException -> Maybe UTF16_Invalid #

displayException :: UTF16_Invalid -> String #

Exception UTF32_Invalid 

Methods

toException :: UTF32_Invalid -> SomeException #

fromException :: SomeException -> Maybe UTF32_Invalid #

displayException :: UTF32_Invalid -> String #

Exception ValidationFailure 
Exception OutOfBound 
Exception InvalidRecast 
Exception NonEmptyCollectionIsEmpty 
Exception PartialError # 
Typeable * input => Exception (ParseError input) # 

class Typeable k (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

data SomeException :: * #

The SomeException type is the root of the exception type hierarchy. When an exception of type e is thrown, behind the scenes it is encapsulated in a SomeException.

data IOException :: * #

Exceptions that occur in the IO monad. An IOException records a more specific error type, a descriptive string and maybe the handle that was used when the error was flagged.

Proxy

data Proxy k (t :: k) :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Generic1 k (Proxy k) 

Associated Types

type Rep1 (Proxy k) (f :: Proxy k -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Proxy k) f a #

to1 :: Rep1 (Proxy k) f a -> f a #

Monad (Proxy *)

Since: 4.7.0.0

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *)

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

liftA2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *)

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *)

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Bounded (Proxy k t) 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

Enum (Proxy k s)

Since: 4.7.0.0

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s)

Since: 4.7.0.0

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy * t) #

toConstr :: Proxy * t -> Constr #

dataTypeOf :: Proxy * t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Proxy * t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Proxy * t)) #

gmapT :: (forall b. Data b => b -> b) -> Proxy * t -> Proxy * t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy * t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy * t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

Ord (Proxy k s)

Since: 4.7.0.0

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s)

Since: 4.7.0.0

Show (Proxy k s)

Since: 4.7.0.0

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s)

Since: 4.7.0.0

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s)

Since: 4.9.0.0

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

type Rep1 k (Proxy k) 
type Rep1 k (Proxy k) = D1 k (MetaData "Proxy" "Data.Proxy" "base" False) (C1 k (MetaCons "Proxy" PrefixI False) (U1 k))
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 * (MetaData "Proxy" "Data.Proxy" "base" False) (C1 * (MetaCons "Proxy" PrefixI False) (U1 *))

asProxyTypeOf :: a -> proxy a -> a #

asProxyTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

Partial

data Partial a Source #

Partialiality wrapper.

Instances

Monad Partial Source # 

Methods

(>>=) :: Partial a -> (a -> Partial b) -> Partial b #

(>>) :: Partial a -> Partial b -> Partial b #

return :: a -> Partial a #

fail :: String -> Partial a #

Functor Partial Source # 

Methods

fmap :: (a -> b) -> Partial a -> Partial b #

(<$) :: a -> Partial b -> Partial a #

Applicative Partial Source # 

Methods

pure :: a -> Partial a #

(<*>) :: Partial (a -> b) -> Partial a -> Partial b #

liftA2 :: (a -> b -> c) -> Partial a -> Partial b -> Partial c #

(*>) :: Partial a -> Partial b -> Partial b #

(<*) :: Partial a -> Partial b -> Partial a #

partial :: a -> Partial a Source #

Create a value that is partial. this can only be unwrap using the fromPartial function

data PartialError Source #

An error related to the evaluation of a Partial value that failed.

it contains the name of the function and the reason for failure

fromPartial :: Partial a -> a Source #

Dewrap a possible partial value

ifThenElse :: Bool -> a -> a -> a #

for support of if .. then .. else

Old Prelude Strings as [Char] with bridge back and forth

type LString = String Source #

Alias to Prelude String ([Char]) for compatibility purpose