base-4.20.0.0: Core data structures and operations
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Prelude

Description

The Prelude: a standard module. The Prelude is imported by default into all Haskell modules unless either there is an explicit import statement for it, or the NoImplicitPrelude extension is enabled.

Synopsis

Standard types, classes and related functions

Basic data types

data Bool Source #

Constructors

False 
True 

Instances

Instances details
Bits Bool Source #

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Bits

FiniteBits Bool Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Bits

Data Bool Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

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

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

toConstr :: Bool -> Constr Source #

dataTypeOf :: Bool -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Bounded Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Enum Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Storable Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Foreign.Storable

Generic Bool Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Associated Types

type DemoteRep Bool 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep Bool = Bool

Methods

fromSing :: forall (a :: Bool). Sing a -> DemoteRep Bool

Ix Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Ix

Read Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Read

Show Bool Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Eq Bool Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Bool Source # 
Instance details

Defined in GHC.Classes

SingI 'False

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

sing :: Sing 'False

SingI 'True

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

sing :: Sing 'True

Lift Bool Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bool -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Bool -> Code m Bool Source #

type DemoteRep Bool Source # 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep Bool = Bool
type Rep Bool Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))
data Sing (a :: Bool) Source # 
Instance details

Defined in GHC.Internal.Generics

data Sing (a :: Bool) where

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

Boolean "and", lazy in the second argument

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

Boolean "or", lazy in the second argument

not :: Bool -> Bool Source #

Boolean "not"

otherwise :: Bool Source #

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

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

data Maybe a Source #

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

Instances details
Eq1 Maybe Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 Maybe Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 Maybe Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Show1 Maybe Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Alternative Maybe Source #

Picks the leftmost Just value, or, alternatively, Nothing.

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

empty :: Maybe a Source #

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

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

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

Applicative Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

pure :: a -> Maybe a Source #

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

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

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

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

Functor Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Monad Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

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

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

return :: a -> Maybe a Source #

MonadPlus Maybe Source #

Picks the leftmost Just value, or, alternatively, Nothing.

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

mzero :: Maybe a Source #

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

MonadFail Maybe Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fail

Methods

fail :: String -> Maybe a Source #

MonadFix Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Maybe a) -> Maybe a Source #

MonadZip Maybe Source #

Since: ghc-internal-4.8.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Zip

Methods

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

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

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

Foldable Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Maybe m -> m Source #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Maybe a -> m Source #

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

foldr' :: (a -> b -> b) -> b -> Maybe a -> b Source #

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

foldl' :: (b -> a -> b) -> b -> Maybe a -> b Source #

foldr1 :: (a -> a -> a) -> Maybe a -> a Source #

foldl1 :: (a -> a -> a) -> Maybe a -> a Source #

toList :: Maybe a -> [a] Source #

null :: Maybe a -> Bool Source #

length :: Maybe a -> Int Source #

elem :: Eq a => a -> Maybe a -> Bool Source #

maximum :: Ord a => Maybe a -> a Source #

minimum :: Ord a => Maybe a -> a Source #

sum :: Num a => Maybe a -> a Source #

product :: Num a => Maybe a -> a Source #

Traversable Maybe Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) Source #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) Source #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) Source #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) Source #

Generic1 Maybe Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

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

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

Lift a => Lift (Maybe a :: Type) Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Maybe a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Maybe a -> Code m (Maybe a) Source #

Semigroup a => Monoid (Maybe a) Source #

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 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Methods

mempty :: Maybe a Source #

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

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

Semigroup a => Semigroup (Maybe a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

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

sconcat :: NonEmpty (Maybe a) -> Maybe a Source #

stimes :: Integral b => b -> Maybe a -> Maybe a Source #

Data a => Data (Maybe a) Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

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

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

toConstr :: Maybe a -> Constr Source #

dataTypeOf :: Maybe a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic (Maybe a) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Maybe a -> Rep (Maybe a) x Source #

to :: Rep (Maybe a) x -> Maybe a Source #

SingKind a => SingKind (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Associated Types

type DemoteRep (Maybe a) 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> DemoteRep (Maybe a)

Read a => Read (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Read

Show a => Show (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Eq a => Eq (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Maybe

Methods

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

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

Ord a => Ord (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Maybe

Methods

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

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

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

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

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

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

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

SingI ('Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

sing :: Sing ('Nothing :: Maybe a)

SingI a2 => SingI ('Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

sing :: Sing ('Just a2)

type Rep1 Maybe Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type DemoteRep (Maybe a) Source # 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep a)
type Rep (Maybe a) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Internal.Maybe" "ghc-internal" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
data Sing (b :: Maybe a) Source # 
Instance details

Defined in GHC.Internal.Generics

data Sing (b :: Maybe a) where

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

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

Expand

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 GHC.Internal.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
""

data Either a b Source #

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

Expand

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

Instances details
Bifoldable Either Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

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

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

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

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

Bifoldable1 Either Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => Either m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Either a b -> m Source #

Bifunctor Either Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

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

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

Bitraversable Either Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

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

Eq2 Either Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 Either Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read2 Either Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

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

Show2 Either Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Either a :: Type -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

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

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

(Lift a, Lift b) => Lift (Either a b :: Type) Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Either a b -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Either a b -> Code m (Either a b) Source #

Eq a => Eq1 (Either a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord a => Ord1 (Either a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read a => Read1 (Either a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

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

Show a => Show1 (Either a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Applicative (Either e) Source #

Since: base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

pure :: a -> Either e a Source #

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

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c Source #

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

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

Functor (Either a) Source #

Since: base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

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

Monad (Either e) Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b Source #

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

return :: a -> Either e a Source #

MonadFix (Either e) Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

mfix :: (a -> Either e a) -> Either e a Source #

Foldable (Either a) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Either a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

toList :: Either a a0 -> [a0] Source #

null :: Either a a0 -> Bool Source #

length :: Either a a0 -> Int Source #

elem :: Eq a0 => a0 -> Either a a0 -> Bool Source #

maximum :: Ord a0 => Either a a0 -> a0 Source #

minimum :: Ord a0 => Either a a0 -> a0 Source #

sum :: Num a0 => Either a a0 -> a0 Source #

product :: Num a0 => Either a a0 -> a0 Source #

Traversable (Either a) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source #

Semigroup (Either a b) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

sconcat :: NonEmpty (Either a b) -> Either a b Source #

stimes :: Integral b0 => b0 -> Either a b -> Either a b Source #

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

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

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

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

toConstr :: Either a b -> Constr Source #

dataTypeOf :: Either a b -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic (Either a b) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Either a b) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

Methods

from :: Either a b -> Rep (Either a b) x Source #

to :: Rep (Either a b) x -> Either a b Source #

(Read a, Read b) => Read (Either a b) Source #

Since: base-3.0

Instance details

Defined in GHC.Internal.Data.Either

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

Since: base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

show :: Either a b -> String Source #

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

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

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

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Either

Methods

compare :: Either a b -> Either a b -> Ordering Source #

(<) :: Either a b -> Either a b -> Bool Source #

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

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

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

max :: Either a b -> Either a b -> Either a b Source #

min :: Either a b -> Either a b -> Either a b Source #

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

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Either a b) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Either a b) = D1 ('MetaData "Either" "GHC.Internal.Data.Either" "ghc-internal" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

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

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

Expand

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

data Ordering Source #

Constructors

LT 
EQ 
GT 

Instances

Instances details
Monoid Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Base

Semigroup Ordering Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Data Ordering Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

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

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

toConstr :: Ordering -> Constr Source #

dataTypeOf :: Ordering -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Bounded Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Enum Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Generic Ordering Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))
Ix Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Ix

Read Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Read

Show Ordering Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Eq Ordering Source # 
Instance details

Defined in GHC.Classes

Ord Ordering Source # 
Instance details

Defined in GHC.Classes

type Rep Ordering Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

data Char Source #

The character type Char represents Unicode codespace and its elements are code points as in definitions D9 and D10 of the Unicode Standard.

Character literals in Haskell are single-quoted: 'Q', 'Я' or 'Ω'. To represent a single quote itself use '\'', and to represent a backslash use '\\'. The full grammar can be found in the section 2.6 of the Haskell 2010 Language Report.

To specify a character by its code point one can use decimal, hexadecimal or octal notation: '\65', '\x41' and '\o101' are all alternative forms of 'A'. The largest code point is '\x10ffff'.

There is a special escape syntax for ASCII control characters:

EscapeAlternativesMeaning
'\NUL''\0'null character
'\SOH''\1'start of heading
'\STX''\2'start of text
'\ETX''\3'end of text
'\EOT''\4'end of transmission
'\ENQ''\5'enquiry
'\ACK''\6'acknowledge
'\BEL''\7', '\a'bell (alert)
'\BS''\8', '\b'backspace
'\HT''\9', '\t'horizontal tab
'\LF''\10', '\n'line feed (new line)
'\VT''\11', '\v'vertical tab
'\FF''\12', '\f'form feed
'\CR''\13', '\r'carriage return
'\SO''\14'shift out
'\SI''\15'shift in
'\DLE''\16'data link escape
'\DC1''\17'device control 1
'\DC2''\18'device control 2
'\DC3''\19'device control 3
'\DC4''\20'device control 4
'\NAK''\21'negative acknowledge
'\SYN''\22'synchronous idle
'\ETB''\23'end of transmission block
'\CAN''\24'cancel
'\EM''\25'end of medium
'\SUB''\26'substitute
'\ESC''\27'escape
'\FS''\28'file separator
'\GS''\29'group separator
'\RS''\30'record separator
'\US''\31'unit separator
'\SP''\32', ' 'space
'\DEL''\127'delete

Data.Char provides utilities to work with Char.

Instances

Instances details
IsChar Char Source #

Since: base-2.1

Instance details

Defined in Text.Printf

PrintfArg Char Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Data Char Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

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

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

toConstr :: Char -> Constr Source #

dataTypeOf :: Char -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Bounded Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Enum Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Storable Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Foreign.Storable

Ix Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Ix

Read Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Read

Show Char Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Eq Char Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Char Source # 
Instance details

Defined in GHC.Classes

TestCoercion SChar Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testCoercion :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (Coercion a b) Source #

TestEquality SChar Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testEquality :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (a :~: b) Source #

Lift Char Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Char -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Char -> Code m Char Source #

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

Defined in GHC.Internal.Generics

Associated Types

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))

Methods

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

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

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

Since: base-4.21.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Since: base-4.21.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Since: base-4.21.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => UChar m -> m Source #

foldMap :: Monoid m => (a -> m) -> UChar a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source #

foldr :: (a -> b -> b) -> b -> UChar a -> b Source #

foldr' :: (a -> b -> b) -> b -> UChar a -> b Source #

foldl :: (b -> a -> b) -> b -> UChar a -> b Source #

foldl' :: (b -> a -> b) -> b -> UChar a -> b Source #

foldr1 :: (a -> a -> a) -> UChar a -> a Source #

foldl1 :: (a -> a -> a) -> UChar a -> a Source #

toList :: UChar a -> [a] Source #

null :: UChar a -> Bool Source #

length :: UChar a -> Int Source #

elem :: Eq a => a -> UChar a -> Bool Source #

maximum :: Ord a => UChar a -> a Source #

minimum :: Ord a => UChar a -> a Source #

sum :: Num a => UChar a -> a Source #

product :: Num a => UChar a -> a Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Generic (URec Char p) Source # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

Methods

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

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

Show (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Ord (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

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

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

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

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

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

data URec Char (p :: k) Source #

Used for marking occurrences of Char#

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

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

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Char) (b :: Char) = CmpChar a b
type Rep1 (URec Char :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec Char :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: k -> Type)))
type Rep (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

type String = [Char] Source #

String is an alias for a list of characters.

String constants in Haskell are values of type String. That means if you write a string literal like "hello world", it will have the type [Char], which is the same as String.

Note: You can ask the compiler to automatically infer different types with the -XOverloadedStrings language extension, for example "hello world" :: Text. See IsString for more information.

Because String is just a list of characters, you can use normal list functions to do basic string manipulation. See Data.List for operations on lists.

Performance considerations

Expand

[Char] is a relatively memory-inefficient type. It is a linked list of boxed word-size characters, internally it looks something like:

╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭────╮
│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ [] │
╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰────╯
        v               v               v
       'a'             'b'             'c'

The String "abc" will use 5*3+1 = 16 (in general 5n+1) words of space in memory.

Furthermore, operations like (++) (string concatenation) are O(n) (in the left argument).

For historical reasons, the base library uses String in a lot of places for the conceptual simplicity, but library code dealing with user-data should use the text package for Unicode text, or the the bytestring package for binary data.

Tuples

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

Extract the first component of a pair.

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

Extract the second component of a pair.

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

Convert an uncurried function to a curried function.

Examples

Expand
>>> curry fst 1 2
1

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

uncurry converts a curried function to a function on pairs.

Examples

Expand
>>> uncurry (+) (1,2)
3
>>> uncurry ($) (show, 1)
"1"
>>> map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]

Basic type classes

class Eq a where Source #

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.

The Haskell Report defines no laws for Eq. However, instances are encouraged to follow these properties:

Reflexivity
x == x = True
Symmetry
x == y = y == x
Transitivity
if x == y && y == z = True, then x == z = True
Extensionality
if x == y = True and f is a function whose return type is an instance of Eq, then f x == f y = True
Negation
x /= y = not (x == y)

Minimal complete definition

(==) | (/=)

Methods

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

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

Instances

Instances details
Eq ByteArray Source #

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Eq Timeout Source # 
Instance details

Defined in System.Timeout

Eq BigNat # 
Instance details

Defined in GHC.Num.BigNat

Eq Void Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Eq ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Eq ClosureType Source # 
Instance details

Defined in GHC.Internal.ClosureTypes

Eq BlockReason Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq ThreadId Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq ThreadStatus Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Eq Constr Source #

Equality of constructors

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq ConstrRep Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq DataRep Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq Fixity Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Eq All Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Eq Any Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Eq SomeTypeRep Source # 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Eq Unique Source # 
Instance details

Defined in GHC.Internal.Data.Unique

Eq Version Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Version

Eq ControlMessage Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Control

Methods

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

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

Eq Event Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

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

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

Eq EventLifetime Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Methods

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

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

Eq Lifetime Source #

Since: base-4.8.1.0

Instance details

Defined in GHC.Internal.Event.Internal.Types

Eq FdKey Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Methods

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

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

Eq State Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Manager

Methods

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

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

Eq TimeoutKey Source # 
Instance details

Defined in GHC.Internal.Event.TimeOut

Eq State Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Event.TimerManager

Methods

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

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

Eq Unique Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Unique

Methods

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

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

Eq ErrorCall Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Exception

Eq ArithException Source #

Since: base-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Eq SpecConstrAnnotation Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Exts

Eq Fingerprint Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Eq Errno Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Foreign.C.Error

Methods

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

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

Eq CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Methods

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

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

Eq CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Eq IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq ForeignSrcLang Source # 
Instance details

Defined in GHC.Internal.ForeignSrcLang

Eq Associativity Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Eq DecidedStrictness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq Fixity Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

Eq SourceStrictness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq SourceUnpackedness Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Eq MaskingState Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.IO

Eq BufferState Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Buffer

Eq IODeviceType Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Eq SeekMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Device

Eq CodingProgress Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.IO.Encoding.Types

Eq ArrayException Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq AsyncException Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq ExitCode Source # 
Instance details

Defined in GHC.Internal.IO.Exception

Eq IOErrorType Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq IOException Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Exception

Eq HandlePosn Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle

Eq BufferMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq Handle Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq Newline Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq NewlineMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.Handle.Types

Eq IOMode Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.IO.IOMode

Eq IoSubSystem Source # 
Instance details

Defined in GHC.Internal.IO.SubSystem

Eq InfoProv Source # 
Instance details

Defined in GHC.Internal.InfoProv.Types

Eq Int16 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Methods

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

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

Eq Int32 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Methods

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

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

Eq Int64 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Methods

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

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

Eq Int8 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Methods

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

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

Eq Extension Source # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Eq IoManagerFlag Source # 
Instance details

Defined in GHC.Internal.RTS.Flags

Eq StackEntry Source # 
Instance details

Defined in GHC.Internal.Stack.CloneStack

Eq SrcLoc Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Stack.Types

Eq CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CTimer Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Eq CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

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

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

Eq AnnLookup Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq AnnTarget Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Bang Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq BndrVis Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Body Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Bytes Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Callconv Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Clause Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Con Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Dec Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq DecidedStrictness Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DerivClause Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DerivStrategy Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DocLoc Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Exp Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq FamilyResultSig Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Fixity Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq FixityDirection Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Foreign Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq FunDep Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Guard Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Info Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq InjectivityAnn Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Inline Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Lit Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Loc Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Match Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq ModName Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Module Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq ModuleInfo Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Name Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq NameFlavour Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq NameSpace Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq NamespaceSpecifier Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq OccName Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Overlap Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Pat Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq PatSynArgs Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq PatSynDir Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Phases Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq PkgName Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Pragma Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Range Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq Role Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq RuleBndr Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq RuleMatch Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Safety Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq SourceStrictness Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq SourceUnpackedness Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Specificity Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Stmt Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq TyLit Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq TySynEqn Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Type Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Eq TypeFamilyHead Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Lexeme Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Text.Read.Lex

Eq Number Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Text.Read.Lex

Eq SomeChar Source # 
Instance details

Defined in GHC.Internal.TypeLits

Eq SomeSymbol Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeLits

Eq SomeNat Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.TypeNats

Eq GeneralCategory Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Unicode

Eq Word16 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Eq Word32 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Eq Word64 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Eq Word8 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Methods

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

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

Eq Module Source # 
Instance details

Defined in GHC.Classes

Eq Ordering Source # 
Instance details

Defined in GHC.Classes

Eq TrName Source # 
Instance details

Defined in GHC.Classes

Eq TyCon Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Integer # 
Instance details

Defined in GHC.Num.Integer

Eq Natural # 
Instance details

Defined in GHC.Num.Natural

Eq () Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Bool Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Char Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Double Source #

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

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

Also note that Double's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Eq Float Source #

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

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

Also note that Float's Eq instance does not satisfy extensionality:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Int Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq Word Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq (Chan a) Source #

Since: base-4.4.0.0

Instance details

Defined in Control.Concurrent.Chan

Methods

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

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

Eq (MutableByteArray s) Source #

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Eq a => Eq (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

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

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

Eq a => Eq (First a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

Eq a => Eq (Last a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

Eq a => Eq (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

Eq a => Eq (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

Eq m => Eq (WrappedMonoid m) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq (NonEmpty a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Eq (TVar a) Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

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

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

Eq a => Eq (And a) Source #

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

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

Eq a => Eq (Iff a) Source #

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

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

Eq a => Eq (Ior a) Source #

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

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

Eq a => Eq (Xor a) Source #

Since: base-4.16

Instance details

Defined in GHC.Internal.Data.Bits

Methods

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

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

Eq a => Eq (Identity a) Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

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

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

Eq a => Eq (First a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

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

Eq a => Eq (Last a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

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

Eq a => Eq (Down a) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

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

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

Eq a => Eq (Dual a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Eq a => Eq (Product a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Eq a => Eq (Sum a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

Eq (ConstPtr a) Source # 
Instance details

Defined in GHC.Internal.Foreign.C.ConstPtr

Methods

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

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

Eq (ForeignPtr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.ForeignPtr

Eq a => Eq (ZipList a) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Functor.ZipList

Methods

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

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

Eq p => Eq (Par1 p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (IOPort a) Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IOPort

Methods

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

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

Eq (IORef a) Source #

Pointer equality.

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.IORef

Methods

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

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

Eq (MVar a) Source #

Compares the underlying pointers.

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.MVar

Methods

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

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

Eq (FunPtr a) Source # 
Instance details

Defined in GHC.Internal.Ptr

Methods

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

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

Eq (Ptr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Ptr

Methods

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

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

Eq a => Eq (Ratio a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Real

Methods

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

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

Eq (StablePtr a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Stable

Eq (StableName a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.StableName

Eq flag => Eq (TyVarBndr flag) Source # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

(==) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source #

(/=) :: TyVarBndr flag -> TyVarBndr flag -> Bool Source #

Eq (SChar c) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

(==) :: SChar c -> SChar c -> Bool Source #

(/=) :: SChar c -> SChar c -> Bool Source #

Eq (SSymbol s) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

(==) :: SSymbol s -> SSymbol s -> Bool Source #

(/=) :: SSymbol s -> SSymbol s -> Bool Source #

Eq (SNat n) Source #

Since: base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

(==) :: SNat n -> SNat n -> Bool Source #

(/=) :: SNat n -> SNat n -> Bool Source #

Eq a => Eq (Maybe a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Maybe

Methods

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

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

Eq a => Eq (Solo a) Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq a => Eq [a] Source # 
Instance details

Defined in GHC.Classes

Methods

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

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

Eq (Fixed a) Source #

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

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

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

Eq a => Eq (Arg a b) Source #

Note that Arg's Eq instance does not satisfy extensionality:

>>> Arg 0 0 == Arg 0 1
True
>>> let f (Arg _ x) = x in f (Arg 0 0) == f (Arg 0 1)
False

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

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

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

(Ix i, Eq e) => Eq (Array i e) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Arr

Methods

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

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

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

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Either

Methods

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

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

Eq (Proxy s) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

Eq (TypeRep a) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Methods

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

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

Eq (U1 p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (V1 p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (IOArray i e) Source #

Since: base-4.1.0.0

Instance details

Defined in GHC.Internal.IOArray

Methods

(==) :: IOArray i e -> IOArray i e -> Bool Source #

(/=) :: IOArray i e -> IOArray i e -> Bool Source #

Eq (STRef s a) Source #

Pointer equality.

Since: base-2.1

Instance details

Defined in GHC.Internal.STRef

Methods

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

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

(Eq a, Eq b) => Eq (a, b) Source # 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b) -> (a, b) -> Bool Source #

(/=) :: (a, b) -> (a, b) -> Bool Source #

Eq (STArray s i e) Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Arr

Methods

(==) :: STArray s i e -> STArray s i e -> Bool Source #

(/=) :: STArray s i e -> STArray s i e -> Bool Source #

Eq a => Eq (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(==) :: Const a b -> Const a b -> Bool Source #

(/=) :: Const a b -> Const a b -> Bool Source #

Eq (f a) => Eq (Ap f a) Source #

Since: base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(==) :: Ap f a -> Ap f a -> Bool Source #

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

Eq (f a) => Eq (Alt f a) Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> Bool Source #

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

Eq (Coercion a b) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Coercion

Methods

(==) :: Coercion a b -> Coercion a b -> Bool Source #

(/=) :: Coercion a b -> Coercion a b -> Bool Source #

Eq (a :~: b) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

(==) :: (a :~: b) -> (a :~: b) -> Bool Source #

(/=) :: (a :~: b) -> (a :~: b) -> Bool Source #

Eq (OrderingI a b) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

Methods

(==) :: OrderingI a b -> OrderingI a b -> Bool Source #

(/=) :: OrderingI a b -> OrderingI a b -> Bool Source #

(Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.Generics

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (URec Char p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (URec Double p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (URec Float p) Source # 
Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (URec Int p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (URec Word p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

(Eq a, Eq b, Eq c) => Eq (a, b, c) Source # 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool Source #

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

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

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

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

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

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

Eq (a :~~: b) Source #

Since: base-4.10.0.0

Instance details

Defined in GHC.Internal.Data.Type.Equality

Methods

(==) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

(/=) :: (a :~~: b) -> (a :~~: b) -> Bool Source #

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq c => Eq (K1 i c p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

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

Defined in GHC.Classes

Methods

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

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

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

Since: base-4.18.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

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

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

Eq (f p) => Eq (M1 i c f p) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

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

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) Source # 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) Source # 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) Source # 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

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

Defined in GHC.Classes

Methods

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

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

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

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

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

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

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

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

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

Defined in GHC.Classes

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

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

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

Defined in GHC.Classes

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

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

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

Defined in GHC.Classes

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

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

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

Defined in GHC.Classes

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

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

class Eq a => Ord a where Source #

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.

Ord, as defined by the Haskell report, implements a total order and has the following properties:

Comparability
x <= y || y <= x = True
Transitivity
if x <= y && y <= z = True, then x <= z = True
Reflexivity
x <= x = True
Antisymmetry
if x <= y && y <= x = True, then x == y = True

The following operator interactions are expected to hold:

  1. x >= y = y <= x
  2. x < y = x <= y && x /= y
  3. x > y = y < x
  4. x < y = compare x y == LT
  5. x > y = compare x y == GT
  6. x == y = compare x y == EQ
  7. min x y == if x <= y then x else y = True
  8. max x y == if x >= y then x else y = True

Note that (7.) and (8.) do not require min and max to return either of their arguments. The result is merely required to equal one of the arguments in terms of (==). Users who expect a stronger guarantee are advised to write their own min and/or max functions.

The nuance of the above distinction is not always fully internalized by developers, and in the past (tracing back to the Haskell 1.4 Report) the specification for Ord asserted the stronger property that (min x y, max x y) = (x, y) or (y, x), or in other words, that min and max will return one of their arguments, using argument order as the tie-breaker if the arguments are equal by comparison. A few list and Foldable functions have behavior that is best understood with this assumption in mind: all variations of minimumBy and maximumBy (which can't use min and max in their implementations) are written such that minimumBy compare and maximumBy compare are respectively equivalent to minimum and maximum (which do use min and max) only if min and max adhere to this tie-breaking convention. Otherwise, if there are multiple least or largest elements in a container, minimum and maximum may not return the same one that minimumBy compare and maximumBy compare do (though they should return something that is equal). (This is relevant for types with non-extensional equality, like Arg, but also in cases where the precise reference held matters for memory-management reasons.) Unless there is a reason to deviate, it is less confusing for implementors of Ord to respect this same convention (as the default definitions of min and max do).

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

Minimal complete definition

compare | (<=)

Methods

compare :: a -> a -> Ordering Source #

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

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

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

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

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances

Instances details
Ord ByteArray Source #

Non-lexicographic ordering. This compares the lengths of the byte arrays first and uses a lexicographic ordering if the lengths are equal. Subject to change between major versions.

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Ord BigNat # 
Instance details

Defined in GHC.Num.BigNat

Ord Void Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Base

Ord ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Ord ClosureType Source # 
Instance details

Defined in GHC.Internal.ClosureTypes

Ord BlockReason Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord ThreadId Source #

Since: base-4.2.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord ThreadStatus Source #

Since: base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Ord All Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering Source #

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

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

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

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

max :: All -> All -> All Source #

min :: All -> All -> All Source #

Ord Any Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering Source #

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

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

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

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

max :: Any -> Any -> Any Source #

min :: Any -> Any -> Any Source #

Ord SomeTypeRep Source # 
Instance details

Defined in GHC.Internal.Data.Typeable.Internal

Ord Unique Source # 
Instance details

Defined in GHC.Internal.Data.Unique

Ord Version Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Data.Version

Ord TimeoutKey Source # 
Instance details

Defined in GHC.Internal.Event.TimeOut

Ord Unique Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Unique

Methods

compare :: Unique -> Unique -> Ordering Source #

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

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

(>) :: Unique -> Unique -> Bool Source #

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

max :: Unique -> Unique -> Unique Source #

min :: Unique -> Unique -> Unique Source #

Ord ErrorCall Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Exception

Ord ArithException Source #

Since: base-3.0

Instance details

Defined in GHC.Internal.Exception.Type

Ord Fingerprint Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Fingerprint.Type

Ord CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Ord IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord Associativity Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics