Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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
- data Bool
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- otherwise :: Bool
- data Maybe a
- maybe :: b -> (a -> b) -> Maybe a -> b
- data Either a b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- data Ordering
- data Char
- type String = [Char]
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- curry :: ((a, b) -> c) -> a -> b -> c
- uncurry :: (a -> b -> c) -> (a, b) -> c
- class Eq a where
- class Eq a => Ord a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Bounded a where
- data Int
- data Integer
- data Float
- data Double
- type Rational = Ratio Integer
- data Word
- class Num a where
- class (Num a, Ord a) => Real a where
- toRational :: a -> Rational
- class (Real a, Enum a) => Integral a where
- class Num a => Fractional a where
- (/) :: a -> a -> a
- recip :: a -> a
- fromRational :: Rational -> a
- class Fractional a => Floating a where
- class (Real a, Fractional a) => RealFrac a where
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- atan2 :: a -> a -> a
- subtract :: Num a => a -> a -> a
- even :: Integral a => a -> Bool
- odd :: Integral a => a -> Bool
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- (^) :: (Num a, Integral b) => a -> b -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Semigroup a where
- (<>) :: a -> a -> a
- class Semigroup a => Monoid a where
- class Functor f where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- class Functor f => Applicative f where
- class Applicative m => Monad m where
- class Monad m => MonadFail m where
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class Foldable t where
- foldMap :: Monoid m => (a -> m) -> t a -> m
- foldr :: (a -> b -> b) -> b -> t a -> b
- foldl :: (b -> a -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> t a -> a
- foldl1 :: (a -> a -> a) -> t a -> a
- elem :: Eq a => a -> t a -> Bool
- maximum :: forall a. Ord a => t a -> a
- minimum :: forall a. Ord a => t a -> a
- sum :: Num a => t a -> a
- product :: Num a => t a -> a
- class (Functor t, Foldable t) => Traversable t where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- id :: a -> a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- error :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => [Char] -> a
- errorWithoutStackTrace :: forall (r :: RuntimeRep). forall (a :: TYPE r). [Char] -> a
- undefined :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => a
- seq :: a -> b -> b
- ($!) :: forall r a (b :: TYPE r). (a -> b) -> a -> b
- map :: (a -> b) -> [a] -> [b]
- (++) :: [a] -> [a] -> [a]
- filter :: (a -> Bool) -> [a] -> [a]
- head :: [a] -> a
- last :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- null :: Foldable t => t a -> Bool
- length :: Foldable t => t a -> Int
- (!!) :: [a] -> Int -> a
- reverse :: [a] -> [a]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- concat :: Foldable t => t [a] -> [a]
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- cycle :: [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- lines :: String -> [String]
- words :: String -> [String]
- unlines :: [String] -> String
- unwords :: [String] -> String
- type ShowS = String -> String
- class Show a where
- shows :: Show a => a -> ShowS
- showChar :: Char -> ShowS
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- type ReadS a = String -> [(a, String)]
- class Read a where
- reads :: Read a => ReadS a
- readParen :: Bool -> ReadS a -> ReadS a
- read :: Read a => String -> a
- lex :: ReadS String
- data IO a
- putChar :: Char -> IO ()
- putStr :: String -> IO ()
- putStrLn :: String -> IO ()
- print :: Show a => a -> IO ()
- getChar :: IO Char
- getLine :: IO String
- getContents :: IO String
- interact :: (String -> String) -> IO ()
- type FilePath = String
- readFile :: FilePath -> IO String
- writeFile :: FilePath -> String -> IO ()
- appendFile :: FilePath -> String -> IO ()
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- type IOError = IOException
- ioError :: IOError -> IO a
- userError :: String -> IOError
Standard types, classes and related functions
Basic data types
Instances
Bounded Bool # | Since: base-2.1 |
Enum Bool # | Since: base-2.1 |
Eq Bool | |
Data Bool # | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Ord Bool | |
Read Bool # | Since: base-2.1 |
Show Bool # | Since: base-2.1 |
Ix Bool # | Since: base-2.1 |
Generic Bool # | Since: base-4.6.0.0 |
FiniteBits Bool # | Since: base-4.7.0.0 |
Bits Bool # | Interpret Since: base-4.7.0.0 |
Defined in Data.Bits (.&.) :: Bool -> Bool -> Bool Source # (.|.) :: Bool -> Bool -> Bool Source # xor :: Bool -> Bool -> Bool Source # complement :: Bool -> Bool Source # shift :: Bool -> Int -> Bool Source # rotate :: Bool -> Int -> Bool Source # setBit :: Bool -> Int -> Bool Source # clearBit :: Bool -> Int -> Bool Source # complementBit :: Bool -> Int -> Bool Source # testBit :: Bool -> Int -> Bool Source # bitSizeMaybe :: Bool -> Maybe Int Source # bitSize :: Bool -> Int Source # isSigned :: Bool -> Bool Source # shiftL :: Bool -> Int -> Bool Source # unsafeShiftL :: Bool -> Int -> Bool Source # shiftR :: Bool -> Int -> Bool Source # unsafeShiftR :: Bool -> Int -> Bool Source # rotateL :: Bool -> Int -> Bool Source # | |
Storable Bool # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Bool -> Int Source # alignment :: Bool -> Int Source # peekElemOff :: Ptr Bool -> Int -> IO Bool Source # pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Bool Source # pokeByteOff :: Ptr b -> Int -> Bool -> IO () Source # | |
type Rep Bool # | |
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). 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.
Instances
Monad Maybe # | Since: base-2.1 |
Functor Maybe # | Since: base-2.1 |
MonadFix Maybe # | Since: base-2.1 |
MonadFail Maybe # | Since: base-4.9.0.0 |
Applicative Maybe # | Since: base-2.1 |
Foldable Maybe # | Since: base-2.1 |
Defined in Data.Foldable 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 # | |
Traversable Maybe # | Since: base-2.1 |
MonadPlus Maybe # | Since: base-2.1 |
Alternative Maybe # | Since: base-2.1 |
MonadZip Maybe # | Since: base-4.8.0.0 |
Show1 Maybe # | Since: base-4.9.0.0 |
Read1 Maybe # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] Source # | |
Ord1 Maybe # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq1 Maybe # | Since: base-4.9.0.0 |
Eq a => Eq (Maybe a) # | Since: base-2.1 |
Data a => Data (Maybe a) # | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Ord a => Ord (Maybe a) # | Since: base-2.1 |
Read a => Read (Maybe a) # | Since: base-2.1 |
Show a => Show (Maybe a) # | Since: base-2.1 |
Generic (Maybe a) # | Since: base-4.6.0.0 |
Semigroup a => Semigroup (Maybe a) # | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) # | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Generic1 Maybe # | Since: base-4.6.0.0 |
type Rep (Maybe a) # | |
Defined in GHC.Generics | |
type Rep1 Maybe # | |
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
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is
either correct or an error; by convention, the Left
constructor is
used to hold an error value and the Right
constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
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 Int
s.
>>>
:{
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"
Instances
Show2 Either # | Since: base-4.9.0.0 |
Read2 Either # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes 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 # | |
Ord2 Either # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq2 Either # | Since: base-4.9.0.0 |
Bifunctor Either # | Since: base-4.8.0.0 |
Bifoldable Either # | Since: base-4.10.0.0 |
Bitraversable Either # | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) Source # | |
Monad (Either e) # | Since: base-4.4.0.0 |
Functor (Either a) # | Since: base-3.0 |
MonadFix (Either e) # | Since: base-4.3.0.0 |
Applicative (Either e) # | Since: base-3.0 |
Defined in Data.Either | |
Foldable (Either a) # | Since: base-4.7.0.0 |
Defined in Data.Foldable 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 # | |
Traversable (Either a) # | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Show a => Show1 (Either a) # | Since: base-4.9.0.0 |
Read a => Read1 (Either a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes 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 # | |
Ord a => Ord1 (Either a) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq a => Eq1 (Either a) # | Since: base-4.9.0.0 |
Generic1 (Either a :: Type -> Type) # | Since: base-4.6.0.0 |
(Eq a, Eq b) => Eq (Either a b) # | Since: base-2.1 |
(Data a, Data b) => Data (Either a b) # | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
(Ord a, Ord b) => Ord (Either a b) # | Since: base-2.1 |
Defined in Data.Either 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 # | |
(Read a, Read b) => Read (Either a b) # | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) # | Since: base-3.0 |
Generic (Either a b) # | Since: base-4.6.0.0 |
Semigroup (Either a b) # | Since: base-4.9.0.0 |
type Rep1 (Either a :: Type -> Type) # | |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "Data.Either" "base" '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) # | |
Defined in GHC.Generics type Rep (Either a b) = D1 ('MetaData "Either" "Data.Either" "base" '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
, apply the first function to Left
aa
;
if it is
, apply the second function to Right
bb
.
Examples
We create two values of type
, one using the
Either
String
Int
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
Instances
Bounded Ordering # | Since: base-2.1 |
Enum Ordering # | Since: base-2.1 |
Defined in GHC.Enum succ :: Ordering -> Ordering Source # pred :: Ordering -> Ordering Source # toEnum :: Int -> Ordering Source # fromEnum :: Ordering -> Int Source # enumFrom :: Ordering -> [Ordering] Source # enumFromThen :: Ordering -> Ordering -> [Ordering] Source # enumFromTo :: Ordering -> Ordering -> [Ordering] Source # enumFromThenTo :: Ordering -> Ordering -> Ordering -> [Ordering] Source # | |
Eq Ordering | |
Data Ordering # | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Ord Ordering | |
Defined in GHC.Classes | |
Read Ordering # | Since: base-2.1 |
Show Ordering # | Since: base-2.1 |
Ix Ordering # | Since: base-2.1 |
Defined in GHC.Arr | |
Generic Ordering # | Since: base-4.6.0.0 |
Semigroup Ordering # | Since: base-4.9.0.0 |
Monoid Ordering # | Since: base-2.1 |
type Rep Ordering # | |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and
chr
).
Instances
Bounded Char # | Since: base-2.1 |
Enum Char # | Since: base-2.1 |
Eq Char | |
Data Char # | Since: base-4.0.0.0 |
Defined in Data.Data 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 # | |
Ord Char | |
Read Char # | Since: base-2.1 |
Show Char # | Since: base-2.1 |
Ix Char # | Since: base-2.1 |
Storable Char # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Char -> Int Source # alignment :: Char -> Int Source # peekElemOff :: Ptr Char -> Int -> IO Char Source # pokeElemOff :: Ptr Char -> Int -> Char -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Char Source # pokeByteOff :: Ptr b -> Int -> Char -> IO () Source # | |
IsChar Char # | Since: base-2.1 |
PrintfArg Char # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |
Generic1 (URec Char :: k -> Type) # | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Foldable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => URec Char m -> m Source # foldMap :: Monoid m => (a -> m) -> URec Char a -> m Source # foldMap' :: Monoid m => (a -> m) -> URec Char a -> m Source # foldr :: (a -> b -> b) -> b -> URec Char a -> b Source # foldr' :: (a -> b -> b) -> b -> URec Char a -> b Source # foldl :: (b -> a -> b) -> b -> URec Char a -> b Source # foldl' :: (b -> a -> b) -> b -> URec Char a -> b Source # foldr1 :: (a -> a -> a) -> URec Char a -> a Source # foldl1 :: (a -> a -> a) -> URec Char a -> a Source # toList :: URec Char a -> [a] Source # null :: URec Char a -> Bool Source # length :: URec Char a -> Int Source # elem :: Eq a => a -> URec Char a -> Bool Source # maximum :: Ord a => URec Char a -> a Source # minimum :: Ord a => URec Char a -> a Source # | |
Traversable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Char p) # | Since: base-4.9.0.0 |
Ord (URec Char p) # | Since: base-4.9.0.0 |
Defined in GHC.Generics 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 # | |
Show (URec Char p) # | Since: base-4.9.0.0 |
Generic (URec Char p) # | Since: base-4.9.0.0 |
data URec Char (p :: k) # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Char :: k -> Type) # | |
Defined in GHC.Generics | |
type Rep (URec Char p) # | |
Defined in GHC.Generics |
Tuples
uncurry :: (a -> b -> c) -> (a, b) -> c Source #
uncurry
converts a curried function to a function on pairs.
Examples
>>>
uncurry (+) (1,2)
3
>>>
uncurry ($) (show, 1)
"1"
>>>
map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]
Basic type classes
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, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
Eq Bool | |
Eq Char | |
Eq Double | Note that due to the presence of
Also note that
|
Eq Float | Note that due to the presence of
Also note that
|
Eq Int | |
Eq Int8 # | Since: base-2.1 |
Eq Int16 # | Since: base-2.1 |
Eq Int32 # | Since: base-2.1 |
Eq Int64 # | Since: base-2.1 |
Eq Integer | |
Eq Natural # | Since: base-4.8.0.0 |
Eq Ordering | |
Eq Word | |
Eq Word8 # | Since: base-2.1 |
Eq Word16 # | Since: base-2.1 |
Eq Word32 # | Since: base-2.1 |
Eq Word64 # | Since: base-2.1 |
Eq SomeTypeRep # | |
Defined in Data.Typeable.Internal (==) :: SomeTypeRep -> SomeTypeRep -> Bool Source # (/=) :: SomeTypeRep -> SomeTypeRep -> Bool Source # | |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq BigNat | |
Eq SrcLoc # | Since: base-4.9.0.0 |
Eq GeneralCategory # | Since: base-2.1 |
Defined in GHC.Unicode (==) :: GeneralCategory -> GeneralCategory -> Bool Source # (/=) :: GeneralCategory -> GeneralCategory -> Bool Source # | |
Eq Number # | Since: base-4.6.0.0 |
Eq Lexeme # | Since: base-2.1 |
Eq Fingerprint # | Since: base-4.4.0.0 |
Defined in GHC.Fingerprint.Type (==) :: Fingerprint -> Fingerprint -> Bool Source # (/=) :: Fingerprint -> Fingerprint -> Bool Source # | |
Eq IOMode # | Since: base-4.2.0.0 |
Eq IntPtr # | |
Eq WordPtr # | |
Eq CUIntMax # | |
Eq CIntMax # | |
Eq CUIntPtr # | |
Eq CIntPtr # | |
Eq CSUSeconds # | |
Defined in Foreign.C.Types (==) :: CSUSeconds -> CSUSeconds -> Bool Source # (/=) :: CSUSeconds -> CSUSeconds -> Bool Source # | |
Eq CUSeconds # | |
Eq CTime # | |
Eq CClock # | |
Eq CSigAtomic # | |
Defined in Foreign.C.Types (==) :: CSigAtomic -> CSigAtomic -> Bool Source # (/=) :: CSigAtomic -> CSigAtomic -> Bool Source # | |
Eq CWchar # | |
Eq CSize # | |
Eq CPtrdiff # | |
Eq CDouble # | |
Eq CFloat # | |
Eq CBool # | |
Eq CULLong # | |
Eq CLLong # | |
Eq CULong # | |
Eq CLong # | |
Eq CUInt # | |
Eq CInt # | |
Eq CUShort # | |
Eq CShort # | |
Eq CUChar # | |
Eq CSChar # | |
Eq CChar # | |
Eq SomeNat # | Since: base-4.7.0.0 |
Eq SomeSymbol # | Since: base-4.7.0.0 |
Defined in GHC.TypeLits (==) :: SomeSymbol -> SomeSymbol -> Bool Source # (/=) :: SomeSymbol -> SomeSymbol -> Bool Source # | |
Eq DecidedStrictness # | Since: base-4.9.0.0 |
Defined in GHC.Generics (==) :: DecidedStrictness -> DecidedStrictness -> Bool Source # (/=) :: DecidedStrictness -> DecidedStrictness -> Bool Source # | |
Eq SourceStrictness # | Since: base-4.9.0.0 |
Defined in GHC.Generics (==) :: SourceStrictness -> SourceStrictness -> Bool Source # (/=) :: SourceStrictness -> SourceStrictness -> Bool Source # | |
Eq SourceUnpackedness # | Since: base-4.9.0.0 |
Defined in GHC.Generics (==) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # (/=) :: SourceUnpackedness -> SourceUnpackedness -> Bool Source # | |
Eq Associativity # | Since: base-4.6.0.0 |
Defined in GHC.Generics (==) :: Associativity -> Associativity -> Bool Source # (/=) :: Associativity -> Associativity -> Bool Source # | |
Eq Fixity # | Since: base-4.6.0.0 |
Eq Any # | Since: base-2.1 |
Eq All # | Since: base-2.1 |
Eq ArithException # | Since: base-3.0 |
Defined in GHC.Exception.Type (==) :: ArithException -> ArithException -> Bool Source # (/=) :: ArithException -> ArithException -> Bool Source # | |
Eq ErrorCall # | Since: base-4.7.0.0 |
Eq IOException # | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOException -> IOException -> Bool Source # (/=) :: IOException -> IOException -> Bool Source # | |
Eq MaskingState # | Since: base-4.3.0.0 |
Defined in GHC.IO (==) :: MaskingState -> MaskingState -> Bool Source # (/=) :: MaskingState -> MaskingState -> Bool Source # | |
Eq BufferState # | Since: base-4.2.0.0 |
Defined in GHC.IO.Buffer (==) :: BufferState -> BufferState -> Bool Source # (/=) :: BufferState -> BufferState -> Bool Source # | |
Eq CodingProgress # | Since: base-4.4.0.0 |
Defined in GHC.IO.Encoding.Types (==) :: CodingProgress -> CodingProgress -> Bool Source # (/=) :: CodingProgress -> CodingProgress -> Bool Source # | |
Eq SeekMode # | Since: base-4.2.0.0 |
Eq IODeviceType # | Since: base-4.2.0.0 |
Defined in GHC.IO.Device (==) :: IODeviceType -> IODeviceType -> Bool Source # (/=) :: IODeviceType -> IODeviceType -> Bool Source # | |
Eq NewlineMode # | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types (==) :: NewlineMode -> NewlineMode -> Bool Source # (/=) :: NewlineMode -> NewlineMode -> Bool Source # | |
Eq Newline # | Since: base-4.2.0.0 |
Eq BufferMode # | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types (==) :: BufferMode -> BufferMode -> Bool Source # (/=) :: BufferMode -> BufferMode -> Bool Source # | |
Eq Handle # | Since: base-4.1.0.0 |
Eq IOErrorType # | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception (==) :: IOErrorType -> IOErrorType -> Bool Source # (/=) :: IOErrorType -> IOErrorType -> Bool Source # | |
Eq ExitCode # | |
Eq ArrayException # | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception (==) :: ArrayException -> ArrayException -> Bool Source # (/=) :: ArrayException -> ArrayException -> Bool Source # | |
Eq AsyncException # | Since: base-4.2.0.0 |
Defined in GHC.IO.Exception (==) :: AsyncException -> AsyncException -> Bool Source # (/=) :: AsyncException -> AsyncException -> Bool Source # | |
Eq Errno # | Since: base-2.1 |
Eq Fd # | |
Eq CTimer # | |
Eq CKey # | |
Eq CId # | |
Eq CFsFilCnt # | |
Eq CFsBlkCnt # | |
Eq CClockId # | |
Eq CBlkCnt # | |
Eq CBlkSize # | |
Eq CRLim # | |
Eq CTcflag # | |
Eq CSpeed # | |
Eq CCc # | |
Eq CUid # | |
Eq CNlink # | |
Eq CGid # | |
Eq CSsize # | |
Eq CPid # | |
Eq COff # | |
Eq CMode # | |
Eq CIno # | |
Eq CDev # | |
Eq Lifetime # | Since: base-4.8.1.0 |
Eq Event # | Since: base-4.4.0.0 |
Eq ThreadStatus # | Since: base-4.3.0.0 |
Defined in GHC.Conc.Sync (==) :: ThreadStatus -> ThreadStatus -> Bool Source # (/=) :: ThreadStatus -> ThreadStatus -> Bool Source # | |
Eq BlockReason # | Since: base-4.3.0.0 |
Defined in GHC.Conc.Sync (==) :: BlockReason -> BlockReason -> Bool Source # (/=) :: BlockReason -> BlockReason -> Bool Source # | |
Eq ThreadId # | Since: base-4.2.0.0 |
Eq TimeoutKey # | Since: base-4.7.0.0 |
Defined in GHC.Event.TimerManager (==) :: TimeoutKey -> TimeoutKey -> Bool Source # (/=) :: TimeoutKey -> TimeoutKey -> Bool Source # | |
Eq FdKey # | Since: base-4.4.0.0 |
Eq HandlePosn # | Since: base-4.1.0.0 |
Defined in GHC.IO.Handle (==) :: HandlePosn -> HandlePosn -> Bool Source # (/=) :: HandlePosn -> HandlePosn -> Bool Source # | |
Eq Version # | Since: base-2.1 |
Eq ByteOrder # | Since: base-4.11.0.0 |
Eq Unique # | |
Eq Fixity # | Since: base-4.0.0.0 |
Eq ConstrRep # | Since: base-4.0.0.0 |
Eq DataRep # | Since: base-4.0.0.0 |
Eq Constr # | Equality of constructors Since: base-4.0.0.0 |
Eq SpecConstrAnnotation # | Since: base-4.3.0.0 |
Defined in GHC.Exts (==) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # (/=) :: SpecConstrAnnotation -> SpecConstrAnnotation -> Bool Source # | |
Eq Void # | Since: base-4.8.0.0 |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) # | Since: base-2.1 |
Eq a => Eq (Ratio a) # | Since: base-2.1 |
Eq (StablePtr a) # | Since: base-2.1 |
Eq (Ptr a) # | Since: base-2.1 |
Eq (FunPtr a) # | |
Eq p => Eq (Par1 p) # | Since: base-4.7.0.0 |
Eq a => Eq (NonEmpty a) # | Since: base-4.9.0.0 |
Eq (MVar a) # | Since: base-4.1.0.0 |
Eq a => Eq (Down a) # | Since: base-4.6.0.0 |
Eq a => Eq (Product a) # | Since: base-2.1 |
Eq a => Eq (Sum a) # | Since: base-2.1 |
Eq a => Eq (Dual a) # | Since: base-2.1 |
Eq a => Eq (Last a) # | Since: base-2.1 |
Eq a => Eq (First a) # | Since: base-2.1 |
Eq (IORef a) # | Pointer equality. Since: base-4.0.0.0 |
Eq (ForeignPtr a) # | Since: base-2.1 |
Defined in GHC.ForeignPtr (==) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (/=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # | |
Eq (TVar a) # | Since: base-4.8.0.0 |
Eq a => Eq (Identity a) # | Since: base-4.8.0.0 |
Eq a => Eq (ZipList a) # | Since: base-4.7.0.0 |
Eq (StableName a) # | Since: base-2.1 |
Defined in GHC.StableName (==) :: StableName a -> StableName a -> Bool Source # (/=) :: StableName a -> StableName a -> Bool Source # | |
Eq (Chan a) # | Since: base-4.4.0.0 |
Eq a => Eq (Option a) # | Since: base-4.9.0.0 |
Eq m => Eq (WrappedMonoid m) # | Since: base-4.9.0.0 |
Defined in Data.Semigroup (==) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # (/=) :: WrappedMonoid m -> WrappedMonoid m -> Bool Source # | |
Eq a => Eq (Last a) # | Since: base-4.9.0.0 |
Eq a => Eq (First a) # | Since: base-4.9.0.0 |
Eq a => Eq (Max a) # | Since: base-4.9.0.0 |
Eq a => Eq (Min a) # | Since: base-4.9.0.0 |
Eq (Fixed a) # | Since: base-2.1 |
Eq a => Eq (Complex a) # | Since: base-2.1 |
(Eq a, Eq b) => Eq (Either a b) # | Since: base-2.1 |
Eq (V1 p) # | Since: base-4.9.0.0 |
Eq (U1 p) # | Since: base-4.9.0.0 |
Eq (TypeRep a) # | Since: base-2.1 |
(Eq a, Eq b) => Eq (a, b) | |
Eq (STRef s a) # | Pointer equality. Since: base-2.1 |
(Ix i, Eq e) => Eq (Array i e) # | Since: base-2.1 |
Eq (Proxy s) # | Since: base-4.7.0.0 |
Eq (IOArray i e) # | Since: base-4.1.0.0 |
Eq a => Eq (Arg a b) # | Since: base-4.9.0.0 |
Eq (f p) => Eq (Rec1 f p) # | Since: base-4.7.0.0 |
Eq (URec Word p) # | Since: base-4.9.0.0 |
Eq (URec Int p) # | Since: base-4.9.0.0 |
Eq (URec Float p) # | |
Eq (URec Double p) # | Since: base-4.9.0.0 |
Eq (URec Char p) # | Since: base-4.9.0.0 |
Eq (URec (Ptr ()) p) # | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (STArray s i e) # | Since: base-2.1 |
Eq (a :~: b) # | Since: base-4.7.0.0 |
Eq (Coercion a b) # | Since: base-4.7.0.0 |
Eq (f a) => Eq (Alt f a) # | Since: base-4.8.0.0 |
Eq (f a) => Eq (Ap f a) # | Since: base-4.12.0.0 |
Eq a => Eq (Const a b) # | Since: base-4.9.0.0 |
Eq c => Eq (K1 i c p) # | Since: base-4.7.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) # | Since: base-4.7.0.0 |
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) # | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
Eq (a :~~: b) # | Since: base-4.10.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) # | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a) # | Since: base-4.9.0.0 |
Eq (f p) => Eq (M1 i c f p) # | Since: base-4.7.0.0 |
Eq (f (g p)) => Eq ((f :.: g) p) # | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) # | Since: base-4.9.0.0 |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
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.
The Haskell Report defines no laws for Ord
. However, <=
is customarily
expected to implement a non-strict partial order and have the following
properties:
- Transitivity
- if
x <= y && y <= z
=True
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
Note that the following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
max x y == if x >= y then x else y
=True
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
compare :: a -> a -> Ordering Source #
(<) :: a -> a -> Bool infix 4 Source #
(<=) :: a -> a -> Bool infix 4 Source #
(>) :: a -> a -> Bool infix 4 Source #