6.1 Standard Haskell Types
These types are defined by the Haskell Prelude. Numeric types are
described in Section 6.3. When appropriate, the Haskell
definition of the type is given. Some definitions may not be
completely valid on syntactic grounds but they faithfully convey the
meaning of the underlying type.
data Bool = False | True deriving (Read, Show, Eq, Ord, Enum, Bounded)The boolean type Bool is an enumeration.The basic boolean functions are && (and), || (or), and not. The name otherwise is defined as True to make guarded expressions more readable.
The character type Char is an enumeration and consists of 256 values, conforming to the ISO 8859-1 standard . The lexical syntax for characters is defined in Section 2.5; character literals are nullary constructors in the datatype Char. Type Char is an instance of the classes Read, Show, Eq, Ord, Enum, and Bounded. The toEnum and fromEnum functions, standard functions over bounded enumerations, map characters onto Int values in the range [ 0 , 255 ].
Note that ASCII control characters each have several representations in character literals: numeric escapes, ASCII mnemonic escapes, and the \^X notation. In addition, there are the following equivalences: \a and \BEL, \b and \BS, \f and \FF, \r and \CR, \t and \HT, \v and \VT, and \n and \LF.
A string is a list of characters:
type String = [Char]Strings may be abbreviated using the lexical syntax described in Section 2.5. For example, "A string" abbreviates
[ 'A',' ','s','t','r', 'i','n','g']
data [a] = [] | a : [a] deriving (Eq, Ord)Lists are an algebraic datatype of two constructors, although with special syntax, as described in Section 3.7. The first constructor is the null list, written `[]' ("nil"), and the second is `:' ("cons"). The module PreludeList (see Appendix A.1) defines many standard list functions. Arithmetic sequences and list comprehensions, two convenient syntaxes for special kinds of lists, are described in Sections 3.10 and 3.11, respectively. Lists are an instance of classes Read, Show, Eq, Ord, Monad, MonadZero, and MonadPlus.
Tuples are algebraic datatypes with special syntax, as defined in Section 3.8. Each tuple type has a single constructor. There is no upper bound on the size of a tuple. However, some Haskell implementations may restrict the size of tuples and limit the instances associated with larger tuples. The Prelude and libraries define tuple functions such as zip for tuples up to a size of 7. All tuples are instances of Eq, Ord, Bounded, Read, and Show. Classes defined in the libraries may also supply instances for tuple types. The constructor for a tuple is written by omitting the expressions surrounding the commas: thus (x,y) and (,) x y produce the same value. The following functions are defined for pairs (2-tuples): fst, snd, curry, and uncurry. Similar functions are not predefined for larger tuples.
data () = () deriving (Eq, Ord, Bounded, Enum, Read, Show)The unit datatype () has one non-bottom member, the nullary constructor (). See also Section 3.9.
data VoidThe Void has no constructors; only bottom is an instance of this type.
IOError is an abstract type representing errors raised by I/O
operations. It is an instance of Show and Eq. Values of this type
are constructed by the various I/O functions and are not presented in
any further detail in this report. The Library Report contains many
other I/O functions.
For convenience, the Prelude provides the following auxiliary
functions:
The Functor
class is used for types which can be mapped over. Lists, IO, and
Maybe are in this class. The
IO type, Maybe, and lists are instances of Monad. The do syntax
provides a more readable notation for the operators in Monad. Both
lists and Maybe are instances of the MonadZero class.
The MonadPlus class provides a `monadic addition' operator: ++.
In the Prelude, Maybe and
lists are in this class. For lists, ++ defines concatenation. For
Maybe, the ++ function returns the first non-empty value (if any).
Instances of these classes should satisfy the following laws:
All instances defined in the Prelude satisfy these laws.
The Prelude provides the following auxiliary
functions:
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 types Int, Char, Bool,
(), Ordering, and all tuples are instances of Bounded.
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.
The functions seq and strict are defined by the equations:
These functions are usually introduced to improve performance by
avoiding unneeded laziness. Strict datatypes (see
Section 4.2.1) are defined in terms of the strict
function. This class explicitly marks functions and types
which employ polymorphic strictness.
The Eval instance for a type T with a constructor C implicitly
derived by the compiler is:
Haskell provides several kinds of numbers; the numeric
types and the operations upon them have been heavily influenced by
Common Lisp and Scheme.
Numeric function names and operators are usually overloaded, using
several type classes with an inclusion relation shown in
Figure 5.
The class Num of numeric
types is a subclass of Eq, since all numbers may be
compared for equality; its subclass Real is also a
subclass of Ord, since the other comparison operations
apply to all but complex numbers (defined in the Complex library).
The class Integral contains both fixed- and
arbitrary-precision integers; the class
Fractional contains all non-integral types; and
the class Floating contains all floating-point
types, both real and complex.
The Prelude defines only the most basic numeric types: fixed sized
integers (Int), arbitrary precision integers (Integer), single
precision floating (Float), and double precision floating
(Double). Other numeric types such as rationals and complex numbers
are defined in libraries. In particular, the type Rational is a
ratio of two Integer values, as defined in the Rational
library.
The default floating point operations defined by the Haskell
Prelude do not
conform to current language independent arithmetic (LIA) standards. These
standards require considerable more complexity in the numeric
structure and have thus been relegated to a library. Some, but not
all, aspects of the IEEE standard floating point standard have been
accounted for in class RealFloat.
Table 3 lists the standard numeric types.
The type Int covers at
least the range
[ - 229, 229 - 1]. As Int is an instance of the Bounded
class, maxBound and minBound can be used to determine the exact
Int range defined by an implementation.
Float is implementation-defined; it is desirable that
this type be at least equal in range and precision to the IEEE
single-precision type. Similarly, Double should
cover IEEE double-precision. The results of exceptional
conditions (such as overflow or underflow) on the fixed-precision
numeric types are undefined; an implementation may choose error
(bottom, semantically), a truncated value, or a special value such as
infinity, indefinite, etc.
The standard numeric classes and other numeric functions defined in
the Prelude are shown
in Figures 6--7.
Figure 5 shows the class dependencies and
built-in types which are instances of the numeric classes.
The syntax of numeric literals is given in
Section 2.4. An integer literal represents the
application
of the function fromInteger to the appropriate
value of type
Integer. Similarly, a floating literal stands for an application of
fromRational to a value of type Rational (that is,
Ratio Integer). Given the typings:
The infix class methods
(+),
(*),
(-),
and the unary function
negate (which can also be written as a prefix minus sign; see
section 3.4) apply to all numbers. The class methods
quot, rem, div, and
mod apply only to integral numbers, while the class method
(/)
applies only to fractional ones. The quot, rem,
div, and mod class methods satisfy these laws:
`quot` is integer division truncated toward zero,
while the result of `div` is truncated toward
negative infinity.
The quotRem class method takes a dividend and a divisor as arguments
and returns a (quotient, remainder) pair; divMod is defined
similarly:
The one-argument exponential function exp and the
logarithm function log act on floating-point numbers and
use base e. logBase a x returns the
logarithm of x in base a. sqrt returns the
principal square root of a floating-point number.
There are three two-argument exponentiation operations:
(^) raises any number to a nonnegative integer power,
(^^) raises a
fractional number to any integer power, and (**)
takes two floating-point arguments. The value of x^0 or x^^0
is 1 for any x, including zero; 0**y is undefined.
A number has a magnitude
and a sign. The functions abs and
signum apply to any number and satisfy the law:
The circular and hyperbolic sine, cosine,
and tangent functions and their inverses are provided
for floating-point numbers. A version of arctangent
taking two real floating-point arguments is also provided: For real floating
x and y, atan2 y x differs from
atan (y/x) in that its range is
( -pi , pi ] rather than (- pi / 2 , pi / 2 ) (because the signs
of the arguments provide quadrant information), and that it is defined
when x is zero.
The precise definition of the above functions is as in Common Lisp,
which in turn follows Penfield's proposal for
APL . See these references for discussions
of branch cuts, discontinuities, and implementation.
The ceiling, floor,
truncate, and round
functions each take a real fractional argument and return an integral
result. ceiling x returns the least integer not less than x, and
floor x, the greatest integer not greater than x. truncate x
yields the integer nearest x between 0 and x, inclusive.
round x returns the nearest integer to x, the even integer if
x is equidistant between two integers.
The function properFraction takes a real
fractional number x and returns a pair comprising x as a
proper fraction: an integral number with the same sign as x and a
fraction with the same type and sign as x and with absolute
value less than 1. The ceiling, floor, truncate, and round
functions can be defined in terms of this one.
Two functions convert numbers to type Rational:
toRational returns the rational equivalent of
its real argument with full precision;
approxRational takes two real fractional arguments
x and e and returns the simplest rational number within
e of x, where a rational p/q in reduced form is
simpler than another p' / q' if
|p| <= |p'| and q <= q' .
Every real interval contains a unique simplest rational;
in particular, note that 0/1 is the simplest rational of all. The class methods of class RealFloat allow
efficient, machine-independent
access to the components of a floating-point number.
The functions floatRadix,
floatDigits, and
floatRange give the parameters of a
floating-point type: the radix of the representation, the number of
digits of this radix in the significand, and the lowest and highest
values the exponent may assume, respectively.
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 decodeFloat x yields (m,n), then x is
equal in value to mbn, where b is the floating-point radix, and
furthermore, either m and n are both zero or else
bd-1<=m<bd, where d is the value of floatDigits x.
encodeFloat performs the inverse of this
transformation. The functions significand
and exponent together provide the same
information as decodeFloat, but rather than an Integer,
significand x yields a value of the same type as x, scaled to lie
in the open interval (-1,1). exponent 0 is zero. scaleFloat
multiplies a floating-point number by an integer power of the radix.
The functions isNaN, isInfinite, isDenormalized,
isNegativeZero, and isIEEE all support numbers represented using
the IEEE standard. For non-IEEE floating point numbers, these may all
return false.
Also available are the following coercion functions:
6.1.7 Function Types
Functions are an abstract type: no constructors directly create
functional values. Functions are an instance of the Show class but
not Read. The following simple functions are found the Prelude:
id, const, (.), flip, ($), and until.
6.1.8 The IO and IOError Types
The IO type serves as a tag for operations (actions) which interact
with the outside world. The IO type is abstract: no constructors are
visible to the user. IO is an instance of the Monad and
Show classes. Section 7 describes I/O operations.
6.1.9 Other Types
data Maybe a = Nothing | Just a deriving (Eq, Ord, Read, Show)
data Either a b = Left a | Right b deriving (Eq, Ord, Read, Show)
data Ordering = LT | EQ | GT deriving
(Eq, Ord, Bounded, Enum, Read, Show)
The Maybe type is an instance of classes Functor, Monad,
MonadZero and MonadPlus. The Ordering type is used by compare
in the class Ord. The functions maybe and either are found in
the Prelude.
6.2 Standard Haskell Classes
Figure 5 shows the hierarchy of
Haskell classes defined in the Prelude and the Prelude types which
are instances of these classes. The Void type is not mentioned in
this figure since it is not a member of any classes.
Figure 5
Standard Haskell Classes
6.2.1 The Eq Class
class Eq a where
(==), (/=) :: a -> a -> Bool
x /= y = not (x == y)
All basic datatypes except for functions and IO are instances of this class.
Instances of Eq can be derived for any user-defined datatype whose
constituents are also instances of Eq.
6.2.2 The Ord Class
class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>=), (>) :: a -> a -> Bool
max, min :: a -> a -> a
compare x y
| x == y = EQ
| x <= y = LT
| otherwise = GT
x <= y = compare x y /= GT
x < y = compare x y == LT
x >= y = compare x y /= LT
x > y = compare x y == GT
-- note that (min x y, max x y) = (x,y) or (y,x)
max x y | x >= y = x
| otherwise = y
min x y | x < y = x
| otherwise = y
The Ord class is used for totally ordered datatypes. All basic
datatypes
except for functions and IO are instances of this class. 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 defaults allow a user to create an Ord instance
either with a type-specific compare function or with type-specific
== and <= functions.
6.2.3 The Read and Show Classes
type ReadS a = String -> [(a,String)]
type ShowS = String -> String
class Read a where
readsPrec :: Int -> ReadS a
readList :: ReadS [a]
class Show a where
showsPrec :: Int -> a -> ShowS
showList :: [a] -> ShowS
The Read and Show classes are used to convert values to
or from strings.
Derived instances of Read and Show replicate the style in which a
constructor is declared: infix constructors and field names are used
on input and output. Strings produced by showsPrec are usually
readable by readsPrec. Functions and the IO type are not in Read.
reads :: (Read a) => ReadS a
reads = readsPrec 0
shows :: (Show a) => a -> ShowS
shows = showsPrec 0
read :: (Read a) => String -> a
read s = case [x | (x,t) <- reads s, ("","") <- lex t] of
[x] -> x
[] -> error "PreludeText.read: no parse"
_ -> error "PreludeText.read: ambiguous parse"
show :: (Show a) => a -> String
show x = shows x ""
shows and reads use a default precedence of 0. The show
function returns a String instead of a ShowS; the read function reads
input from a string which must be completely consumed by the input
process. The lex function used by read is also part of the Prelude.
6.2.4 The Enum Class
class (Ord a) => Enum a where
toEnum :: Int -> a
fromEnum :: a -> Int
enumFrom :: a -> [a] -- [n..]
enumFromThen :: a -> a -> [a] -- [n,n'..]
enumFromTo :: a -> a -> [a] -- [n..m]
enumFromThenTo :: a -> a -> a -> [a] -- [n,n'..m]
enumFromTo n m = takeWhile (<= m) (enumFrom n)
enumFromThenTo n n' m
= takeWhile (if n' >= n then (<= m) else (>= m))
(enumFromThen n n')
Class Enum defines operations on sequentially ordered types.
The toEnum and fromEnum functions map values from a type in
Enum onto Int. These functions are not meaningful for all
instances of Enum: floating
point values or Integer may not be mapped onto an Int. An
runtime error occurs if either toEnum or fromEnum is given a value
not mappable to the result type. Instances of Enum may be derived
for any enumeration type (types whose constructors have no fields).
There are also Enum instances for floats.
class Functor f where
map :: (a -> b) -> (f a -> f b)
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
class (Monad m) => MonadZero m where
zero :: m a
class (MonadZero m) => MonadPlus m where
(++) :: m a -> m a -> m a
These classes define the basic monadic operations. See Section
7 for more information about monads.
The monadic classes
serve to organize a set of operations common to a number of
related types. These types are all container types: that is, they
contain a value or values of another type. (To be precise, types in
these classes must have kind *->*.)
In the Prelude, lists,
Maybe, and IO are all predefined container types.
map id = id
map (f . g) = map f . map g
map f xs = xs >>= return . f
return a >>= k = k a
m >>= return = m
m >>= (\x -> k x >>= h)) = (m >>= k) >>= h
m >> zero = zero
zero >>= m = zero
m ++ zero = m
zero ++ m = m
accumulate :: Monad m => [m a] -> m [a]
sequence :: Monad m => [m a] -> m ()
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
guard :: MonadZero m => Bool -> m ()
6.2.6 The Bounded Class
class Bounded a where
minBound, maxBound :: a
class Eval a where
strict :: (a -> b) -> a -> b
seq :: a -> b -> b
strict f x = x `seq` f x
Class Eval is a special class for which no instances may be
explicitly defined.
An Eval instance is implicitly derived for every
datatype. Functions as well as
all other built-in types are in Eval. (As a consequence, bottom is
not the same as \x -> bottom since seq can be used to distinguish them.)
seq bottom b = bottom
seq a b = b, if a /= bottom
strict f x = seq x (f x)
instance Eval T where
x `seq` y = case x of
C -> y
_ -> y -- catches any other constructors in T
The case is used to force evaluation of the first argument to `seq`
before returning the second argument. The constructor mentioned
by seq is arbitrary: any constructor from T can be
used.
Type
Class
Description
Integer Integral Arbitrary-precision integers
Int Integral Fixed-precision integers
(Integral a) => Ratio a RealFrac Rational numbers
Float RealFloat Real floating-point, single precision
Double RealFloat Real floating-point, double precision
(RealFloat a) => Complex a Floating Complex floating-point
Table 2
Standard Numeric Types
class (Eq a, Show a, Eval a) => Num a where
(+), (-), (*) :: a -> a -> a
negate :: a -> a
abs, signum :: a -> a
fromInteger :: Integer -> a
class (Num a, Ord a) => Real a where
toRational :: a -> Rational
class (Real a, Enum a) => Integral a where
quot, rem, div, mod :: a -> a -> a
quotRem, divMod :: a -> a -> (a,a)
toInteger :: a -> Integer
class (Num a) => Fractional a where
(/) :: a -> a -> a
recip :: a -> a
fromRational :: Rational -> a
class (Fractional a) => Floating a where
pi :: a
exp, log, sqrt :: a -> a
(**), logBase :: a -> a -> a
sin, cos, tan :: a -> a
asin, acos, atan :: a -> a
sinh, cosh, tanh :: a -> a
asinh, acosh, atanh :: a -> a
Figure 6
Standard Numeric Classes and Related Operations, Part 1
class (Real a, Fractional a) => RealFrac a where
properFraction :: (Integral b) => a -> (b,a)
truncate, round :: (Integral b) => a -> b
ceiling, floor :: (Integral b) => a -> b
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, isInfinite, isDenormalized, isNegativeZero, isIEEE
:: a -> Bool
fromIntegral :: (Integral a, Num b) => a -> b
gcd, lcm :: (Integral a) => a -> a-> a
(^) :: (Num a, Integral b) => a -> b -> a
(^^) :: (Fractional a, Integral b) => a -> b -> a
fromRealFrac :: (RealFrac a, Fractional b) => a -> b
atan2 :: (RealFloat a) => a -> a -> a
Figure 7
Standard Numeric Classes and Related Operations, Part 2
fromInteger :: (Num a) => Integer -> a
fromRational :: (Fractional a) => Rational -> a
integer and floating literals have the
typings (Num a) => a and (Fractional a) => a, respectively.
Numeric literals are defined in this indirect way so that they may be
interpreted as values of any appropriate numeric type.
See Section 4.3.4 for a discussion of overloading ambiguity.
6.3.2 Arithmetic and Number-Theoretic Operations
(x `quot` y)*y + (x `rem` y) == x
(x `div` y)*y + (x `mod` y) == x
quotRem x y = (x `quot` y, x `rem` y)
divMod x y = (x `div` y, x `mod` y)
Also available on integral numbers are the even and odd predicates:
even x = x `rem` 2 == 0
odd = not . even
Finally, there are the greatest common divisor and least common
multiple functions: gcd x y is the greatest
integer that divides both x and y. lcm x y
is the smallest positive integer that both x and y divide.
6.3.3 Exponentiation and Logarithms
6.3.4 Magnitude and Sign
abs x * signum x == x
For real numbers, these functions are defined by:
abs x | x >= 0 = x
| x < 0 = -x
signum x | x > 0 = 1
| x == 0 = 0
| x < 0 = -1
6.3.5 Trigonometric Functions
6.3.6 Coercions and Component Extraction
fromIntegral :: (Integral a, Num b) => a -> b
fromRealFrac :: (RealFrac a, Fractional b) => a -> b