foundation-0.0.12: 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 c a. cat b c -> cat a b -> cat a c #

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

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.12-FHTc6niWcrs4WuDH8ZMZpU" 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 -> () 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 #

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

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. 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 :: forall r. forall a. HasCallStack => String -> a Source #

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

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

Data that can be fully evaluated in Normal Form

Minimal complete definition

toNormalForm

Instances

NormalForm Bool Source # 

Methods

toNormalForm :: Bool -> () Source #

NormalForm Char Source # 

Methods

toNormalForm :: Char -> () Source #

NormalForm Double Source # 

Methods

toNormalForm :: Double -> () Source #

NormalForm Float Source # 

Methods

toNormalForm :: Float -> () Source #

NormalForm Int Source # 

Methods

toNormalForm :: Int -> () Source #

NormalForm Int8 Source # 

Methods

toNormalForm :: Int8 -> () Source #

NormalForm Int16 Source # 

Methods

toNormalForm :: Int16 -> () Source #

NormalForm Int32 Source # 

Methods

toNormalForm :: Int32 -> () Source #

NormalForm Int64 Source # 

Methods

toNormalForm :: Int64 -> () Source #

NormalForm Integer Source # 

Methods

toNormalForm :: Integer -> () Source #

NormalForm Word Source # 

Methods

toNormalForm :: Word -> () Source #

NormalForm Word8 Source # 

Methods

toNormalForm :: Word8 -> () Source #

NormalForm Word16 Source # 

Methods

toNormalForm :: Word16 -> () Source #

NormalForm Word32 Source # 

Methods

toNormalForm :: Word32 -> () Source #

NormalForm Word64 Source # 

Methods

toNormalForm :: Word64 -> () Source #

NormalForm () Source # 

Methods

toNormalForm :: () -> () Source #

NormalForm Natural Source # 

Methods

toNormalForm :: Natural -> () Source #

NormalForm CChar Source # 

Methods

toNormalForm :: CChar -> () Source #

NormalForm CSChar Source # 

Methods

toNormalForm :: CSChar -> () Source #

NormalForm CUChar Source # 

Methods

toNormalForm :: CUChar -> () Source #

NormalForm CShort Source # 

Methods

toNormalForm :: CShort -> () Source #

NormalForm CUShort Source # 

Methods

toNormalForm :: CUShort -> () Source #

NormalForm CInt Source # 

Methods

toNormalForm :: CInt -> () Source #

NormalForm CUInt Source # 

Methods

toNormalForm :: CUInt -> () Source #

NormalForm CLong Source # 

Methods

toNormalForm :: CLong -> () Source #

NormalForm CULong Source # 

Methods

toNormalForm :: CULong -> () Source #

NormalForm CLLong Source # 

Methods

toNormalForm :: CLLong -> () Source #

NormalForm CULLong Source # 

Methods

toNormalForm :: CULLong -> () Source #

NormalForm CFloat Source # 

Methods

toNormalForm :: CFloat -> () Source #

NormalForm CDouble Source # 

Methods

toNormalForm :: CDouble -> () Source #

NormalForm String Source # 

Methods

toNormalForm :: String -> () Source #

NormalForm IPv4 Source # 

Methods

toNormalForm :: IPv4 -> () Source #

NormalForm IPv6 Source # 

Methods

toNormalForm :: IPv6 -> () Source #

NormalForm UUID Source # 

Methods

toNormalForm :: UUID -> () Source #

NormalForm a => NormalForm [a] Source # 

Methods

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

NormalForm a => NormalForm (Maybe a) Source # 

Methods

toNormalForm :: Maybe a -> () Source #

NormalForm (Ptr a) Source # 

Methods

toNormalForm :: Ptr a -> () Source #

NormalForm (CountOf a) Source # 

Methods

toNormalForm :: CountOf a -> () Source #

NormalForm (Offset a) Source # 

Methods

toNormalForm :: Offset a -> () Source #

NormalForm (Block ty) Source # 

Methods

toNormalForm :: Block ty -> () Source #

NormalForm (UArray ty) Source # 

Methods

toNormalForm :: UArray ty -> () Source #

NormalForm a => NormalForm (Array a) Source # 

Methods

toNormalForm :: Array a -> () Source #

NormalForm (ChunkedUArray ty) Source # 

Methods

toNormalForm :: ChunkedUArray ty -> () Source #

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

Methods

toNormalForm :: Either l r -> () Source #

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

Methods

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

NormalForm (BlockN n a) Source # 

Methods

toNormalForm :: BlockN n a -> () Source #

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

Methods

toNormalForm :: These a b -> () Source #

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

Methods

toNormalForm :: Tuple2 a b -> () Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

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

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 

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show Int8 

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show Int16 

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Integer 
Show Ordering 
Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Word16 
Show Word32 
Show Word64 
Show CallStack 
Show TypeRep 
Show () 

Methods

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

show :: () -> String #

showList :: [()] -> ShowS #

Show TyCon 

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Module 
Show TrName 
Show FD 

Methods

showsPrec :: Int -> FD -> ShowS #

show :: FD -> String #

showList :: [FD] -> ShowS #

Show HandleType 

Methods

showsPrec :: Int -> HandleType -> ShowS #

show :: HandleType -> String #

showList :: [HandleType] -> ShowS #

Show Natural 
Show Void 

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show DataType 
Show Constr 
Show DataRep 
Show ConstrRep 
Show Fixity 
Show Version 
Show GCStats 
Show HandlePosn 
Show PatternMatchFail 
Show RecSelError 
Show RecConError 
Show RecUpdError 
Show NoMethodError 
Show TypeError 
Show NonTermination 
Show NestedAtomically 
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 Fd 

Methods

showsPrec :: Int -> Fd -> ShowS #

show :: Fd -> String #

showList :: [Fd] -> ShowS #

Show ThreadId 
Show BlockReason 
Show ThreadStatus 
Show BlockedIndefinitelyOnMVar 
Show BlockedIndefinitelyOnSTM 
Show Deadlock 
Show AllocationLimitExceeded 
Show AssertionFailed 
Show SomeAsyncException 
Show AsyncException 
Show ArrayException 
Show ExitCode 
Show IOErrorType 
Show Handle 
Show BufferMode 
Show Newline 
Show NewlineMode 
Show WordPtr 
Show IntPtr 
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 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 SeekMode 
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 MaskingState 
Show IOException 
Show ErrorCall 
Show ArithException 
Show SomeNat 
Show SomeSymbol 
Show IOMode 
Show Lexeme 
Show Number 
Show GeneralCategory 
Show SomeException 
Show SrcLoc 
Show PartialError # 
Show Endianness # 
Show OutOfBound # 
Show ValidationFailure # 
Show String # 
Show Encoding # 
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 And # 

Methods

showsPrec :: Int -> And -> ShowS #

show :: And -> String #

showList :: [And] -> ShowS #

Show Condition # 
Show AsciiString # 
Show Seconds # 
Show NanoSeconds # 
Show Bitmap # 
Show IPv4 # 

Methods

showsPrec :: Int -> IPv4 -> ShowS #

show :: IPv4 -> String #

showList :: [IPv4] -> ShowS #

Show IPv6 # 

Methods

showsPrec :: Int -> IPv6 -> ShowS #

show :: IPv6 -> String #

showList :: [IPv6] -> ShowS #

Show UUID # 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

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

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) 

Methods

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

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Ptr a) 

Methods

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

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show (FunPtr a) 

Methods

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

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show (V1 p) 

Methods

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

show :: V1 p -> String #

showList :: [V1 p] -> ShowS #

Show (U1 p) 

Methods

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

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Show p => Show (Par1 p) 

Methods

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

show :: Par1 p -> String #

showList :: [Par1 p] -> 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

Methods

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

show :: Identity a -> String #

showList :: [Identity a] -> 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 (ForeignPtr a) 
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 (BE a) # 

Methods

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

show :: BE a -> String #

showList :: [BE a] -> ShowS #

Show a => Show (LE a) # 

Methods

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

show :: LE a -> String #

showList :: [LE a] -> ShowS #

Show (FinalPtr a) # 

Methods

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

show :: FinalPtr a -> String #

showList :: [FinalPtr a] -> ShowS #

Show (CountOf ty) # 

Methods

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

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Show (Offset ty) # 

Methods

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

show :: Offset ty -> String #

showList :: [Offset 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 #

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

Methods

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

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

Show a => Show (Array a) # 

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

(Show ty, PrimType ty) => Show (ChunkedUArray ty) # 
Show a => Show (DList a) # 

Methods

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

show :: DList a -> String #

showList :: [DList a] -> ShowS #

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 (f p) => Show (Rec1 f p) 

Methods

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

show :: Rec1 f p -> String #

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

Show (URec Char p) 

Methods

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

show :: URec Char p -> String #

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

Show (URec Double p) 

Methods

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

show :: URec Double p -> String #

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

Show (URec Float p) 

Methods

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

show :: URec Float p -> String #

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

Show (URec Int p) 

Methods

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

show :: URec Int p -> String #

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

Show (URec Word p) 

Methods

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

show :: URec Word p -> String #

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

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

Methods

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

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

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

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

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) 

Methods

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

show :: Proxy k s -> String #

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

Show (ST s a) 

Methods

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

show :: ST s a -> String #

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

(Show a, PrimType a) => Show (BlockN n a) # 

Methods

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

show :: BlockN n a -> String #

showList :: [BlockN 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 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 k => Show (Result input k) # 

Methods

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

show :: Result input k -> String #

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

Show c => Show (K1 i c p) 

Methods

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

show :: K1 i c p -> String #

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

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

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

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 (f p) => Show (M1 i c f p) 

Methods

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

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

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

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

Methods

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

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

showList :: [(a, b, c, d)] -> 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 a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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

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 

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 

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 

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 

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

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 
Ord Word32 
Ord Word64 
Ord TypeRep 
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 Natural 
Ord Void 

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 
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 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 ThreadId 
Ord BlockReason 
Ord ThreadStatus 
Ord AsyncException 
Ord ArrayException 
Ord ExitCode 
Ord BufferMode 
Ord Newline 
Ord NewlineMode 
Ord WordPtr 
Ord IntPtr 
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 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 SeekMode 
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 ErrorCall 
Ord ArithException 
Ord SomeNat 
Ord SomeSymbol 
Ord IOMode 
Ord GeneralCategory 
Ord String # 
Ord Encoding # 
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 AsciiString # 
Ord Seconds # 
Ord NanoSeconds # 
Ord Bitmap # 
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 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 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) 

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 (V1 p) 

Methods

compare :: V1 p -> V1 p -> Ordering #

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

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

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

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

max :: V1 p -> V1 p -> V1 p #

min :: V1 p -> V1 p -> V1 p #

Ord (U1 p) 

Methods

compare :: U1 p -> U1 p -> Ordering #

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

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

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

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

max :: U1 p -> U1 p -> U1 p #

min :: U1 p -> U1 p -> U1 p #

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 (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 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 (ForeignPtr a) 
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 #

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

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

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 #

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

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

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

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 #

(Ord ty, PrimType ty) => Ord (ChunkedUArray ty) # 
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 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 (f p) => Ord (Rec1 f p) 

Methods

compare :: Rec1 f p -> Rec1 f p -> Ordering #

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

(<=) :: Rec1 f p -> Rec1 f p -> Bool #

(>) :: Rec1 f p -> Rec1 f p -> Bool #

(>=) :: Rec1 f p -> Rec1 f p -> Bool #

max :: Rec1 f p -> Rec1 f p -> Rec1 f p #

min :: Rec1 f p -> Rec1 f p -> Rec1 f p #

Ord (URec Char p) 

Methods

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

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

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

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

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

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

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

Ord (URec Double p) 

Methods

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

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

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

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

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

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

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

Ord (URec Float p) 

Methods

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

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

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

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

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

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

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

Ord (URec Int p) 

Methods

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

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

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

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

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

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

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

Ord (URec Word p) 

Methods

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

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

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

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

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

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

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

Ord (URec (Ptr ()) p) 

Methods

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

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

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

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

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

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

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

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

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) 

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) 

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 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 c => Ord (K1 i c p) 

Methods

compare :: K1 i c p -> K1 i c p -> Ordering #

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

(<=) :: K1 i c p -> K1 i c p -> Bool #

(>) :: K1 i c p -> K1 i c p -> Bool #

(>=) :: K1 i c p -> K1 i c p -> Bool #

max :: K1 i c p -> K1 i c p -> K1 i c p #

min :: K1 i c p -> K1 i c p -> K1 i c p #

(Ord (g p), Ord (f p)) => Ord ((:+:) f g p) 

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

(Ord (g p), Ord (f p)) => Ord ((:*:) f g p) 

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering #

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

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

(>) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

Ord (f (g p)) => Ord ((:.:) f g p) 

Methods

compare :: (f :.: g) p -> (f :.: g) p -> Ordering #

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

(<=) :: (f :.: g) p -> (f :.: g) p -> Bool #

(>) :: (f :.: g) p -> (f :.: g) p -> Bool #

(>=) :: (f :.: g) p -> (f :.: g) p -> Bool #

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) 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 (f p) => Ord (M1 i c f p) 

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering #

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

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

(>) :: M1 i c f p -> M1 i c f p -> Bool #

(>=) :: M1 i c f p -> M1 i c f p -> Bool #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p #

min :: M1 i c f p -> M1 i c f p -> M1 i c f 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 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 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 

Methods

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

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

Eq Int16 

Methods

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

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

Eq Int32 

Methods

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

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

Eq Int64 

Methods

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

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

Eq Integer 

Methods

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

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

Eq Ordering 
Eq Word 

Methods

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

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

Eq Word8 

Methods

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

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

Eq Word16 

Methods

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

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

Eq Word32 

Methods

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

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

Eq Word64 

Methods

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

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

Eq TypeRep 

Methods

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

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

Eq () 

Methods

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

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

Eq TyCon 

Methods

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

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

Eq BigNat 

Methods

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

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

Eq SpecConstrAnnotation 
Eq Natural 

Methods

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

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

Eq Void 

Methods

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

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

Eq Constr

Equality of constructors

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 

Methods

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

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

Eq HandlePosn 
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 Fd 

Methods

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

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

Eq ThreadId 
Eq BlockReason 
Eq ThreadStatus 
Eq Errno 

Methods

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

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

Eq AsyncException 
Eq ArrayException 
Eq ExitCode 
Eq IOErrorType 
Eq Handle 

Methods

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

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

Eq BufferMode 
Eq Newline 

Methods

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

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

Eq NewlineMode 
Eq WordPtr 

Methods

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

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

Eq IntPtr 

Methods

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

(/=) :: IntPtr -> IntPtr -> 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 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 IODeviceType 
Eq SeekMode 
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 MaskingState 
Eq IOException 
Eq ErrorCall 
Eq ArithException 
Eq SomeNat 

Methods

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

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

Eq SomeSymbol 
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 PartialError # 
Eq Endianness # 
Eq Sign # 

Methods

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

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

Eq ValidationFailure # 
Eq String # 

Methods

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

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

Eq Encoding # 
Eq Arch # 

Methods

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

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

Eq OS # 

Methods

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

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

Eq And # 

Methods

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

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

Eq Condition # 
Eq AsciiString # 
Eq Seconds # 

Methods

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

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

Eq NanoSeconds # 
Eq Bitmap # 

Methods

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

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

Eq IPv4 # 

Methods

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

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

Eq IPv6 # 

Methods

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

(/=) :: IPv6 -> IPv6 -> 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 (V1 p) 

Methods

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

(/=) :: V1 p -> V1 p -> Bool #

Eq (U1 p) 

Methods

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

(/=) :: U1 p -> U1 p -> Bool #

Eq p => Eq (Par1 p) 

Methods

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

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

Eq a => Eq (Identity a) 

Methods

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

(/=) :: Identity a -> Identity a -> 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 (TVar a) 

Methods

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

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

Eq (ForeignPtr a) 

Methods

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

(/=) :: ForeignPtr a -> ForeignPtr 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 (IORef a) 

Methods

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

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

Eq a => Eq (BE a) # 

Methods

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

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

Eq a => Eq (LE a) # 

Methods

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

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

Eq (FinalPtr a) # 

Methods

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

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

Eq (CountOf ty) # 

Methods

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

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

Eq (Offset ty) # 

Methods

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

(/=) :: Offset ty -> Offset 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 #

(PrimType ty, Eq ty) => Eq (UArray ty) # 

Methods

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

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

Eq a => Eq (Array a) # 

Methods

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

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

PrimType ty => Eq (ChunkedUArray ty) # 
Eq a => Eq (DList a) # 

Methods

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

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

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

Methods

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

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

Eq (f p) => Eq (Rec1 f p) 

Methods

(==) :: Rec1 f p -> Rec1 f p -> Bool #

(/=) :: Rec1 f p -> Rec1 f p -> Bool #

Eq (URec Char p) 

Methods

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

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

Eq (URec Double p) 

Methods

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

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

Eq (URec Float p) 

Methods

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

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

Eq (URec Int p) 

Methods

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

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

Eq (URec Word p) 

Methods

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

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

Eq (URec (Ptr ()) p) 

Methods

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

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> 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) 

Methods

(==) :: Array i e -> Array i e -> Bool #

(/=) :: Array i e -> Array i e -> Bool #

Eq a => Eq (Arg a b) 

Methods

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

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

Eq (Proxy k s) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Eq (STRef s a) 

Methods

(==) :: STRef s a -> STRef s a -> Bool #

(/=) :: STRef s a -> STRef s a -> Bool #

PrimType a => Eq (BlockN n a) # 

Methods

(==) :: BlockN n a -> BlockN n a -> Bool #

(/=) :: BlockN n a -> BlockN 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 c => Eq (K1 i c p) 

Methods

(==) :: K1 i c p -> K1 i c p -> Bool #

(/=) :: K1 i c p -> K1 i c p -> Bool #

(Eq (g p), Eq (f p)) => Eq ((:+:) f g p) 

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(Eq (g p), Eq (f p)) => Eq ((:*:) f g p) 

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool #

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

Eq (f (g p)) => Eq ((:.:) f g p) 

Methods

(==) :: (f :.: g) p -> (f :.: g) p -> Bool #

(/=) :: (f :.: g) p -> (f :.: g) 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) 

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 (f p) => Eq (M1 i c f p) 

Methods

(==) :: M1 i c f p -> M1 i c f p -> Bool #

(/=) :: M1 i c f p -> M1 i c f 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 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 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 
Bounded Char 
Bounded Int 

Methods

minBound :: Int #

maxBound :: Int #

Bounded Int8 
Bounded Int16 
Bounded Int32 
Bounded Int64 
Bounded Ordering 
Bounded Word 
Bounded Word8 
Bounded Word16 
Bounded Word32 
Bounded Word64 
Bounded () 

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 Fd 

Methods

minBound :: Fd #

maxBound :: Fd #

Bounded WordPtr 
Bounded IntPtr 
Bounded CChar 
Bounded CSChar 
Bounded CUChar 
Bounded CShort 
Bounded CUShort 
Bounded CInt 
Bounded CUInt 
Bounded CLong 
Bounded CULong 
Bounded CLLong 
Bounded CULLong 
Bounded CPtrdiff 
Bounded CSize 
Bounded CWchar 
Bounded CSigAtomic 
Bounded CIntPtr 
Bounded CUIntPtr 
Bounded CIntMax 
Bounded CUIntMax 
Bounded All 

Methods

minBound :: All #

maxBound :: All #

Bounded Any 

Methods

minBound :: Any #

maxBound :: Any #

Bounded Associativity 
Bounded SourceUnpackedness 
Bounded SourceStrictness 
Bounded DecidedStrictness 
Bounded GeneralCategory 
Bounded Encoding # 
Bounded Arch # 
Bounded OS # 

Methods

minBound :: OS #

maxBound :: OS #

Bounded Seconds # 
Bounded NanoSeconds # 
Bounded a => Bounded (Identity a) 
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 a => Bounded (WrappedMonoid 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) 

Methods

minBound :: (a, b) #

maxBound :: (a, b) #

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

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

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) 

Methods

minBound :: Coercion k a b #

maxBound :: Coercion k a b #

(~) k a b => Bounded ((:~:) k a b) 

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

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

Methods

minBound :: (a, b, c, d) #

maxBound :: (a, b, c, d) #

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

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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) 

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 

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 

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 

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 

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 
Enum Int32 
Enum Int64 
Enum Integer 
Enum Ordering 
Enum Word 

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 
Enum Word16 
Enum Word32 
Enum Word64 
Enum () 

Methods

succ :: () -> () #

pred :: () -> () #

toEnum :: Int -> () #

fromEnum :: () -> Int #

enumFrom :: () -> [()] #

enumFromThen :: () -> () -> [()] #

enumFromTo :: () -> () -> [()] #

enumFromThenTo :: () -> () -> () -> [()] #

Enum Natural 
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 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 WordPtr 
Enum IntPtr 
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 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 SeekMode 
Enum Associativity 
Enum SourceUnpackedness 
Enum SourceStrictness 
Enum DecidedStrictness 
Enum IOMode 
Enum GeneralCategory 
Enum Encoding # 
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) 

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 (Identity a) 
Enum a => Enum (Min a) 

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) 

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) 

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) 

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) 
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 (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 (Proxy k s) 

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) 

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) 

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

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

Methods

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

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

Functor Maybe 

Methods

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

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

Functor IO 

Methods

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

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

Functor V1 

Methods

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

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

Functor U1 

Methods

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

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

Functor Par1 

Methods

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

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

Functor Id 

Methods

fmap :: (a -> b) -> Id a -> Id b #

(<$) :: a -> Id b -> Id a #

Functor P 

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Functor Identity 

Methods

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

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

Functor Min 

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

Functor Max 

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max 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 Option 

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Functor NonEmpty 

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 Handler 

Methods

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

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

Functor STM 

Methods

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

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

Functor Dual 

Methods

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

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

Functor Sum 

Methods

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

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

Functor Product 

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 

Methods

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

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

Functor Partial # 

Methods

fmap :: (a -> b) -> Partial a -> Partial b #

(<$) :: a -> Partial b -> Partial 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 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 ((->) r) 

Methods

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

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

Functor (Either a) 

Methods

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

(<$) :: a -> Either a b -> Either a 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 #

Functor ((,) a) 

Methods

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

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

Functor (StateL s) 

Methods

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

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

Functor (StateR s) 

Methods

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

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

Functor (Array i) 

Methods

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

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

Functor (Arg a) 

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b #

(<$) :: a -> Arg a b -> Arg a a #

Monad m => Functor (WrappedMonad m) 

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Functor (ArrowMonad a) 

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a #

Functor (Proxy *) 

Methods

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

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

Functor (ST s) 

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 (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 m => Functor (ResourceT m) # 

Methods

fmap :: (a -> b) -> ResourceT m a -> ResourceT m b #

(<$) :: a -> ResourceT m b -> ResourceT m a #

Functor (MonadRandomState gen) # 

Methods

fmap :: (a -> b) -> MonadRandomState gen a -> MonadRandomState gen b #

(<$) :: a -> MonadRandomState gen b -> MonadRandomState gen 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 g, Functor f) => Functor ((:.:) f g) 

Methods

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

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

Arrow a => Functor (WrappedArrow a b) 

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a #

Functor (Const * m) 

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 #

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 (StateT s m) # 

Methods

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

(<$) :: a -> StateT s m b -> StateT s 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 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 (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 #

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

Integral Literal support

e.g. 123 :: Integer 123 :: Word8

Minimal complete definition

fromInteger

Methods

fromInteger :: Integer -> a Source #

Instances

Integral Double Source # 
Integral Float Source # 
Integral Int Source # 
Integral Int8 Source # 
Integral Int16 Source # 
Integral Int32 Source # 
Integral Int64 Source # 
Integral Integer Source # 
Integral Word Source # 
Integral Word8 Source # 
Integral Word16 Source # 
Integral Word32 Source # 
Integral Word64 Source # 
Integral Natural Source # 
Integral COff Source # 
Integral CInt Source # 
Integral CFloat Source # 
Integral CDouble Source # 
Integral CSize Source # 
Integral CUIntPtr Source # 
Integral (CountOf ty) Source # 
Integral (Offset ty) Source # 

class Fractional a where Source #

Fractional Literal support

e.g. 1.2 :: Double 0.03 :: Float

Minimal complete definition

fromRational

Methods

fromRational :: Rational -> a Source #

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 

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

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 

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 (K1 i) 

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) 

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

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 ((,,,) x1 x2) 

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) 

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) 

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) 

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

A minimal complete definition must include implementations of these functions satisfying the following laws:

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

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Methods

pure :: a -> f a #

Lift a value.

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

Sequential application.

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

Methods

pure :: a -> [a] #

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

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

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

Applicative Maybe 

Methods

pure :: a -> Maybe a #

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

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

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

Applicative IO 

Methods

pure :: a -> IO a #

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

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

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

Applicative U1 

Methods

pure :: a -> U1 a #

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

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

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

Applicative Par1 

Methods

pure :: a -> Par1 a #

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

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

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

Applicative Id 

Methods

pure :: a -> Id a #

(<*>) :: Id (a -> b) -> Id a -> Id b #

(*>) :: Id a -> Id b -> Id b #

(<*) :: Id a -> Id b -> Id a #

Applicative P 

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Applicative Identity 

Methods

pure :: a -> Identity a #

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

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

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

Applicative Min 

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max 

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First 

Methods

pure :: a -> First a #

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

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

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

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

Applicative Option 

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

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

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

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

Applicative ZipList 

Methods

pure :: a -> ZipList a #

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

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

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

Applicative STM 

Methods

pure :: a -> STM a #

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

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

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

Applicative Dual 

Methods

pure :: a -> Dual a #

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

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

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

Applicative Sum 

Methods

pure :: a -> Sum a #

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

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

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

Applicative Product 

Methods

pure :: a -> Product a #

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

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

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

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

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

Applicative ReadP 

Methods

pure :: a -> ReadP a #

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

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

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

Applicative Partial # 

Methods

pure :: a -> Partial a #

(<*>) :: Partial (a -> b) -> Partial a -> Partial b #

(*>) :: Partial a -> Partial b -> Partial b #

(<*) :: Partial a -> Partial b -> Partial a #

Applicative DList # 

Methods

pure :: a -> DList a #

(<*>) :: DList (a -> b) -> DList a -> DList b #

(*>) :: DList a -> DList b -> DList b #

(<*) :: DList a -> DList b -> DList a #

Applicative Gen # 

Methods

pure :: a -> Gen a #

(<*>) :: Gen (a -> b) -> Gen a -> Gen b #

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

(*>) :: Check a -> Check b -> Check b #

(<*) :: Check a -> Check b -> Check a #

Applicative ((->) a) 

Methods

pure :: a -> a -> a #

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

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

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

Applicative (Either e) 

Methods

pure :: a -> Either e a #

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

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

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

Applicative f => Applicative (Rec1 f) 

Methods

pure :: a -> Rec1 f a #

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

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

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

Monoid a => Applicative ((,) a) 

Methods

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

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

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

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

Applicative (StateL s) 

Methods

pure :: a -> StateL s a #

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

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

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

Applicative (StateR s) 

Methods

pure :: a -> StateR s a #

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

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

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

Monad m => Applicative (WrappedMonad m) 

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a) 

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

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

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

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

Applicative (ST s) 

Methods

pure :: a -> ST s a #

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

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

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

ParserSource input => Applicative (Parser input) # 

Methods

pure :: a -> Parser input a #

(<*>) :: Parser input (a -> b) -> Parser input a -> Parser input b #

(*>) :: Parser input a -> Parser input b -> Parser input b #

(<*) :: Parser input a -> Parser input b -> Parser input a #

Applicative m => Applicative (ResourceT m) # 

Methods

pure :: a -> ResourceT m a #

(<*>) :: ResourceT m (a -> b) -> ResourceT m a -> ResourceT m b #

(*>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

(<*) :: ResourceT m a -> ResourceT m b -> ResourceT m a #

Applicative (MonadRandomState gen) # 

Methods

pure :: a -> MonadRandomState gen a #

(<*>) :: MonadRandomState gen (a -> b) -> MonadRandomState gen a -> MonadRandomState gen b #

(*>) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen b #

(<*) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen a #

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

Methods

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

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

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

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

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

Methods

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

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

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

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

Arrow a => Applicative (WrappedArrow a b) 

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

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

Methods

pure :: a -> Const * m a #

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

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

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

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

(*>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

(<*) :: ReaderT r m a -> ReaderT r m b -> ReaderT 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 #

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

(<*) :: StateT s m a -> StateT s m b -> StateT s 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 #

(*>) :: 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 f => Applicative (M1 i c f) 

Methods

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

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

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

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

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 #

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

Methods

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

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

return :: a -> [a] #

fail :: String -> [a] #

Monad Maybe 

Methods

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

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

return :: a -> Maybe a #

fail :: String -> Maybe a #

Monad IO 

Methods

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

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

return :: a -> IO a #

fail :: String -> IO a #

Monad U1 

Methods

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

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

return :: a -> U1 a #

fail :: String -> U1 a #

Monad Par1 

Methods

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

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

return :: a -> Par1 a #

fail :: String -> Par1 a #

Monad P 

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

fail :: String -> P a #

Monad Identity 

Methods

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

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

return :: a -> Identity a #

fail :: String -> Identity a #

Monad Min 

Methods

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

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

return :: a -> Min a #

fail :: String -> Min a #

Monad Max 

Methods

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

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

return :: a -> Max a #

fail :: String -> Max 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 Option 

Methods

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

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

return :: a -> Option a #

fail :: String -> Option a #

Monad NonEmpty 

Methods

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

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

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Monad STM 

Methods

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

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

return :: a -> STM a #

fail :: String -> STM a #

Monad Dual 

Methods

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

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

return :: a -> Dual a #

fail :: String -> Dual a #

Monad Sum 

Methods

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

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

return :: a -> Sum a #

fail :: String -> Sum a #

Monad Product 

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 

Methods

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

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

return :: a -> ReadP a #

fail :: String -> ReadP 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 DList # 

Methods

(>>=) :: DList a -> (a -> DList b) -> DList b #

(>>) :: DList a -> DList b -> DList b #

return :: a -> DList a #

fail :: String -> DList 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 ((->) r) 

Methods

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

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

return :: a -> r -> a #

fail :: String -> r -> a #

Monad (Either e) 

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 f => Monad (Rec1 f) 

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 #

Monoid a => Monad ((,) a) 

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) 

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

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) 

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 #

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

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 g) => Monad ((:*:) f g) 

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

(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 f => Monad (M1 i c f) 

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

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] 

Associated Types

type Item [a] :: * #

Methods

fromList :: [Item [a]] -> [a] #

fromListN :: Int -> [Item [a]] -> [a] #

toList :: [a] -> [Item [a]] #

IsList (NonEmpty a) 

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

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

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

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 (ChunkedUArray ty) # 

Associated Types

type Item (ChunkedUArray ty) :: * #

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

Numeric type classes

class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a where Source #

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

class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a where Source #

Non Negative Number literals, convertible through the generic Natural type

Minimal complete definition

toNatural

Methods

toNatural :: a -> Natural Source #

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

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

(+) :: a -> a -> a infixl 6 Source #

scale :: IsNatural n => n -> a -> a Source #

Instances

Additive Double Source # 
Additive Float Source # 
Additive Int Source # 

Methods

azero :: Int Source #

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

scale :: IsNatural n => n -> Int -> Int Source #

Additive Int8 Source # 

Methods

azero :: Int8 Source #

(+) :: Int8 -> Int8 -> Int8 Source #

scale :: IsNatural n => n -> Int8 -> Int8 Source #

Additive Int16 Source # 
Additive Int32 Source # 
Additive Int64 Source # 
Additive Integer Source # 
Additive Word Source # 

Methods

azero :: Word Source #

(+) :: Word -> Word -> Word Source #

scale :: IsNatural n => n -> Word -> Word Source #

Additive Word8 Source # 
Additive Word16 Source # 
Additive Word32 Source # 
Additive Word64 Source # 
Additive Natural Source # 
Additive CSize Source # 
Additive Seconds Source # 
Additive NanoSeconds Source # 
Additive (CountOf ty) Source # 

Methods

azero :: CountOf ty Source #

(+) :: CountOf ty -> CountOf ty -> CountOf ty Source #

scale :: IsNatural n => n -> CountOf ty -> CountOf ty Source #

Additive (Offset ty) Source # 

Methods

azero :: Offset ty Source #

(+) :: Offset ty -> Offset ty -> Offset ty Source #

scale :: IsNatural n => n -> Offset ty -> Offset ty Source #

class Subtractive a where Source #

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

Methods

(-) :: a -> a -> Difference a infixl 6 Source #

Instances

Subtractive Char Source # 

Associated Types

type Difference Char :: * Source #

Methods

(-) :: Char -> Char -> Difference Char Source #

Subtractive Double Source # 

Associated Types

type Difference Double :: * Source #

Subtractive Float Source # 

Associated Types

type Difference Float :: * Source #

Subtractive Int Source # 

Associated Types

type Difference Int :: * Source #

Methods

(-) :: Int -> Int -> Difference Int Source #

Subtractive Int8 Source # 

Associated Types

type Difference Int8 :: * Source #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 Source #

Subtractive Int16 Source # 

Associated Types

type Difference Int16 :: * Source #

Subtractive Int32 Source # 

Associated Types

type Difference Int32 :: * Source #

Subtractive Int64 Source # 

Associated Types

type Difference Int64 :: * Source #

Subtractive Integer Source # 

Associated Types

type Difference Integer :: * Source #

Subtractive Word Source # 

Associated Types

type Difference Word :: * Source #

Methods

(-) :: Word -> Word -> Difference Word Source #

Subtractive Word8 Source # 

Associated Types

type Difference Word8 :: * Source #

Subtractive Word16 Source # 

Associated Types

type Difference Word16 :: * Source #

Subtractive Word32 Source # 

Associated Types

type Difference Word32 :: * Source #

Subtractive Word64 Source # 

Associated Types

type Difference Word64 :: * Source #

Subtractive Natural Source # 

Associated Types

type Difference Natural :: * Source #

Subtractive (CountOf ty) Source # 

Associated Types

type Difference (CountOf ty) :: * Source #

Methods

(-) :: CountOf ty -> CountOf ty -> Difference (CountOf ty) Source #

Subtractive (Offset ty) Source # 

Associated Types

type Difference (Offset ty) :: * Source #

Methods

(-) :: Offset ty -> Offset ty -> Difference (Offset ty) Source #

class Multiplicative a where Source #

Represent class of things that can be multiplied together

x * midentity = x
midentity * x = x

Minimal complete definition

midentity, (*)

Methods

midentity :: a Source #

Identity element over multiplication

(*) :: a -> a -> a infixl 7 Source #

Multiplication of 2 elements that result in another element

(^) :: (IsNatural n, IDivisible n) => a -> n -> a infixr 8 Source #

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 Source # 
Multiplicative Float Source # 
Multiplicative Int Source # 

Methods

midentity :: Int Source #

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

(^) :: (IsNatural n, IDivisible n) => Int -> n -> Int Source #

Multiplicative Int8 Source # 

Methods

midentity :: Int8 Source #

(*) :: Int8 -> Int8 -> Int8 Source #

(^) :: (IsNatural n, IDivisible n) => Int8 -> n -> Int8 Source #

Multiplicative Int16 Source # 
Multiplicative Int32 Source # 
Multiplicative Int64 Source # 
Multiplicative Integer Source # 
Multiplicative Rational Source # 
Multiplicative Word Source # 

Methods

midentity :: Word Source #

(*) :: Word -> Word -> Word Source #

(^) :: (IsNatural n, IDivisible n) => Word -> n -> Word Source #

Multiplicative Word8 Source # 
Multiplicative Word16 Source # 
Multiplicative Word32 Source # 
Multiplicative Word64 Source # 
Multiplicative Natural Source # 

class (Additive a, Multiplicative a) => IDivisible a where Source #

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

mod :: a -> a -> a Source #

divMod :: a -> a -> (a, a) Source #

Instances

IDivisible Int Source # 

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

divMod :: Int -> Int -> (Int, Int) Source #

IDivisible Int8 Source # 

Methods

div :: Int8 -> Int8 -> Int8 Source #

mod :: Int8 -> Int8 -> Int8 Source #

divMod :: Int8 -> Int8 -> (Int8, Int8) Source #

IDivisible Int16 Source # 
IDivisible Int32 Source # 
IDivisible Int64 Source # 
IDivisible Integer Source # 
IDivisible Word Source # 

Methods

div :: Word -> Word -> Word Source #

mod :: Word -> Word -> Word Source #

divMod :: Word -> Word -> (Word, Word) Source #

IDivisible Word8 Source # 
IDivisible Word16 Source # 
IDivisible Word32 Source # 
IDivisible Word64 Source # 
IDivisible Natural Source # 

class Multiplicative a => Divisible a where Source #

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

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 

Methods

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

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

return :: a -> Maybe a #

fail :: String -> Maybe a #

Functor Maybe 

Methods

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

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

Applicative Maybe 

Methods

pure :: a -> Maybe a #

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

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

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

Foldable Maybe 

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 

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

Generic1 Maybe 

Associated Types

type Rep1 (Maybe :: * -> *) :: * -> * #

Methods

from1 :: Maybe a -> Rep1 Maybe a #

to1 :: Rep1 Maybe a -> Maybe a #

Alternative Maybe 

Methods

empty :: Maybe a #

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

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

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

MonadPlus Maybe 

Methods

mzero :: Maybe a #

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

MonadFailure Maybe Source # 

Associated Types

type Failure (Maybe :: * -> *) :: * Source #

Methods

mFail :: Failure Maybe -> Maybe () Source #

Eq a => Eq (Maybe a) 

Methods

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

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

Data a => Data (Maybe a) 

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

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 is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

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

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

NormalForm a => NormalForm (Maybe a) Source # 

Methods

toNormalForm :: Maybe a -> () Source #

Arbitrary a => Arbitrary (Maybe a) Source # 

Methods

arbitrary :: Gen (Maybe a) Source #

SingI (Maybe a) (Nothing a) 

Methods

sing :: Sing (Nothing a) a

SingKind a (KProxy a) => SingKind (Maybe a) (KProxy (Maybe a)) 

Associated Types

type DemoteRep (KProxy (Maybe a)) (kparam :: KProxy (KProxy (Maybe a))) :: *

Methods

fromSing :: Sing (KProxy (Maybe a)) a -> DemoteRep (KProxy (Maybe a)) kparam

SingI a a1 => SingI (Maybe a) (Just a a1) 

Methods

sing :: Sing (Just a a1) a

type Rep1 Maybe 
type Failure Maybe Source # 
type Failure Maybe = ()
type Rep (Maybe a) 
data Sing (Maybe a) 
data Sing (Maybe a) where
type (==) (Maybe k) a b 
type (==) (Maybe k) a b = EqMaybe k a b
type DemoteRep (Maybe a) (KProxy (Maybe a)) 
type DemoteRep (Maybe a) (KProxy (Maybe a)) = Maybe (DemoteRep a (KProxy a))

data Ordering :: * #

Constructors

LT 
EQ 
GT 

Instances

Bounded Ordering 
Enum Ordering 
Eq Ordering 
Data Ordering 

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 
Show Ordering 
Ix Ordering 
Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Semigroup Ordering 
Monoid Ordering 
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 
Enum Bool 

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 

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

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Ix Bool 

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 #

Storable Bool 

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 
FiniteBits Bool 
NormalForm Bool Source # 

Methods

toNormalForm :: Bool -> () Source #

Arbitrary Bool Source # 
IsProperty Bool Source # 
SingI Bool False 

Methods

sing :: Sing False a

SingI Bool True 

Methods

sing :: Sing True a

SingKind Bool (KProxy Bool) 

Associated Types

type DemoteRep (KProxy Bool) (kparam :: KProxy (KProxy Bool)) :: *

Methods

fromSing :: Sing (KProxy Bool) a -> DemoteRep (KProxy Bool) kparam

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 (==) Bool a b 
type (==) Bool a b = EqBool a b
type DemoteRep Bool (KProxy Bool) 
type DemoteRep Bool (KProxy Bool) = Bool

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

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 

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

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Ix Char 

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

Methods

toChar :: Char -> Char #

fromChar :: Char -> Char #

Storable Char 

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

Subtractive Char Source # 

Associated Types

type Difference Char :: * Source #

Methods

(-) :: Char -> Char -> Difference Char Source #

NormalForm Char Source # 

Methods

toNormalForm :: Char -> () Source #

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

Generic1 (URec Char) 

Associated Types

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

Methods

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

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

Eq (URec Char p) 

Methods

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

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

Ord (URec Char p) 

Methods

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

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

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

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

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

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

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

Show (URec Char p) 

Methods

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

show :: URec Char p -> String #

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

Generic (URec Char p) 

Associated Types

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

Methods

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

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

data URec Char

Used for marking occurrences of Char#

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

data 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 

Methods

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

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

return :: a -> IO a #

fail :: String -> IO a #

Functor IO 

Methods

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

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

Applicative IO 

Methods

pure :: a -> IO a #

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

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

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

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

Alternative IO 

Methods

empty :: IO a #

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

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

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

MonadPlus IO 

Methods

mzero :: IO a #

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

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 #

PrimMonad IO Source # 

Associated Types

type PrimState (IO :: * -> *) :: * Source #

type PrimVar (IO :: * -> *) :: * -> * Source #

MonadRandom IO Source # 
Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

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

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

(~) * a () => PrintfType (IO a) 

Methods

spr :: String -> [UPrintf] -> IO a

(~) * a () => HPrintfType (IO a) 

Methods

hspr :: Handle -> String -> [UPrintf] -> IO a

type PrimState IO Source # 
type PrimVar IO Source # 

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 

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) 

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) 

Methods

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

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

Applicative (Either e) 

Methods

pure :: a -> Either e a #

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

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

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

Foldable (Either a) 

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) 

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

Generic1 (Either a) 

Associated Types

type Rep1 (Either a :: * -> *) :: * -> * #

Methods

from1 :: Either a a -> Rep1 (Either a) a #

to1 :: Rep1 (Either a) a -> Either a a #

MonadFailure (Either a) Source # 

Associated Types

type Failure (Either a :: * -> *) :: * Source #

Methods

mFail :: Failure (Either a) -> Either a () Source #

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

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) 

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

Methods

toNormalForm :: Either l r -> () Source #

(Arbitrary l, Arbitrary r) => Arbitrary (Either l r) Source # 

Methods

arbitrary :: Gen (Either l r) Source #

type Rep1 (Either a) 
type Failure (Either a) Source # 
type Failure (Either a) = a
type Rep (Either a b) 
type (==) (Either k k1) a b 
type (==) (Either k k1) a b = EqEither k k1 a b

Numbers

data Int8 :: * #

8-bit signed integer type

Instances

Bounded Int8 
Enum Int8 

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 

Methods

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

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

Integral Int8 

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 

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 

Methods

(+) :: Int8 -> Int8 -> Int8 #

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

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8 

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

Methods

toRational :: Int8 -> Rational #

Show Int8 

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8 

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

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 
FiniteBits Int8 
HasNegation Int8 Source # 

Methods

negate :: Int8 -> Int8 Source #

Integral Int8 Source # 
IsIntegral Int8 Source # 
Additive Int8 Source # 

Methods

azero :: Int8 Source #

(+) :: Int8 -> Int8 -> Int8 Source #

scale :: IsNatural n => n -> Int8 -> Int8 Source #

IDivisible Int8 Source # 

Methods

div :: Int8 -> Int8 -> Int8 Source #

mod :: Int8 -> Int8 -> Int8 Source #

divMod :: Int8 -> Int8 -> (Int8, Int8) Source #

Multiplicative Int8 Source # 

Methods

midentity :: Int8 Source #

(*) :: Int8 -> Int8 -> Int8 Source #

(^) :: (IsNatural n, IDivisible n) => Int8 -> n -> Int8 Source #

Subtractive Int8 Source # 

Associated Types

type Difference Int8 :: * Source #

Methods

(-) :: Int8 -> Int8 -> Difference Int8 Source #

Signed Int8 Source # 

Methods

abs :: Int8 -> Int8 Source #

signum :: Int8 -> Sign Source #

NormalForm Int8 Source # 

Methods

toNormalForm :: Int8 -> () Source #

PrimType Int8 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 #

Hashable Int8 Source # 

Methods

hashMix :: Hasher st => Int8 -> st -> st Source #

Arbitrary Int8 Source # 
IntegralUpsize Int8 Int Source # 
IntegralUpsize Int8 Int16 Source # 
IntegralUpsize Int8 Int32 Source # 
IntegralUpsize Int8 Int64 Source # 
IntegralUpsize Int8 Integer Source # 
IntegralDownsize Int Int8 Source # 
IntegralDownsize Int64 Int8 Source # 
IntegralDownsize Integer Int8 Source # 
type Difference Int8 Source # 

data Int16 :: * #

16-bit signed integer type

Instances

Bounded Int16 
Enum Int16 
Eq Int16 

Methods

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

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

Integral Int16 
Data Int16 

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

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

Methods

toRational :: Int16 -> Rational #

Show Int16 

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16 
PrintfArg Int16 
Storable Int16 

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 
FiniteBits Int16 
HasNegation Int16 Source # 

Methods

negate :: Int16 -> Int16 Source #

Integral Int16 Source # 
IsIntegral Int16 Source # 
Additive Int16 Source # 
IDivisible Int16 Source # 
Multiplicative Int16 Source # 
Subtractive Int16 Source # 

Associated Types

type Difference Int16 :: * Source #

Signed Int16 Source # 
NormalForm Int16 Source # 

Methods

toNormalForm :: Int16 -> () Source #

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

Hashable Int16 Source # 

Methods

hashMix :: Hasher st => Int16 -> st -> st Source #

Arbitrary Int16 Source # 
IntegralUpsize Int8 Int16 Source # 
IntegralUpsize Int16 Int Source # 
IntegralUpsize Int16 Int32 Source # 
IntegralUpsize Int16 Int64 Source # 
IntegralUpsize Int16 Integer Source # 
IntegralUpsize Word8 Int16 Source # 
IntegralDownsize Int Int16 Source # 
IntegralDownsize Int64 Int16 Source # 
IntegralDownsize Integer Int16 Source # 
type Difference Int16 Source # 

data Int32 :: * #

32-bit signed integer type

Instances

Bounded Int32 
Enum Int32 
Eq Int32 

Methods

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

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

Integral Int32 
Data Int32 

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

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

Methods

toRational :: Int32 -> Rational #

Show Int32 

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32 
PrintfArg Int32 
Storable Int32 

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 
FiniteBits Int32 
HasNegation Int32 Source # 

Methods

negate :: Int32 -> Int32 Source #

Integral Int32 Source # 
IsIntegral Int32 Source # 
Additive Int32 Source # 
IDivisible Int32 Source # 
Multiplicative Int32 Source # 
Subtractive Int32 Source # 

Associated Types

type Difference Int32 :: * Source #

Signed Int32 Source # 
NormalForm Int32 Source # 

Methods

toNormalForm :: Int32 -> () Source #

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

Hashable Int32 Source # 

Methods

hashMix :: Hasher st => Int32 -> st -> st Source #

Arbitrary Int32 Source # 
IntegralUpsize Int8 Int32 Source # 
IntegralUpsize Int16 Int32 Source # 
IntegralUpsize Int32 Int Source # 
IntegralUpsize Int32 Int64 Source # 
IntegralUpsize Int32 Integer Source # 
IntegralUpsize Word8 Int32 Source # 
IntegralDownsize Int Int32 Source # 
IntegralDownsize Int64 Int32 Source # 
IntegralDownsize Integer Int32 Source # 
type Difference Int32 Source # 

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

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

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

Integral Int64 
Data Int64 

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

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

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
PrintfArg Int64 
Storable Int64 

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 
FiniteBits Int64 
HasNegation Int64 Source # 

Methods

negate :: Int64 -> Int64 Source #

Integral Int64 Source # 
IsIntegral Int64 Source # 
Additive Int64 Source # 
IDivisible Int64 Source # 
Multiplicative Int64 Source # 
Subtractive Int64 Source # 

Associated Types

type Difference Int64 :: * Source #

Signed Int64 Source # 
NormalForm Int64 Source # 

Methods

toNormalForm :: Int64 -> () Source #

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

Hashable Int64 Source # 

Methods

hashMix :: Hasher st => Int64 -> st -> st Source #

Arbitrary Int64 Source # 
IntegralCast Int64 Word64 Source # 
IntegralCast Word64 Int64 Source # 
IntegralUpsize Int Int64 Source # 
IntegralUpsize Int8 Int64 Source # 
IntegralUpsize Int16 Int64 Source # 
IntegralUpsize Int32 Int64 Source # 
IntegralUpsize Int64 Integer Source # 
IntegralUpsize Word8 Int64 Source # 
IntegralDownsize Int64 Int Source # 
IntegralDownsize Int64 Int8 Source # 
IntegralDownsize Int64 Int16 Source # 
IntegralDownsize Int64 Int32 Source # 
IntegralDownsize Integer Int64 Source # 
type Difference Int64 Source # 

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

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

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

Integral Word8 
Data Word8 

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

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

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
PrintfArg Word8 
Storable Word8 

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 
FiniteBits Word8 
HasNegation Word8 Source # 

Methods

negate :: Word8 -> Word8 Source #

Integral Word8 Source # 
IsNatural Word8 Source # 
IsIntegral Word8 Source # 
Additive Word8 Source # 
IDivisible Word8 Source # 
Multiplicative Word8 Source # 
Subtractive Word8 Source # 

Associated Types

type Difference Word8 :: * Source #

NormalForm Word8 Source # 

Methods

toNormalForm :: Word8 -> () Source #

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

Hashable Word8 Source # 

Methods

hashMix :: Hasher st => Word8 -> st -> st Source #

Arbitrary Word8 Source # 
IntegralUpsize Word8 Int Source # 
IntegralUpsize Word8 Int16 Source # 
IntegralUpsize Word8 Int32 Source # 
IntegralUpsize Word8 Int64 Source # 
IntegralUpsize Word8 Integer Source # 
IntegralUpsize Word8 Word Source # 
IntegralUpsize Word8 Word16 Source # 
IntegralUpsize Word8 Word32 Source # 
IntegralUpsize Word8 Word64 Source # 
IntegralUpsize Word8 Natural Source # 
IntegralDownsize Integer Word8 Source # 
IntegralDownsize Word16 Word8 Source # 
IntegralDownsize Word32 Word8 Source # 
IntegralDownsize Word64 Word8 Source # 
IntegralDownsize Natural Word8 Source # 
type Difference Word8 Source # 

data Word16 :: * #

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 

Methods

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

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

Integral Word16 
Data Word16 

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 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
PrintfArg Word16 
Storable Word16 
Bits Word16 
FiniteBits Word16 
HasNegation Word16 Source # 

Methods

negate :: Word16 -> Word16 Source #

Integral Word16 Source # 
ByteSwap Word16 Source # 

Methods

byteSwap :: Word16 -> Word16

IsNatural Word16 Source # 
IsIntegral Word16 Source # 
Additive Word16 Source # 
IDivisible Word16 Source # 
Multiplicative Word16 Source # 
Subtractive Word16 Source # 

Associated Types

type Difference Word16 :: * Source #

NormalForm Word16 Source # 

Methods

toNormalForm :: Word16 -> () Source #

PrimType Word16 Source # 
StorableFixed Word16 Source # 
Storable Word16 Source # 
Hashable Word16 Source # 

Methods

hashMix :: Hasher st => Word16 -> st -> st Source #

Arbitrary Word16 Source # 
IntegralUpsize Word8 Word16 Source # 
IntegralUpsize Word16 Integer Source # 
IntegralUpsize Word16 Word Source # 
IntegralUpsize Word16 Word32 Source # 
IntegralUpsize Word16 Word64 Source # 
IntegralUpsize Word16 Natural Source # 
IntegralDownsize Integer Word16 Source # 
IntegralDownsize Word16 Word8 Source # 
IntegralDownsize Word32 Word16 Source # 
IntegralDownsize Word64 Word16 Source # 
IntegralDownsize Natural Word16 Source # 
StorableFixed (BE Word16) Source # 

Methods

size :: proxy (BE Word16) -> CountOf Word8 Source #

alignment :: proxy (BE Word16) -> CountOf Word8 Source #

StorableFixed (LE Word16) Source # 

Methods

size :: proxy (LE Word16) -> CountOf Word8 Source #

alignment :: proxy (LE Word16) -> CountOf Word8 Source #

Storable (BE Word16) Source # 

Methods

peek :: Ptr (BE Word16) -> IO (BE Word16) Source #

poke :: Ptr (BE Word16) -> BE Word16 -> IO () Source #

Storable (LE Word16) Source # 

Methods

peek :: Ptr (LE Word16) -> IO (LE Word16) Source #

poke :: Ptr (LE Word16) -> LE Word16 -> IO () Source #

type Difference Word16 Source # 

data Word32 :: * #

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 

Methods

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

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

Integral Word32 
Data Word32 

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 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
PrintfArg Word32 
Storable Word32 
Bits Word32 
FiniteBits Word32 
HasNegation Word32 Source # 

Methods

negate :: Word32 -> Word32 Source #

Integral Word32 Source # 
ByteSwap Word32 Source # 

Methods

byteSwap :: Word32 -> Word32

IsNatural Word32 Source # 
IsIntegral Word32 Source # 
Additive Word32 Source # 
IDivisible Word32 Source # 
Multiplicative Word32 Source # 
Subtractive Word32 Source # 

Associated Types

type Difference Word32 :: * Source #

NormalForm Word32 Source # 

Methods

toNormalForm :: Word32 -> () Source #

PrimType Word32 Source # 
StorableFixed Word32 Source # 
Storable Word32 Source # 
Hashable Word32 Source # 

Methods

hashMix :: Hasher st => Word32 -> st -> st Source #

Arbitrary Word32 Source # 
IntegralUpsize Word8 Word32 Source # 
IntegralUpsize Word16 Word32 Source # 
IntegralUpsize Word32 Integer Source # 
IntegralUpsize Word32 Word Source # 
IntegralUpsize Word32 Word64 Source # 
IntegralUpsize Word32 Natural Source # 
IntegralDownsize Integer Word32 Source # 
IntegralDownsize Word32 Word8 Source # 
IntegralDownsize Word32 Word16 Source # 
IntegralDownsize Word64 Word32 Source # 
IntegralDownsize Natural Word32 Source # 
StorableFixed (BE Word32) Source # 

Methods

size :: proxy (BE Word32) -> CountOf Word8 Source #

alignment :: proxy (BE Word32) -> CountOf Word8 Source #

StorableFixed (LE Word32) Source # 

Methods

size :: proxy (LE Word32) -> CountOf Word8 Source #

alignment :: proxy (LE Word32) -> CountOf Word8 Source #

Storable (BE Word32) Source # 

Methods

peek :: Ptr (BE Word32) -> IO (BE Word32) Source #

poke :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

Storable (LE Word32) Source # 

Methods

peek :: Ptr (LE Word32) -> IO (LE Word32) Source #

poke :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

type Difference Word32 Source # 

data Word64 :: * #

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 

Methods

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

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

Integral Word64 
Data Word64 

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 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
PrintfArg Word64 
Storable Word64 
Bits Word64 
FiniteBits Word64 
HasNegation Word64 Source # 

Methods

negate :: Word64 -> Word64 Source #

Integral Word64 Source # 
ByteSwap Word64 Source # 

Methods

byteSwap :: Word64 -> Word64

IsNatural Word64 Source # 
IsIntegral Word64 Source # 
Additive Word64 Source # 
IDivisible Word64 Source # 
Multiplicative Word64 Source # 
Subtractive Word64 Source # 

Associated Types

type Difference Word64 :: * Source #

NormalForm Word64 Source # 

Methods

toNormalForm :: Word64 -> () Source #

PrimType Word64 Source # 
StorableFixed Word64 Source # 
Storable Word64 Source # 
Hashable Word64 Source # 

Methods

hashMix :: Hasher st => Word64 -> st -> st Source #

Arbitrary Word64 Source # 
IntegralCast Int64 Word64 Source # 
IntegralCast Word64 Int64 Source # 
IntegralUpsize Word Word64 Source # 
IntegralUpsize Word8 Word64 Source # 
IntegralUpsize Word16 Word64 Source # 
IntegralUpsize Word32 Word64 Source # 
IntegralUpsize Word64 Integer Source # 
IntegralUpsize Word64 Natural Source # 
IntegralDownsize Integer Word64 Source # 
IntegralDownsize Word64 Word8 Source # 
IntegralDownsize Word64 Word16 Source # 
IntegralDownsize Word64 Word32 Source # 
IntegralDownsize Natural Word64 Source # 
StorableFixed (BE Word64) Source # 

Methods

size :: proxy (BE Word64) -> CountOf Word8 Source #

alignment :: proxy (BE Word64) -> CountOf Word8 Source #

StorableFixed (LE Word64) Source # 

Methods

size :: proxy (LE Word64) -> CountOf Word8 Source #

alignment :: proxy (LE Word64) -> CountOf Word8 Source #

Storable (BE Word64) Source # 

Methods

peek :: Ptr (BE Word64) -> IO (BE Word64) Source #

poke :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

Storable (LE Word64) Source # 

Methods

peek :: Ptr (LE Word64) -> IO (LE Word64) Source #

poke :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

type Difference Word64 Source # 

data Word :: * #

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

Instances

Bounded Word 
Enum Word 

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 

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 

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 

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

Methods

toRational :: Word -> Rational #

Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word 

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

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 
FiniteBits Word 
HasNegation Word Source # 

Methods

negate :: Word -> Word Source #

Integral Word Source # 
IsNatural Word Source # 
IsIntegral Word Source # 
Additive Word Source # 

Methods

azero :: Word Source #

(+) :: Word -> Word -> Word Source #

scale :: IsNatural n => n -> Word -> Word Source #

IDivisible Word Source # 

Methods

div :: Word -> Word -> Word Source #

mod :: Word -> Word -> Word Source #

divMod :: Word -> Word -> (Word, Word) Source #

Multiplicative Word Source # 

Methods

midentity :: Word Source #

(*) :: Word -> Word -> Word Source #

(^) :: (IsNatural n, IDivisible n) => Word -> n -> Word Source #

Subtractive Word Source # 

Associated Types

type Difference Word :: * Source #

Methods

(-) :: Word -> Word -> Difference Word Source #

NormalForm Word Source # 

Methods

toNormalForm :: Word -> () Source #

PrimType Word Source # 
Arbitrary Word Source # 
IntegralCast Int Word Source # 
IntegralCast Word Int Source # 
IntegralUpsize Word Integer Source # 
IntegralUpsize Word Word64 Source # 
IntegralUpsize Word Natural Source # 
IntegralUpsize Word8 Word Source # 
IntegralUpsize Word16 Word Source # 
IntegralUpsize Word32 Word Source # 
IntegralCast Word (CountOf ty) Source # 

Methods

integralCast :: Word -> CountOf ty Source #

IntegralCast Word (Offset ty) Source # 

Methods

integralCast :: Word -> Offset ty Source #

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

Generic1 (URec Word) 

Associated Types

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

Methods

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

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

Eq (URec Word p) 

Methods

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

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

Ord (URec Word p) 

Methods

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

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

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

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

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

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

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

Show (URec Word p) 

Methods

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

show :: URec Word p -> String #

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

Generic (URec Word p) 

Associated Types

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

Methods

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

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

data URec Word

Used for marking occurrences of Word#

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

data 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 

Methods

minBound :: Int #

maxBound :: Int #

Enum Int 

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 

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 

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 

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

Methods

toRational :: Int -> Rational #

Show Int 

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int 

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

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 

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

Methods

negate :: Int -> Int Source #

Integral Int Source # 
IsIntegral Int Source # 
Additive Int Source # 

Methods

azero :: Int Source #

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

scale :: IsNatural n => n -> Int -> Int Source #

IDivisible Int Source # 

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

divMod :: Int -> Int -> (Int, Int) Source #

Multiplicative Int Source # 

Methods

midentity :: Int Source #

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

(^) :: (IsNatural n, IDivisible n) => Int -> n -> Int Source #

Subtractive Int Source # 

Associated Types

type Difference Int :: * Source #

Methods

(-) :: Int -> Int -> Difference Int Source #

Signed Int Source # 

Methods

abs :: Int -> Int Source #

signum :: Int -> Sign Source #

NormalForm Int Source # 

Methods

toNormalForm :: Int -> () Source #

PrimType Int Source # 
Arbitrary Int Source # 
IntegralCast Int Word Source # 
IntegralCast Word Int Source # 
IntegralUpsize Int Int64 Source # 
IntegralUpsize Int Integer Source # 
IntegralUpsize Int8 Int Source # 
IntegralUpsize Int16 Int Source # 
IntegralUpsize Int32 Int Source # 
IntegralUpsize Word8 Int Source # 
IntegralDownsize Int Int8 Source # 
IntegralDownsize Int Int16 Source # 
IntegralDownsize Int Int32 Source # 
IntegralDownsize Int64 Int Source # 
IntegralCast Int (CountOf ty) Source # 

Methods

integralCast :: Int -> CountOf ty Source #

IntegralCast Int (Offset ty) Source # 

Methods

integralCast :: Int -> Offset ty Source #

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

Generic1 (URec Int) 

Associated Types

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

Methods

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

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

Eq (URec Int p) 

Methods

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

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

Ord (URec Int p) 

Methods

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

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

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

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

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

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

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

Show (URec Int p) 

Methods

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

show :: URec Int p -> String #

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

Generic (URec Int p) 

Associated Types

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

Methods

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

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

data URec Int

Used for marking occurrences of Int#

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

data Integer :: * #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances

Enum Integer 
Eq Integer 

Methods

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

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

Integral Integer 
Data Integer 

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 
Ord Integer 
Read Integer 
Real Integer 
Show Integer 
Ix Integer 
PrintfArg Integer 
Bits Integer 
HasNegation Integer Source # 
Fractional Rational Source # 
Integral Integer Source # 
IsIntegral Integer Source # 
Additive Integer Source # 
Divisible Rational Source # 
IDivisible Integer Source # 
Multiplicative Integer Source # 
Multiplicative Rational Source # 
Subtractive Integer Source # 

Associated Types

type Difference Integer :: * Source #

IntegralRounding Rational Source # 
Signed Integer Source # 
NormalForm Integer Source # 

Methods

toNormalForm :: Integer -> () Source #

Hashable Integer Source # 

Methods

hashMix :: Hasher st => Integer -> st -> st Source #

Arbitrary Integer Source # 
IntegralUpsize Int Integer Source # 
IntegralUpsize Int8 Integer Source # 
IntegralUpsize Int16 Integer Source # 
IntegralUpsize Int32 Integer Source # 
IntegralUpsize Int64 Integer Source # 
IntegralUpsize Word Integer Source # 
IntegralUpsize Word8 Integer Source # 
IntegralUpsize Word16 Integer Source # 
IntegralUpsize Word32 Integer Source # 
IntegralUpsize Word64 Integer Source # 
IntegralUpsize Natural Integer Source # 
IntegralDownsize Integer Int8 Source # 
IntegralDownsize Integer Int16 Source # 
IntegralDownsize Integer Int32 Source # 
IntegralDownsize Integer Int64 Source # 
IntegralDownsize Integer Word8 Source # 
IntegralDownsize Integer Word16 Source # 
IntegralDownsize Integer Word32 Source # 
IntegralDownsize Integer Word64 Source # 
IntegralDownsize Integer Natural Source # 
type Difference Integer Source # 

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

Methods

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

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

Integral Natural 
Data Natural 

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 
Ord Natural 
Read Natural 
Real Natural 
Show Natural 
Ix Natural 
PrintfArg Natural 
Bits Natural 
Integral Natural Source # 
IsNatural Natural Source # 
IsIntegral Natural Source # 
Additive Natural Source # 
IDivisible Natural Source # 
Multiplicative Natural Source # 
Subtractive Natural Source # 

Associated Types

type Difference Natural :: * Source #

NormalForm Natural Source # 

Methods

toNormalForm :: Natural -> () Source #

Hashable Natural Source # 

Methods

hashMix :: Hasher st => Natural -> st -> st Source #

Arbitrary Natural Source # 
IntegralUpsize Word Natural Source # 
IntegralUpsize Word8 Natural Source # 
IntegralUpsize Word16 Natural Source # 
IntegralUpsize Word32 Natural Source # 
IntegralUpsize Word64 Natural Source # 
IntegralUpsize Natural Integer Source # 
IntegralDownsize Integer Natural Source # 
IntegralDownsize Natural Word8 Source # 
IntegralDownsize Natural Word16 Source # 
IntegralDownsize Natural Word32 Source # 
IntegralDownsize Natural Word64 Source # 
type Difference Natural Source # 

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

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 
RealFloat Float 
PrintfArg Float 
Storable Float 

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

HasNegation Float Source # 

Methods

negate :: Float -> Float Source #

Fractional Float Source # 
Integral Float Source # 
Trigonometry Float Source # 
FloatingPoint Float Source # 
Additive Float Source # 
Divisible Float Source # 

Methods

(/) :: Float -> Float -> Float Source #

Multiplicative Float Source # 
Subtractive Float Source # 

Associated Types

type Difference Float :: * Source #

IntegralRounding Float Source # 
Signed Float Source # 
NormalForm Float Source # 

Methods

toNormalForm :: Float -> () Source #

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

Generic1 (URec Float) 

Associated Types

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

Methods

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

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

Eq (URec Float p) 

Methods

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

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

Ord (URec Float p) 

Methods

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

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

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

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

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

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

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

Show (URec Float p) 

Methods

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

show :: URec Float p -> String #

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

Generic (URec Float p) 

Associated Types

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

Methods

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

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

data URec Float

Used for marking occurrences of Float#

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

data Double :: * #

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Eq Double 

Methods

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

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

Floating Double 
Data Double 

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 
RealFloat Double 
PrintfArg Double 
Storable Double 
HasNegation Double Source # 

Methods

negate :: Double -> Double Source #

Fractional Double Source # 
Integral Double Source # 
Trigonometry Double Source # 
FloatingPoint Double Source # 
Additive Double Source # 
Divisible Double Source # 

Methods

(/) :: Double -> Double -> Double Source #

Multiplicative Double Source # 
Subtractive Double Source # 

Associated Types

type Difference Double :: * Source #

IntegralRounding Double Source # 
Signed Double Source # 
NormalForm Double Source # 

Methods

toNormalForm :: Double -> () Source #

PrimType Double Source # 
StorableFixed Double Source # 
Storable Double Source # 
Arbitrary Double Source # 
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) #

Generic1 (URec Double) 

Associated Types

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

Methods

from1 :: URec Double a -> Rep1 (URec Double) a #

to1 :: Rep1 (URec Double) a -> URec Double a #

Eq (URec Double p) 

Methods

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

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

Ord (URec Double p) 

Methods

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

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

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

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

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

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

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

Show (URec Double p) 

Methods

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

show :: URec Double p -> String #

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

Generic (URec Double p) 

Associated Types

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

Methods

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

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

data URec Double

Used for marking occurrences of Double#

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

newtype CountOf ty Source #

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

Methods

integralCast :: Int -> CountOf ty Source #

IntegralCast Word (CountOf ty) Source # 

Methods

integralCast :: Word -> CountOf ty Source #

Enum (CountOf ty) Source # 

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

Methods

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

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

Ord (CountOf ty) Source # 

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

Methods

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

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Monoid (CountOf ty) Source # 

Methods

mempty :: CountOf ty #

mappend :: CountOf ty -> CountOf ty -> CountOf ty #

mconcat :: [CountOf ty] -> CountOf ty #

Integral (CountOf ty) Source # 
IsNatural (CountOf ty) Source # 

Methods

toNatural :: CountOf ty -> Natural Source #

IsIntegral (CountOf ty) Source # 

Methods

toInteger :: CountOf ty -> Integer Source #

Additive (CountOf ty) Source # 

Methods

azero :: CountOf ty Source #

(+) :: CountOf ty -> CountOf ty -> CountOf ty Source #

scale :: IsNatural n => n -> CountOf ty -> CountOf ty Source #

Subtractive (CountOf ty) Source # 

Associated Types

type Difference (CountOf ty) :: * Source #

Methods

(-) :: CountOf ty -> CountOf ty -> Difference (CountOf ty) Source #

NormalForm (CountOf a) Source # 

Methods

toNormalForm :: CountOf a -> () Source #

Arbitrary (CountOf ty) Source # 

Methods

arbitrary :: Gen (CountOf ty) Source #

type Difference (CountOf ty) Source # 
type Difference (CountOf ty) = CountOf ty

newtype Offset ty Source #

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

Methods

integralCast :: Int -> Offset ty Source #

IntegralCast Word (Offset ty) Source # 

Methods

integralCast :: Word -> Offset ty Source #

Enum (Offset ty) Source # 

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

Methods

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

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

Ord (Offset ty) Source # 

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

Methods

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

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

Integral (Offset ty) Source # 
IsNatural (Offset ty) Source # 

Methods

toNatural :: Offset ty -> Natural Source #

IsIntegral (Offset ty) Source # 

Methods

toInteger :: Offset ty -> Integer Source #

Additive (Offset ty) Source # 

Methods

azero :: Offset ty Source #

(+) :: Offset ty -> Offset ty -> Offset ty Source #

scale :: IsNatural n => n -> Offset ty -> Offset ty Source #

Subtractive (Offset ty) Source # 

Associated Types

type Difference (Offset ty) :: * Source #

Methods

(-) :: Offset ty -> Offset ty -> Difference (Offset ty) Source #

NormalForm (Offset a) Source # 

Methods

toNormalForm :: Offset a -> () Source #

type Difference (Offset ty) Source # 
type Difference (Offset ty) = CountOf ty

Collection types

data UArray ty Source #

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

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

Methods

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

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

Data ty => Data (UArray ty) Source # 

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

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

Methods

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

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

PrimType ty => Monoid (UArray ty) Source # 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

NormalForm (UArray ty) Source # 

Methods

toNormalForm :: UArray ty -> () Source #

PrimType ty => Copy (UArray ty) Source # 

Methods

copy :: UArray ty -> UArray ty 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 => 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 => 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 #

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 #

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 #

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

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 Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 
PrimType Seconds Source # 
PrimType NanoSeconds Source # 
PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

data Array a Source #

Array of a

Instances

Functor Array Source # 

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

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

Methods

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

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

Data ty => Data (Array ty) Source # 

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

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

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Monoid (Array a) Source # 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

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

NormalForm a => NormalForm (Array a) Source # 

Methods

toNormalForm :: Array a -> () Source #

Copy (Array ty) Source # 

Methods

copy :: Array ty -> Array ty 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 #

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 #

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 #

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 #

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 #

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 #

type Item (Array ty) Source # 
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 Source #

Opaque packed array of characters in the UTF8 encoding

Instances

IsList String Source # 

Associated Types

type Item String :: * #

Eq String Source # 

Methods

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

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

Data String Source # 

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 Source # 
Show String Source # 
IsString String Source # 

Methods

fromString :: String -> String #

Monoid String Source # 
NormalForm String Source # 

Methods

toNormalForm :: String -> () Source #

Copy String Source # 

Methods

copy :: String -> 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 #

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

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 #

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 #

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

Methods

hashMix :: Hasher st => String -> st -> st Source #

Arbitrary String Source # 
IsProperty (String, Bool) Source # 
type Item String Source # 
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 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 
Monoid () 

Methods

mempty :: () #

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

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

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid String # 
Monoid Builder # 
Monoid AsciiString # 
Monoid Bitmap # 
Monoid FileName # 
Monoid [a] 

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 is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

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

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

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

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

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

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

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

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

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

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

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

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

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

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

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

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

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

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

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

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

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

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

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

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

Monoid (Endo a) 

Methods

mempty :: Endo a #

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

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

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

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

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

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

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

Monoid (First a) 

Methods

mempty :: First a #

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

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

Monoid (Last a) 

Methods

mempty :: Last a #

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

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

Monoid (CountOf ty) # 

Methods

mempty :: CountOf ty #

mappend :: CountOf ty -> CountOf ty -> CountOf ty #

mconcat :: [CountOf ty] -> CountOf ty #

PrimType ty => Monoid (Block ty) # 

Methods

mempty :: Block ty #

mappend :: Block ty -> Block ty -> Block ty #

mconcat :: [Block ty] -> Block ty #

PrimType ty => Monoid (UArray ty) # 

Methods

mempty :: UArray ty #

mappend :: UArray ty -> UArray ty -> UArray ty #

mconcat :: [UArray ty] -> UArray ty #

Monoid (Array a) # 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

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

Monoid (ChunkedUArray a) # 
Monoid (DList a) # 

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

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

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

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

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

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

Methods

mempty :: (a, b) #

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

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

Monoid (Proxy k s) 

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) 

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) 

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) 

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) 

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 #

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 #

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 #

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 (ChunkedUArray ty) 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 #

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

breakElem :: Eq (Element c) => Element c -> c -> (c, c) Source #

Split a collection when the predicate return true

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

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.

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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 #

data NonEmpty a Source #

NonEmpty property for any Collection

Instances

Eq a => Eq (NonEmpty a) Source # 

Methods

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

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

Show a => Show (NonEmpty a) Source # 

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 #

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 #

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 #

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

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 #

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 #

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, Typeable)

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

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

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 (Typeable, 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 
Exception PatternMatchFail 
Exception RecSelError 
Exception RecConError 
Exception RecUpdError 
Exception NoMethodError 
Exception TypeError 
Exception NonTermination 
Exception NestedAtomically 
Exception BlockedIndefinitelyOnMVar 
Exception BlockedIndefinitelyOnSTM 
Exception Deadlock 
Exception AllocationLimitExceeded 
Exception AssertionFailed 
Exception SomeAsyncException 
Exception AsyncException 
Exception ArrayException 
Exception ExitCode 
Exception IOException 
Exception ErrorCall 
Exception ArithException 
Exception SomeException 
Exception PartialError # 
Exception OutOfBound # 
Exception ValidationFailure # 
Typeable * input => Exception (ParseError input) # 

class Typeable k a #

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 :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 

Methods

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

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

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) 

Methods

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

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

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

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

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

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

Foldable (Proxy *) 

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

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

Generic1 (Proxy *) 

Associated Types

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

Methods

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

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

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

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

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

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

MonadPlus (Proxy *) 

Methods

mzero :: Proxy * a #

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

Bounded (Proxy k s) 

Methods

minBound :: Proxy k s #

maxBound :: Proxy k s #

Enum (Proxy k s) 

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) 

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Data t => Data (Proxy * t) 

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) 

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) 
Show (Proxy k s) 

Methods

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

show :: Proxy k s -> String #

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

Ix (Proxy k s) 

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) 

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) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

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

type Rep1 (Proxy *) 
type Rep1 (Proxy *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) U1)
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 #

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

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