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 :: forall {r :: RuntimeRep} a (b :: TYPE r). 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 :: HasCallStack => [a] -> a
- last :: HasCallStack => [a] -> a
- tail :: HasCallStack => [a] -> [a]
- init :: HasCallStack => [a] -> [a]
- (!!) :: HasCallStack => [a] -> Int -> a
- null :: Foldable t => t a -> Bool
- length :: Foldable t => t a -> Int
- 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 :: HasCallStack => [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- splitAt :: Int -> [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
- class a ~# b => (a :: k) ~ (b :: k)
Standard types, classes and related functions
Basic data types
Instances
Data Bool Source # | 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 # | |
Storable Bool Source # | 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 # | |
Bits Bool Source # | Interpret Since: base-4.7.0.0 |
Defined in GHC.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 # | |
FiniteBits Bool Source # | Since: base-4.7.0.0 |
Bounded Bool Source # | Since: base-2.1 |
Enum Bool Source # | Since: base-2.1 |
Generic Bool Source # | |
Ix Bool Source # | Since: base-2.1 |
Read Bool Source # | Since: base-2.1 |
Show Bool Source # | Since: base-2.1 |
Eq Bool | |
Ord Bool | |
type Rep Bool Source # | Since: base-4.6.0.0 |
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
MonadFail Maybe Source # | Since: base-4.9.0.0 |
MonadFix Maybe Source # | Since: base-2.1 |
MonadZip Maybe Source # | Since: base-4.8.0.0 |
Foldable Maybe Source # | 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 # | |
Eq1 Maybe Source # | Since: base-4.9.0.0 |
Ord1 Maybe Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe Source # | 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 # | |
Show1 Maybe Source # | Since: base-4.9.0.0 |
Traversable Maybe Source # | Since: base-2.1 |
Alternative Maybe Source # | Since: base-2.1 |
Applicative Maybe Source # | Since: base-2.1 |
Functor Maybe Source # | Since: base-2.1 |
Monad Maybe Source # | Since: base-2.1 |
MonadPlus Maybe Source # | Since: base-2.1 |
Generic1 Maybe Source # | |
Data a => Data (Maybe a) Source # | 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 # | |
Semigroup a => Monoid (Maybe a) Source # | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Semigroup a => Semigroup (Maybe a) Source # | Since: base-4.9.0.0 |
Generic (Maybe a) Source # | |
Read a => Read (Maybe a) Source # | Since: base-2.1 |
Show a => Show (Maybe a) Source # | Since: base-2.1 |
Eq a => Eq (Maybe a) Source # | Since: base-2.1 |
Ord a => Ord (Maybe a) Source # | Since: base-2.1 |
type Rep1 Maybe Source # | Since: base-4.6.0.0 |
type Rep (Maybe a) Source # | Since: base-4.6.0.0 |
Defined in GHC.Generics |
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
Bifoldable Either Source # | Since: base-4.10.0.0 |
Bifunctor Either Source # | Since: base-4.8.0.0 |
Bitraversable Either Source # | 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 # | |
Eq2 Either Source # | Since: base-4.9.0.0 |
Ord2 Either Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either Source # | 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 # | |
Show2 Either Source # | Since: base-4.9.0.0 |
Generic1 (Either a :: Type -> Type) Source # | |
MonadFix (Either e) Source # | Since: base-4.3.0.0 |
Foldable (Either a) Source # | 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 # | |
Eq a => Eq1 (Either a) Source # | Since: base-4.9.0.0 |
Ord a => Ord1 (Either a) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Either a) Source # | 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 # | |
Show a => Show1 (Either a) Source # | Since: base-4.9.0.0 |
Traversable (Either a) Source # | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Applicative (Either e) Source # | Since: base-3.0 |
Defined in Data.Either | |
Functor (Either a) Source # | Since: base-3.0 |
Monad (Either e) Source # | Since: base-4.4.0.0 |
(Data a, Data b) => Data (Either a b) Source # | 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 # | |
Semigroup (Either a b) Source # | Since: base-4.9.0.0 |
Generic (Either a b) Source # | |
(Read a, Read b) => Read (Either a b) Source # | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) Source # | Since: base-3.0 |
(Eq a, Eq b) => Eq (Either a b) Source # | Since: base-2.1 |
(Ord a, Ord b) => Ord (Either a b) Source # | 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 # | |
type Rep1 (Either a :: Type -> Type) Source # | Since: base-4.6.0.0 |
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) Source # | Since: base-4.6.0.0 |
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
Data Ordering Source # | 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 # | |
Monoid Ordering Source # | Since: base-2.1 |
Semigroup Ordering Source # | Since: base-4.9.0.0 |
Bounded Ordering Source # | Since: base-2.1 |
Enum Ordering Source # | 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 # | |
Generic Ordering Source # | |
Ix Ordering Source # | Since: base-2.1 |
Read Ordering Source # | Since: base-2.1 |
Show Ordering Source # | Since: base-2.1 |
Eq Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
type Rep Ordering Source # | Since: base-4.6.0.0 |
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
Data Char Source # | 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 # | |
Storable Char Source # | 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 # | |
Bounded Char Source # | Since: base-2.1 |
Enum Char Source # | Since: base-2.1 |
Ix Char Source # | Since: base-2.1 |
Read Char Source # | Since: base-2.1 |
Show Char Source # | Since: base-2.1 |
IsChar Char Source # | Since: base-2.1 |
PrintfArg Char Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Char -> FieldFormatter Source # parseFormat :: Char -> ModifierParser Source # | |
Eq Char | |
Ord Char | |
Generic1 (URec Char :: k -> Type) Source # | |
Foldable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Foldable 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 # | |
Traversable (UChar :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) Source # | Since: base-4.9.0.0 |
Generic (URec Char p) Source # | |
Show (URec Char p) Source # | Since: base-4.9.0.0 |
Eq (URec Char p) Source # | Since: base-4.9.0.0 |
Ord (URec Char p) Source # | 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 # | |
data URec Char (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 |
type Compare (a :: Char) (b :: Char) Source # | |
Defined in Data.Type.Ord | |
type Rep1 (URec Char :: k -> Type) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Char p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
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
[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
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, instances are
encouraged to follow these properties:
Instances
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
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
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
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 (==)
.
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 #