Safe Haskell | Trustworthy |
---|
The Haskell 98 Prelude: a standard module imported by default into all Haskell modules. For more documentation, see the Haskell 98 Report http://www.haskell.org/onlinereport/.
- 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
- 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 Monad m where
- class Functor f where
- fmap :: (a -> b) -> f a -> f b
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
- mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
- sequence :: Monad m => [m a] -> m [a]
- sequence_ :: Monad m => [m a] -> m ()
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- id :: a -> a
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: (a -> b) -> a -> b
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- error :: [Char] -> a
- undefined :: a
- seq :: a -> b -> b
- ($!) :: (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 :: [a] -> Bool
- length :: [a] -> Int
- (!!) :: [a] -> Int -> a
- reverse :: [a] -> [a]
- foldl :: (a -> b -> a) -> a -> [b] -> a
- foldl1 :: (a -> a -> a) -> [a] -> a
- foldr :: (a -> b -> b) -> b -> [a] -> b
- foldr1 :: (a -> a -> a) -> [a] -> a
- and :: [Bool] -> Bool
- or :: [Bool] -> Bool
- any :: (a -> Bool) -> [a] -> Bool
- all :: (a -> Bool) -> [a] -> Bool
- sum :: Num a => [a] -> a
- product :: Num a => [a] -> a
- concat :: [[a]] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
- maximum :: Ord a => [a] -> a
- minimum :: Ord a => [a] -> a
- scanl :: (a -> b -> a) -> a -> [b] -> [a]
- 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])
- elem :: Eq a => a -> [a] -> Bool
- notElem :: Eq a => a -> [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
- catch :: IO a -> (IOError -> IO a) -> IO a
Standard types, classes and related functions
Basic data types
data 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.
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").
data Ordering
data Char
Tuples
curry :: ((a, b) -> c) -> a -> b -> cSource
curry
converts an uncurried function to a curried function.
uncurry :: (a -> b -> c) -> (a, b) -> cSource
uncurry
converts a curried function to a function on pairs.
Basic type classes
class Eq a where
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | |
Eq Int16 | |
Eq Int32 | |
Eq Int64 | |
Eq Integer | |
Eq Ordering | |
Eq () | |
Eq Handle | |
Eq HandlePosn | |
Eq Errno | |
Eq AsyncException | |
Eq ArrayException | |
Eq ExitCode | |
Eq IOErrorType | |
Eq BufferMode | |
Eq Newline | |
Eq NewlineMode | |
Eq WordPtr | |
Eq IntPtr | |
Eq GeneralCategory | |
Eq CChar | |
Eq CSChar | |
Eq CUChar | |
Eq CShort | |
Eq CUShort | |
Eq CInt | |
Eq CUInt | |
Eq CLong | |
Eq CULong | |
Eq CLLong | |
Eq CULLong | |
Eq CFloat | |
Eq CDouble | |
Eq CPtrdiff | |
Eq CSize | |
Eq CWchar | |
Eq CSigAtomic | |
Eq CClock | |
Eq CTime | |
Eq CUSeconds | |
Eq CSUSeconds | |
Eq CIntPtr | |
Eq CUIntPtr | |
Eq CIntMax | |
Eq CUIntMax | |
Eq IODeviceType | |
Eq SeekMode | |
Eq IOMode | |
Eq Lexeme | |
Eq MaskingState | |
Eq IOException | |
Eq ArithException | |
Eq TypeRep | |
Eq TyCon | |
Eq Permissions | |
Eq TimeLocale | |
Eq Month | |
Eq Day | |
Eq ClockTime | |
Eq CalendarTime | |
Eq TimeDiff | |
Eq LocalTime | |
Eq UTCTime | |
Eq NominalDiffTime | |
Eq UniversalTime | |
Eq DiffTime | |
Eq Fixity | |
Eq Associativity | |
Eq Arity | |
Eq Permissions | |
Eq a => Eq [a] | |
Eq a => Eq (Ratio a) | |
Eq a => Eq (Complex a) | |
Eq (IORef a) | |
Eq a => Eq (Maybe a) | |
(Eq a, Eq b) => Eq (Either a b) | |
(Eq a, Eq b) => Eq (a, b) | |
(Ix i, Eq e) => Eq (Array i e) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (STArray s i e) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(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) |
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | |
Ord Int16 | |
Ord Int32 | |
Ord Int64 | |
Ord Integer | |
Ord Ordering | |
Ord () | |
Ord AsyncException | |
Ord ArrayException | |
Ord ExitCode | |
Ord BufferMode | |
Ord Newline | |
Ord NewlineMode | |
Ord WordPtr | |
Ord IntPtr | |
Ord GeneralCategory | |
Ord CChar | |
Ord CSChar | |
Ord CUChar | |
Ord CShort | |
Ord CUShort | |
Ord CInt | |
Ord CUInt | |
Ord CLong | |
Ord CULong | |
Ord CLLong | |
Ord CULLong | |
Ord CFloat | |
Ord CDouble | |
Ord CPtrdiff | |
Ord CSize | |
Ord CWchar | |
Ord CSigAtomic | |
Ord CClock | |
Ord CTime | |
Ord CUSeconds | |
Ord CSUSeconds | |
Ord CIntPtr | |
Ord CUIntPtr | |
Ord CIntMax | |
Ord CUIntMax | |
Ord SeekMode | |
Ord IOMode | |
Ord ArithException | |
Ord TypeRep | |
Ord TyCon | |
Ord Permissions | |
Ord TimeLocale | |
Ord Month | |
Ord Day | |
Ord ClockTime | |
Ord CalendarTime | |
Ord TimeDiff | |
Ord LocalTime | |
Ord UTCTime | |
Ord NominalDiffTime | |
Ord UniversalTime | |
Ord DiffTime | |
Ord Fixity | |
Ord Associativity | |
Ord Arity | |
Ord Permissions | |
Ord a => Ord [a] | |
Integral a => Ord (Ratio a) | |
Ord a => Ord (Maybe a) | |
(Ord a, Ord b) => Ord (Either a b) | |
(Ord a, Ord b) => Ord (a, b) | |
(Ix i, Ord e) => Ord (Array i e) | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
-
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
-
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
.
enumFromThen :: a -> a -> [a]Source
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a]Source
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a]Source
Used in Haskell's translation of [n,n'..m]
.
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Numbers
Numeric types
data Int
data Integer
data Float
data Double
Numeric type classes
Basic numeric class.
Minimal complete definition: all except negate
or (-)
Unary negation.
Absolute value.
Sign of a number.
The functions abs
and signum
should satisfy the law:
abs x * signum x == x
For real numbers, the signum
is either -1
(negative), 0
(zero)
or 1
(positive).
fromInteger :: Integer -> aSource
Conversion from an Integer
.
An integer literal represents the application of the function
fromInteger
to the appropriate value of type Integer
,
so such literals have type (
.
Num
a) => a
Num Double | |
Num Float | |
Num Int | |
Num Int8 | |
Num Int16 | |
Num Int32 | |
Num Int64 | |
Num Integer | |
Num WordPtr | |
Num IntPtr | |
Num CChar | |
Num CSChar | |
Num CUChar | |
Num CShort | |
Num CUShort | |
Num CInt | |
Num CUInt | |
Num CLong | |
Num CULong | |
Num CLLong | |
Num CULLong | |
Num CFloat | |
Num CDouble | |
Num CPtrdiff | |
Num CSize | |
Num CWchar | |
Num CSigAtomic | |
Num CClock | |
Num CTime | |
Num CUSeconds | |
Num CSUSeconds | |
Num CIntPtr | |
Num CUIntPtr | |
Num CIntMax | |
Num CUIntMax | |
Num NominalDiffTime | |
Num DiffTime | |
Integral a => Num (Ratio a) | |
RealFloat a => Num (Complex a) |
class (Num a, Ord a) => Real a whereSource
toRational :: a -> RationalSource
the rational equivalent of its real argument with full precision
class (Real a, Enum a) => Integral a whereSource
integer division truncated toward zero
integer remainder, satisfying
(x `quot` y)*y + (x `rem` y) == x
integer division truncated toward negative infinity
integer modulus, satisfying
(x `div` y)*y + (x `mod` y) == x
quotRem :: a -> a -> (a, a)Source
divMod :: a -> a -> (a, a)Source
toInteger :: a -> IntegerSource
conversion to Integer
class Num a => Fractional a whereSource
Fractional numbers, supporting real division.
Minimal complete definition: fromRational
and (recip
or (
)
/
)
fractional division
reciprocal fraction
fromRational :: Rational -> aSource
Conversion from a Rational
(that is
).
A floating literal stands for an application of Ratio
Integer
fromRational
to a value of type Rational
, so such literals have type
(
.
Fractional
a) => a
class Fractional a => Floating a whereSource
Trigonometric and hyperbolic functions and related functions.
Minimal complete definition:
pi
, exp
, log
, sin
, cos
, sinh
, cosh
,
asin
, acos
, atan
, asinh
, acosh
and atanh
class (Real a, Fractional a) => RealFrac a whereSource
Extracting components of fractions.
Minimal complete definition: properFraction
properFraction :: Integral b => a -> (b, a)Source
The function properFraction
takes a real fractional number x
and returns a pair (n,f)
such that x = n+f
, and:
-
n
is an integral number with the same sign asx
; and -
f
is a fraction with the same type and sign asx
, and with absolute value less than1
.
The default definitions of the ceiling
, floor
, truncate
and round
functions are in terms of properFraction
.
truncate :: Integral b => a -> bSource
returns the integer nearest truncate
xx
between zero and x
round :: Integral b => a -> bSource
returns the nearest integer to round
xx
;
the even integer if x
is equidistant between two integers
ceiling :: Integral b => a -> bSource
returns the least integer not less than ceiling
xx
floor :: Integral b => a -> bSource
returns the greatest integer not greater than floor
xx
class (RealFrac a, Floating a) => RealFloat a whereSource
Efficient, machine-independent access to the components of a floating-point number.
Minimal complete definition:
all except exponent
, significand
, scaleFloat
and atan2
floatRadix :: a -> IntegerSource
a constant function, returning the radix of the representation
(often 2
)
floatDigits :: a -> IntSource
a constant function, returning the number of digits of
floatRadix
in the significand
floatRange :: a -> (Int, Int)Source
a constant function, returning the lowest and highest values the exponent may assume
decodeFloat :: a -> (Integer, Int)Source
The function decodeFloat
applied to a real floating-point
number returns the significand expressed as an Integer
and an
appropriately scaled exponent (an Int
). If
yields decodeFloat
x(m,n)
, then x
is equal in value to m*b^^n
, where b
is the floating-point radix, and furthermore, either m
and n
are both zero or else b^(d-1) <=
, where abs
m < b^dd
is
the value of
.
In particular, floatDigits
x
. If the type
contains a negative zero, also decodeFloat
0 = (0,0)
.
The result of decodeFloat
(-0.0) = (0,0)
is unspecified if either of
decodeFloat
x
or isNaN
x
is isInfinite
xTrue
.
encodeFloat :: Integer -> Int -> aSource
encodeFloat
performs the inverse of decodeFloat
in the
sense that for finite x
with the exception of -0.0
,
.
uncurry
encodeFloat
(decodeFloat
x) = x
is one of the two closest representable
floating-point numbers to encodeFloat
m nm*b^^n
(or ±Infinity
if overflow
occurs); usually the closer, but if m
contains too many bits,
the result may be rounded in the wrong direction.
exponent
corresponds to the second component of decodeFloat
.
and for finite nonzero exponent
0 = 0x
,
.
If exponent
x = snd (decodeFloat
x) + floatDigits
xx
is a finite floating-point number, it is equal in value to
, where significand
x * b ^^ exponent
xb
is the
floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
significand :: a -> aSource
The first component of decodeFloat
, scaled to lie in the open
interval (-1
,1
), either 0.0
or of absolute value >= 1/b
,
where b
is the floating-point radix.
The behaviour is unspecified on infinite or NaN
values.
scaleFloat :: Int -> a -> aSource
multiplies a floating-point number by an integer power of the radix
True
if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: a -> BoolSource
True
if the argument is an IEEE infinity or negative infinity
isDenormalized :: a -> BoolSource
True
if the argument is too small to be represented in
normalized format
isNegativeZero :: a -> BoolSource
True
if the argument is an IEEE negative zero
True
if the argument is an IEEE floating point number
a version of arctangent taking two real floating-point arguments.
For real floating x
and y
,
computes the angle
(from the positive x-axis) of the vector from the origin to the
point atan2
y x(x,y)
.
returns a value in the range [atan2
y x-pi
,
pi
]. It follows the Common Lisp semantics for the origin when
signed zeroes are supported.
, with atan2
y 1y
in a type
that is RealFloat
, should return the same value as
.
A default definition of atan
yatan2
is provided, but implementors
can provide a more accurate implementation.
Numeric functions
lcm :: Integral a => a -> a -> aSource
is the smallest positive integer that both lcm
x yx
and y
divide.
(^^) :: (Fractional a, Integral b) => a -> b -> aSource
raise a number to an integral power
fromIntegral :: (Integral a, Num b) => a -> bSource
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> bSource
general coercion to fractional types
Monads and functors
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Minimal complete definition: >>=
and return
.
Instances of Monad
should satisfy the following laws:
return a >>= k == k a m >>= return == m m >>= (\x -> k x >>= h) == (m >>= k) >>= h
Instances of both Monad
and Functor
should additionally satisfy the law:
fmap f xs == xs >>= return . f
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
(>>=) :: m a -> (a -> m b) -> m bSource
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m bSource
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
sequence :: Monad m => [m a] -> m [a]Source
Evaluate each action in the sequence from left to right, and collect the results.
sequence_ :: Monad m => [m a] -> m ()Source
Evaluate each action in the sequence from left to right, and ignore the results.
Miscellaneous functions
flip :: (a -> b -> c) -> b -> a -> cSource
takes its (first) two arguments in the reverse order of flip
ff
.
($) :: (a -> b) -> a -> bSource
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.
zipWith
($
) fs xs
until :: (a -> Bool) -> (a -> a) -> a -> aSource
yields the result of applying until
p ff
until p
holds.
seq :: a -> b -> b
List operations
map :: (a -> b) -> [a] -> [b]Source
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
(++) :: [a] -> [a] -> [a]Source
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
filter :: (a -> Bool) -> [a] -> [a]Source
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
Return all the elements of a list except the last one. The list must be non-empty.
O(n). length
returns the length of a finite list as an Int
.
It is an instance of the more general genericLength
,
the result type of which may be any kind of number.
List index (subscript) operator, starting from 0.
It is an instance of the more general genericIndex
,
which takes an index of any integral type.
reverse
xs
returns the elements of xs
in reverse order.
xs
must be finite.
Reducing lists (folds)
foldl :: (a -> b -> a) -> a -> [b] -> aSource
foldl
, applied to a binary operator, a starting value (typically
the left-identity of the operator), and a list, reduces the list
using the binary operator, from left to right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
The list must be finite.
foldr :: (a -> b -> b) -> b -> [a] -> bSource
foldr
, applied to a binary operator, a starting value (typically
the right-identity of the operator), and a list, reduces the list
using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Special folds
product :: Num a => [a] -> aSource
The product
function computes the product of a finite list of numbers.
Building lists
Scans
Infinite lists
iterate :: (a -> a) -> a -> [a]Source
iterate
f x
returns an infinite list of repeated applications
of f
to x
:
iterate f x == [x, f x, f (f x), ...]
replicate :: Int -> a -> [a]Source
replicate
n x
is a list of length n
with x
the value of
every element.
It is an instance of the more general genericReplicate
,
in which n
may be of any integral type.
cycle
ties a finite list into a circular one, or equivalently,
the infinite repetition of the original list. It is the identity
on infinite lists.
Sublists
take :: Int -> [a] -> [a]Source
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:
length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
,
in which n
may be of any integral type.
drop :: Int -> [a] -> [a]Source
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:
length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
,
in which n
may be of any integral type.
splitAt :: Int -> [a] -> ([a], [a])Source
splitAt
n xs
returns a tuple where first element is xs
prefix of
length n
and second element is the remainder of the list:
splitAt 6 "Hello World!" == ("Hello ","World!") splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) splitAt 1 [1,2,3] == ([1],[2,3]) splitAt 3 [1,2,3] == ([1,2,3],[]) splitAt 4 [1,2,3] == ([1,2,3],[]) splitAt 0 [1,2,3] == ([],[1,2,3]) splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to (
.
take
n xs, drop
n xs)splitAt
is an instance of the more general genericSplitAt
,
in which n
may be of any integral type.
takeWhile :: (a -> Bool) -> [a] -> [a]Source
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
span :: (a -> Bool) -> [a] -> ([a], [a])Source
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
break :: (a -> Bool) -> [a] -> ([a], [a])Source
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
Searching lists
lookup :: Eq a => a -> [(a, b)] -> Maybe bSource
lookup
key assocs
looks up a key in an association list.
Zipping and unzipping lists
zip :: [a] -> [b] -> [(a, b)]Source
zip
takes two lists and returns a list of corresponding pairs.
If one input list is short, excess elements of the longer list are
discarded.
unzip :: [(a, b)] -> ([a], [b])Source
unzip
transforms a list of pairs into a list of first components
and a list of second components.
Functions on strings
lines :: String -> [String]Source
lines
breaks a string up into a list of strings at newline
characters. The resulting strings do not contain newlines.
words :: String -> [String]Source
words
breaks a string up into a list of words, which were delimited
by white space.
Converting to and from String
Converting to String
Conversion of values to readable String
s.
Minimal complete definition: showsPrec
or show
.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
-
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
:: Int | the operator precedence of the enclosing
context (a number from |
-> a | the value to be converted to a |
-> ShowS |
Convert a value to a readable String
.
showsPrec
should satisfy the law
showsPrec d x r ++ s == showsPrec d x (r ++ s)
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by
showsPrec
, and delivers the value that showsPrec
started with.
showChar :: Char -> ShowSSource
utility function converting a Char
to a show function that
simply prepends the character unchanged.
showString :: String -> ShowSSource
utility function converting a String
to a show function that
simply prepends the string unchanged.
Converting from String
Parsing of String
s, producing values.
Minimal complete definition: readsPrec
(or, for GHC only, readPrec
)
Derived instances of Read
make the following assumptions, which
derived instances of Show
obey:
- If the constructor is defined to be an infix operator, then the
derived
Read
instance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Read
will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Read
instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read
in Haskell 98 is equivalent to
instance (Read a) => Read (Tree a) where readsPrec d r = readParen (d > app_prec) (\r -> [(Leaf m,t) | ("Leaf",s) <- lex r, (m,t) <- readsPrec (app_prec+1) s]) r ++ readParen (d > up_prec) (\r -> [(u:^:v,w) | (u,s) <- readsPrec (up_prec+1) r, (":^:",t) <- lex s, (v,w) <- readsPrec (up_prec+1) t]) r where app_prec = 10 up_prec = 5
Note that right-associativity of :^:
is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where readPrec = parens $ (prec app_prec $ do Ident "Leaf" <- lexP m <- step readPrec return (Leaf m)) +++ (prec up_prec $ do u <- step readPrec Symbol ":^:" <- lexP v <- step readPrec return (u :^: v)) where app_prec = 10 up_prec = 5 readListPrec = readListPrecDefault
:: Int | the operator precedence of the enclosing
context (a number from |
-> ReadS a |
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by
showsPrec
, and delivers the value that
showsPrec
started with.
read :: Read a => String -> aSource
The read
function reads input from a string, which must be
completely consumed by the input process.
The lex
function reads a single lexeme from the input, discarding
initial white space, and returning the characters that constitute the
lexeme. If the input string contains only white space, lex
returns a
single successful `lexeme' consisting of the empty string. (Thus
.) If there is no legal lexeme at the
beginning of the input string, lex
"" = [("","")]lex
fails (i.e. returns []
).
This lexer is not completely faithful to the Haskell lexical syntax in the following respects:
- Qualified names are not handled properly
- Octal and hexadecimal numerics are not recognized as a single token
- Comments are not treated properly
Basic Input and output
Simple I/O operations
Output functions
print :: Show a => a -> IO ()Source
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
Input functions
getContents :: IO StringSource
The getContents
operation returns all user input as a single string,
which is read lazily as it is needed
(same as hGetContents
stdin
).
interact :: (String -> String) -> IO ()Source
The interact
function takes a function of type String->String
as its argument. The entire input from the standard input device is
passed to this function as its argument, and the resulting string is
output on the standard output device.
Files
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
readFile :: FilePath -> IO StringSource
The readFile
function reads a file and
returns the contents of the file as a string.
The file is read lazily, on demand, as with getContents
.
writeFile :: FilePath -> String -> IO ()Source
The computation writeFile
file str
function writes the string str
,
to the file file
.
appendFile :: FilePath -> String -> IO ()Source
The computation appendFile
file str
function appends the string str
,
to the file file
.
Note that writeFile
and appendFile
write a literal string
to a file. To write a value of any printable type, as with print
,
use the show
function to convert the value to a string first.
main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
Exception handling in the I/O monad
type IOError = IOExceptionSource
The Haskell 98 type for exceptions in the IO
monad.
Any I/O operation may raise an IOError
instead of returning a result.
For a more general type of exception, including also those that arise
in pure code, see Control.Exception.Exception.
In Haskell 98, this is an opaque type.
catch :: IO a -> (IOError -> IO a) -> IO aSource
The catch
function establishes a handler that receives any
IOError
raised in the action protected by catch
.
An IOError
is caught by
the most recent handler established by one of the exception handling
functions. These handlers are
not selective: all IOError
s are caught. Exception propagation
must be explicitly provided in a handler by re-raising any unwanted
exceptions. For example, in
f = catch g (\e -> if IO.isEOFError e then return [] else ioError e)
the function f
returns []
when an end-of-file exception
(cf. isEOFError
) occurs in g
; otherwise, the
exception is propagated to the next outer handler.
When an exception propagates outside the main program, the Haskell
system prints the associated IOError
value and exits the program.
Non-I/O exceptions are not caught by this variant; to catch all
exceptions, use catch
from Control.Exception.