Table of Contents
Typeclasses are one of the most powerful features in Haskell. They are also at the heart of some basic language features such as equality testing and numeric operators. Before we talk about what exactly typeclasses are, though, we'd like to first explain the need for them.
Let's imaging that for some unfathomable reason, the designers of the
Haskell language neglected to implement the equality test
==
. Once you got over your shock at hearing this,
you resolved to implement your own equality tests. Your application
consisted of a simple Color type, and so your first
equality test is for this type. Your first attempt might look like
Example 6.1, “Naive Equality -- Colors (naiveeq.hs)”.
Example 6.1. Naive Equality -- Colors (naiveeq.hs)
data Color = Red | Green | Blue colorEq :: Color -> Color -> Bool colorEq Red Red = True colorEq Red _ = False colorEq Green Green = True colorEq Green _ = False colorEq Blue Blue = True colorEq Blue _ = Falsedata Color = Red | Green | Blue colorEq :: Color -> Color -> Bool colorEq Red Red = True colorEq Red _ = False colorEq Green Green = True colorEq Green _ = False colorEq Blue Blue = True colorEq Blue _ = False
You can test this with ghci or hugs:
*Main> colorEq Red Red True *Main> colorEq Red Blue False *Main>colorEq Red Red
True *Main>colorEq Red Blue
False
Now, let's say that you want to add an equality test for
String
s.
Since a Haskell String
is a list of characters, we can
write a simple function to perform that test.
For simplicity, we
cheat a bit and use the ==
operator a couple
of times.
stringEq :: [Char] -> [Char] -> Bool -- Match if both are empty stringEq [] [] = True -- Evaluate when we have only one character in both stringEq [x] [y] = x == y -- If both start with the same char, check the rest stringEq (x:xs) (y:ys) = if x == y then stringEq xs ys else False -- Everything else doesn't match stringEq _ _ = FalsestringEq :: [Char] -> [Char] -> Bool -- Match if both are empty stringEq [] [] = True -- Evaluate when we have only one character in both stringEq [x] [y] = x == y -- If both start with the same char, check the rest stringEq (x:xs) (y:ys) = if x == y then stringEq xs ys else False -- Everything else doesn't match stringEq _ _ = False
You should now be able to see a problem: we have to define a new
function for every different type that we want to be able to compare.
That's inefficient and annoying. It's much more convenient to be able
to just use ==
to compare anything. As it turns
out, this is exactly what Haskell's typeclasses are for.
Typeclasses define a set of functions that can operate on more than one type of data. A typeclass defines an interface, and perhaps even default implementations of functions. You then create an instance for each type that should conform to the typeclass. Once that is done, a function that's part of the typeclass definition can be called with any type that's an instance of the typeclass as a parameter.
Those familiar with object-oriented programming can think of typeclasses as objects in reverse. In OOP, when you define an object, you define what its parent classes are at that time. You must also define how it implements the methods in the parent class, if you need a custom implementation.
With typeclasses, you have greater freedom. Let's say that you have a type from a third party. Perhaps that third party didn't make it part of a typeclass that you'd like it to be part of. No problem; you can define an instance yourself. With OOP, the best you can do is subclass an object and use multiple inheritance (or, in Java, interfaces) to make the child object behave as you like. But you're still stuck if you have a parent object from somewhere.
In case that wasn't all clear, let's consider an example. Imagine you have a
basket of fruit. There are things that you might want to do
with just about all
fruit: eat it, peel it, or maybe remove the seeds. If you were to
model these actions in a Haskell library, you'd set up a Fruit
typeclass. You might define functions such as eat
,
peel
, and removeSeeds
in that
typeclass.
Now, your Apple
type could be an instance of
Fruit
, implementing the three functions. It could
describe removing the core of the apple to get rid of the seeds. You
might also define a Peach
instance that describes
removing the one big seed at the center. Now, you can release Fruit
v1.0. Yum!
Now, some of your friends download your library. They think that
apples and peaches are fine, but maybe they'd also like to be able to
eat oranges. No problem; they define an Orange
type
and make it an instance of Fruit
. It's not
necessary to modify your code to do this; anything that can operate on
a Fruit
can now automatically operate an an
Orange
as well. Thanks to typeclasses, you'll have
the best fruit salad out there.
Let's use typeclasses to solve our equality dilemma from earlier in the chapter. The first thing that we need to do is define the typeclass itself. What we want is a function that takes two parameters, both the same type, and returns a Bool indicating whether or not they are equal. Here's our first definition of a typeclass:
class BasicEq a where isEqual :: a -> a -> Boolclass BasicEq a where isEqual :: a -> a -> Bool
This says that we are declaring a typeclass named
BasicEq
, and we'll refer to instance types with the
letter a
. This typeclass defines one function.
That function takes two parameters -- both corresponding to instance
types -- and returns a Bool.
On the first line, the name of the parameter a
was chosen arbitrarily. We could have used any name. The key is that,
when you list the types of your functions, you must use that name to
refer to instance types.
Let's look at this in ghci. FIXME:
insert reference to where this is defined
Recall that you
can type :t in ghci to
have it show you the type of something. Let's see what it says about
isEqual
:
*Main> :t isEqual
isEqual :: (BasicEq a) => a -> a -> Bool
*Main> :t isEqual
isEqual :: (BasicEq a) => a -> a -> Bool
You can read that this way: "For all types of a, so
long as a is an instance of
BasicEq
, isEqual
takes two
parameters of type a and returns a Bool".
Now that we've seen a very simple typeclass, let's expand it a bit. A not-equal-to function might be useful. Here's what we might say to define a typeclass with two functions:
class BasicEq2 a where isEqual2 :: a -> a -> Bool isNotEqual2 :: a -> a -> Boolclass BasicEq2 a where isEqual2 :: a -> a -> Bool isNotEqual2 :: a -> a -> Bool
Someone providing an instance of BasicEq2
will
be required to define two functions: isEqual2
and
isNotEqual2
.
While our definition of BasicEq2
is fine, it seems
that we're making extra work for ourselves. Logically speaking, if we
know what isEqual
or
isNotEqual
would return, we know how to figure out
what the other function would return, for all types. Rather than
making users of the typeclass define both functions for all types, we
can provide default implementations for them. Then, users will only
have to implement one function.
[1]
Here's an example that shows how to do
this.
class BasicEq3 a where isEqual3 :: a -> a -> Bool isEqual3 x y = not (isNotEqual3 x y) isNotEqual3 :: a -> a -> Bool isNotEqual3 x y = not (isEqual3 x y)class BasicEq3 a where isEqual3 :: a -> a -> Bool isEqual3 x y = not (isNotEqual3 x y) isNotEqual3 :: a -> a -> Bool isNotEqual3 x y = not (isEqual3 x y)
People implementing this class must provide an implementation of at least one function. They can implement both if they wish, but they will not be required to.
With BasicEq3
, we have provided a class that does
very much the same thing as Haskell's built-in ==
and /=
operators. In fact, these operators are
defined by a typeclass that looks almost identical to
BasicEq3
. The Haskell 98 Report FIXME: add
reference? --jg defines a typeclass that implements equality
comparison. See Example 6.2, “Haskell Standard Eq Typeclass” for the built-in
Eq
typeclass, and note how similar it is to our
BasicEq3
typeclass.
FIXME: How to cite sources on this? -- jg
Example 6.2. Haskell Standard Eq Typeclass
class Eq a where (==), (/=) :: a -> a -> Bool -- Minimal complete definition: -- (==) or (/=) x /= y = not (x == y) x == y = not (x /= y) class Eq a where (==), (/=) :: a -> a -> Bool -- Minimal complete definition: -- (==) or (/=) x /= y = not (x == y) x == y = not (x /= y)
Now that you know how to define typeclasses, it's time to learn how to define instances of typeclasses. An instance is just a type. Making it an instance of a particular typeclass means implementing the functions necessary for that typeclass.
Recall our attempt to create a test for equality over a
Color
type back in Example 6.1, “Naive Equality -- Colors (naiveeq.hs)”.
Now let's see how we could make that same Color
type a member of the BasicEq3
class.
instance BasicEq3 Color where isEqual3 Red Red = True isEqual3 Red _ = False isEqual3 Green Green = True isEqual3 Green _ = False isEqual3 Blue Blue = True isEqual3 Blue _ = Falseinstance BasicEq3 Color where isEqual3 Red Red = True isEqual3 Red _ = False isEqual3 Green Green = True isEqual3 Green _ = False isEqual3 Blue Blue = True isEqual3 Blue _ = False
Notice that we provide essentially the same function as we used
back in Example 6.1, “Naive Equality -- Colors (naiveeq.hs)”. In fact, the
implementation is identical. However, in this case, we can use
isEqual3
on any type that
we declare is an instance of BasicEq3
, not just
this one color type. We could define equality tests for any anything
from numbers to graphics using the same basic pattern. In fact, as you
will see in the section called “Equality, Ordering, and Comparisons”, this
works the same as making Haskell's ==
operator
work for your own custom types.
Note also that the BasicEq3
class defined both
isEqual3
and isNotEqual3
, but we
defined only one of them. That's because of the default implementation
contained in BasicEq3
. Since we didn't explicitly
define isNotEqual3
, the compiler automatically uses
the default implementation given in the BasicEq3
declaration.
Now that you're familiar with defining your own typeclasses and making your types instances of typeclasses, it's time to introduce you to typeclasses that are a standard part of Haskell. As we mentioned at the beginning of this chapter, typeclasses are at the core of some imporant aspects of the language. We'll cover the most common ones here.
The Show
typeclass is used to convert types to
String
s. It is perhaps most commonly used to
convert numbers to String
s, but it is defined for
so many types that it can be used to convert quite a bit more. You
can also, of course, define instances for your own types as well.
The most important function of Show
is
show
. It takes one argument: the type to convert.
It returns a String
representing that type.
ghci reports that this way:
ghci> :t show show :: (Show a) => a -> Stringghci>
:t show
show :: (Show a) => a -> String
Let's look at some examples of converting numbers to strings:
ghci> show 1 "1" ghci> show [1, 2, 3] "[1,2,3]" ghci> show (1, 2) "(1,2)"ghci>
show 1
"1"ghci>
show [1, 2, 3]
"[1,2,3]"ghci>
show (1, 2)
"(1,2)"
Remember that ghci displays results as they would
be entered into Haskell. So the expression show 1
returns a single-character string containing the digit
1
. That is, the quotes are not part of the string
itself. We can make that clear by using
printStrLn
:
ghci> putStrLn (show 1) 1 ghci> putStrLn (show [1,2,3]) [1,2,3]ghci>
putStrLn (show 1)
1ghci>
putStrLn (show [1,2,3])
[1,2,3]
You can also use show
on
String
s:
ghci> show "Hello!" "\"Hello!\"" ghci> putStrLn (show "Hello!") "Hello!" ghci> show ['H', 'i'] "\"Hi\"" ghci> putStrLn (show "Hi") "Hi" ghci> show "Hi, \"Jane\"" "\"Hi, \\\"Jane\\\"\"" ghci> putStrLn (show "Hi, \"Jane\"") "Hi, \"Jane\""ghci>
show "Hello!"
"\"Hello!\""ghci>
putStrLn (show "Hello!")
"Hello!"ghci>
show ['H', 'i']
"\"Hi\""ghci>
putStrLn (show "Hi")
"Hi"ghci>
show "Hi, \"Jane\""
"\"Hi, \\\"Jane\\\"\""ghci>
putStrLn (show "Hi, \"Jane\"")
"Hi, \"Jane\""
Running show
on String
s can be
confusing. Since show
generates a result that
is suitable for a Haskell literal, show
adds
quotes and escaping suitable for inclusion in a Haskell program.
ghci also uses show
to
display results, so quotes and escaping get added twice. Using
putStrLn
can help make this difference clear.
You can define a Show
instance for your own types
easily. Here's an example:
instance Show Color where show Red = "Red" show Green = "Green" show Blue = "Blue"instance Show Color where show Red = "Red" show Green = "Green" show Blue = "Blue"
This example defines an instance of Show
for our
type
Color
(see Example 6.1, “Naive Equality -- Colors (naiveeq.hs)”). The implementation is
simple: we define a function show
and that's all
that's needed.
The Read
typeclass is essentially the opposite of Show
: it will
take a String
, parse it, and return data in a native Haskell type.
The most useful function in Read
is read
.
You can ask ghci for its type like this:
ghci> :t read read :: (Read a) => String -> aghci>
:t read
read :: (Read a) => String -> a
Here's an example illustrating the use of read
and show
:
main = do putStrLn "Please enter an integer:" inpStr <- getLine let inpInt = (read inpStr)::Integer putStrLn ("Twice " ++ show inpInt ++ " is " ++ show (inpInt * 2))main = do putStrLn "Please enter an integer:" inpStr <- getLine let inpInt = (read inpStr)::Integer putStrLn ("Twice " ++ show inpInt ++ " is " ++ show (inpInt * 2))
FIXME: have we already explained main?
This is a simple example of read
and show
together. Notice that
we gave an explicit typecast to Integer
when processing the read
.
That's because read
returns a value of type
Read a => a
and show
expects a value of type
Show a => a
. There are many, many types that are
defined for both Read
and Show
. Without knowing a specific type,
the compiler can't possibly guess from these many types which one is
needed -- at least not in this case. Therefore, we give an explicit
cast.
You can see the same effect at work if you try to use read
on the
ghci command line. ghci internally uses show
to display
results, meaning that you can hit this ambiguous typing problem there
as well. You'll need to explicitly cast your read
results in
ghci as shown here:
ghci> read "5" <interactive>:1:0: Ambiguous type variable `a' in the constraint: `Read a' arising from use of `read' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s) ghci> :t (read "5") (read "5") :: (Read a) => a ghci> (read "5")::Integer 5 ghci> (read "5")::Double 5.0ghci>
read "5"
<interactive>:1:0: Ambiguous type variable `a' in the constraint: `Read a' arising from use of `read' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s)ghci>
:t (read "5")
(read "5") :: (Read a) => aghci>
(read "5")::Integer
5ghci>
(read "5")::Double
5.0
Recall the type of read
:
(Read a) => String -> a
. The
a
here is the type of each instance of Read
.
Which particular parsing function is called depends upon the type
that is expected from the return value of read
. Let's see how that
works:
ghci> (read "5.0")::Double 5.0 ghci> (read "5.0")::Integer *** Exception: Prelude.read: no parseghci>
(read "5.0")::Double
5.0ghci>
(read "5.0")::Integer
*** Exception: Prelude.read: no parse
Notice the error when trying to parse 5.0
as an
Integer. The compiler selected a different parser there because the
return value of read
was expected to be of a different type.
The Read
class provides for some fairly complicated parsers. Most
people, however, choose to use Parsec for complicated parsers these
days. FIXME: insert xref to parsec You can
define a simple parser by providing an implementation for the
readsPrec
function. Your implementation can
return a list containing exactly one tuple on a successful parse, or
an empty list on an unsuccessful parse. Here's an example
implementation:
instance Read Color where -- readsPrec is the main function for parsing input readsPrec _ value = -- We pass tryParse a list of pairs. Each pair has a string -- and the desired return value. tryParse will try to match -- the input to one of these strings. tryParse [("Red", Red), ("Green", Green), ("Blue", Blue)] where tryParse [] = [] -- If there is nothing left to try, fail tryParse ((attempt, result):xs) = -- Compare the start of the string to be parsed to the -- text we are looking for. if (take (length attempt) value) == attempt -- If we have a match, return the result and the -- remaining input then [(result, drop (length attempt) value)] -- If we don't have a match, try the next pair -- in the list of attempts. else tryParse xsinstance Read Color where -- readsPrec is the main function for parsing input readsPrec _ value = -- We pass tryParse a list of pairs. Each pair has a string -- and the desired return value. tryParse will try to match -- the input to one of these strings. tryParse [("Red", Red), ("Green", Green), ("Blue", Blue)] where tryParse [] = [] -- If there is nothing left to try, fail tryParse ((attempt, result):xs) = -- Compare the start of the string to be parsed to the -- text we are looking for. if (take (length attempt) value) == attempt -- If we have a match, return the result and the -- remaining input then [(result, drop (length attempt) value)] -- If we don't have a match, try the next pair -- in the list of attempts. else tryParse xs
This example handles the known cases for the three colors. It
returns an empty list (resulting in a "no parse" message) for others.
The function is supposed to return the part of the input that was not
parsed, so that the system can integrate the parsing of different
types together. Here's an example of using this new instance of
Read
:
ghci> (read "Red")::Color Red ghci> (read "Green")::Color Green ghci> (read "Blue")::Color Blue ghci> (read "[Red]")::[Color] [Red] ghci> (read "[Red,Red,Blue]")::[Color] [Red,Red,Blue] ghci> (read "[Red, Red, Blue]")::[Color] *** Exception: Prelude.read: no parseghci>
(read "Red")::Color
Redghci>
(read "Green")::Color
Greenghci>
(read "Blue")::Color
Blueghci>
(read "[Red]")::[Color]
[Red]ghci>
(read "[Red,Red,Blue]")::[Color]
[Red,Red,Blue]ghci>
(read "[Red, Red, Blue]")::[Color]
*** Exception: Prelude.read: no parse
Notice the error on the final attempt. That's because our parser is not smart enough to handle leading spaces yet. If we modified it to accept leading spaces, that attempt would work.
Often times, you may have a data structure in memory that you need to store on disk for later retrieval or send across the network. The process of converting data in memory to a flat series of bits for storage is called serialization.
It turns out that read
and show
make excellent tools for
serialization. show
produces output that is both human-readable and
machine-readable. It also mostly matches Haskell syntax.
ghci> let d1 = [Just 5, Nothing, Nothing, Just 8, Just 9]::[Maybe Int] ghci> putStrLn (show d1) [Just 5,Nothing,Nothing,Just 8,Just 9] ghci> writeFile "/tmp/test" (show d1)ghci>
let d1 = [Just 5, Nothing, Nothing, Just 8, Just 9]::[Maybe Int]
ghci>
putStrLn (show d1)
[Just 5,Nothing,Nothing,Just 8,Just 9]ghci>
writeFile "/tmp/test" (show d1)
First, we assign d1
to be a list. Next, we print
out the result of show d1
so we can see what it
generates. Then, we write the result of show d1
to a file named /tmp/test
.
ghci> input <- readFile "/tmp/test" "[Just 5,Nothing,Nothing,Just 8,Just 9]" ghci> let d2 = read input <interactive>:1:9: Ambiguous type variable `a' in the constraint: `Read a' arising from use of `read' at <interactive>:1:9-18 Probable fix: add a type signature that fixes these type variable(s) ghci> let d2 = (read input)::[Maybe Int] ghci> print d1 [Just 5,Nothing,Nothing,Just 8,Just 9] ghci> print d2 [Just 5,Nothing,Nothing,Just 8,Just 9] ghci> d1 == d2 Trueghci>
input <- readFile "/tmp/test"
"[Just 5,Nothing,Nothing,Just 8,Just 9]"ghci>
let d2 = read input
<interactive>:1:9: Ambiguous type variable `a' in the constraint: `Read a' arising from use of `read' at <interactive>:1:9-18 Probable fix: add a type signature that fixes these type variable(s)ghci>
let d2 = (read input)::[Maybe Int]
ghci>
print d1
[Just 5,Nothing,Nothing,Just 8,Just 9]ghci>
print d2
[Just 5,Nothing,Nothing,Just 8,Just 9]ghci>
d1 == d2
True
First, we ask Haskell to read the file back.[2] Then,
we try to assign the result of read input
to
d2
. That generates an error. The reason is that
the interpreter doesn't know what type d2
is meant
to be, so it doesn't know how to parse the input. If we give it an
explicit cast, it works, and we can verify that the two sets of data
are equal.
Since so many different types are instances of Read
and Show
by
default (and others can be made instances easily; see the section called “Automatic Derivation”), you can use it for
some really complex data structures. Here are a few examples of
slightly more complex data structures:
ghci> putStrLn $ show [("hi", 1), ("there", 3)] [("hi",1),("there",3)] ghci> putStrLn $ show [[1, 2, 3], [], [4, 0, 1], [], [503]] [[1,2,3],[],[4,0,1],[],[503]] ghci> putStrLn $ show [Left 5, Right "three", Left 0, Right "nine"] [Left 5,Right "three",Left 0,Right "nine"] ghci> putStrLn $ show [Left 0, Right [1, 2, 3], Left 5, Right []] [Left 0,Right [1,2,3],Left 5,Right []]ghci>
putStrLn $ show [("hi", 1), ("there", 3)]
[("hi",1),("there",3)]ghci>
putStrLn $ show [[1, 2, 3], [], [4, 0, 1], [], [503]]
[[1,2,3],[],[4,0,1],[],[503]]ghci>
putStrLn $ show [Left 5, Right "three", Left 0, Right "nine"]
[Left 5,Right "three",Left 0,Right "nine"]ghci>
putStrLn $ show [Left 0, Right [1, 2, 3], Left 5, Right []]
[Left 0,Right [1,2,3],Left 5,Right []]
FIXME: some of these tables don't render well under sgml2x. Will need to verify that they look good under the O'Reilly renderer.
Haskell has a powerful set of numeric types. You can using everyting
from fast 32-bit or 64-bit integers to arbitrary-precision rational
numbers. Yet you probably know that operators such as
+
can work with just about all of these. This
feature is implemented using typeclasses. As a side benefit, it
allows you to define your own numeric types and make them first-class
citizens in Haskell.
Let's begin our discussion of the typeclasses surrounding nmeric types with an examination of the types themselves. Table 6.1, “Selected Numeric Types” describes the most commonly-used numeric types in Haskell. Note that there are also many more numeric types available for specific purposes such as interfacing to C.
Table 6.1. Selected Numeric Types
Type | Description |
---|---|
Double | Double-precision floating point |
Float | Single-precision floating point |
Int | Fixed-precision signed integer; minimum range [-2^29..2^29-1] |
Int16 | 16-bit signed integer |
Int32 | 32-bit signed integer |
Int64 | 64-bit signed integer |
Integer | Arbitrary-precision signed integer; range limited only by machine resources |
Rational | Arbitrary-precision rational numbers. Stored as a
ratio of two Integer s. |
Word | Fixed-precision unsigned integer; storage size same as
Int |
Word16 | 16-bit unsigned integer |
Word32 | 32-bit unsigned integer |
Word64 | 64-bit unsigned integer |
These are quite a few different numeric types. There are some
operations, such as addition, that ought to work with all of them.
There are others, such as asin
, that only apply to
floating-point types. Table 6.2, “Selected Numeric Functions and Constants”
summarizes the different functions that operate on numeric types,
and
Table 6.3, “Typeclass Instances for Numeric Types” matches the types with
their respective typeclasses. As you read that table, keep in mind
that Haskell operators are just functions: you can say either
(+) 2 3
or 2 + 3
with the same
result. By convention, when referring to an operator as a function,
it is written in parenthesis as seen in this table.
FIXME: how to sort the operators?
Table 6.2. Selected Numeric Functions and Constants
Item | Type | Description |
---|---|---|
(+) | Num a => a -> a -> a | Addition |
(-) | Num a => a -> a -> a | Subtraction |
(*) | Num a => a -> a -> a | Multiplication |
(/) | Fractional a => a -> a -> a | Fractional division |
(**) | Floating a => a -> a -> a | Raise to the power of |
(%) | Integral a => a -> a -> Ratio a | Ratio composition |
(.&.) | Bits a => a -> a -> a | Bitwise and |
(.|.) | Bits a => a -> a -> a | Bitwise or |
abs | Num a => a -> a | Absolute value |
approxRational | RealFrac a => a -> a ->
Rational | Approximate rational composition based on fractional numerators and denominators |
cos | Floating a => a -> a | Cosine. Also provided are acos ,
cosh , and acosh , with
the same type. |
div | Integral a => a -> a -> a | Integer division always truncated down; see also
quot |
fromInteger | Num a => Integer -> a | Conversion from an Integer to any numeric type |
fromRational | Fractional a => Rational -> a | Conversional from a Rational . May be lossy. |
log | Floating a => a -> a | Natural logarithm |
logBase | Floating a => a -> a -> a | Log with explicit base |
maxBound | Bounded a => a | The maximum value of a bounded type |
minBound | Bounded a => a | The minimum value of a bounded type |
mod | Integral a => a -> a -> a | Integer modulus |
pi | Floating a => a | Mathematical constant pi |
quot | Integral a => a -> a -> a | Integer division; fractional part of quotient truncated towards zero |
recip | Fractional a => a -> a | Reciprocal |
rem | Integral a => a -> a -> a | Remainder of integer division |
round | (RealFrac a, Integral b) => a -> b | Rounds to nearest integer |
shift | Bits a => a -> Int -> a | Shift left by the specified number of bits, which may be negative for a right shift. |
sin | Floating a => a -> a | Sine. Also provided are asin ,
sinh , and asinh , with
the same type. |
sqrt | Floating a => a -> a | Square root |
tan | Floating a => a -> a | Tangent. Also provided are atan ,
tanh , and atanh , with
the same type. |
toInteger | Integral a => a -> Integer | Convert any Integral to an Integer |
toRational | Real a => a -> Rational | Convert losslessly to Rational |
truncate | (RealFrac a, Integral b) => a -> b | Truncates number towards zero |
xor | Bits a => a -> a -> a | Bitwise exclusive or |
Table 6.3. Typeclass Instances for Numeric Types
Type | Bits | Bounded | Floating | Fractional | Integral | Num | Real | RealFrac |
---|---|---|---|---|---|---|---|---|
Double | X | X | X | X | X | |||
Float | X | X | X | X | X | |||
Int | X | X | X | X | X | |||
Int16 | X | X | X | X | X | |||
Int32 | X | X | X | X | X | |||
Int64 | X | X | X | X | X | |||
Integer | X | X | X | X | ||||
Rational or any Ratio | X | X | X | X | ||||
Word | X | X | X | X | X | |||
Word16 | X | X | X | X | X | |||
Word32 | X | X | X | X | X | |||
Word64 | X | X | X | X | X |
One other question regarding Haskell's numeric types is conversion between them. Table 6.2, “Selected Numeric Functions and Constants” listed many functions that can be used for conversion. However, it is not always obvious how to apply them to convert between two arbitrary types. To help you out, Table 6.4, “Conversion Between Numeric Types” provides information on converting between different types.
Table 6.4. Conversion Between Numeric Types
Source Type | Destination Type | |||
---|---|---|---|---|
Double , Float | Int s, Word s | Integer | Rational | |
Double , Float | fromRational . toRational | truncate | truncate | toRational |
Int s, Word s | fromIntegral | fromIntegral | fromIntegral or
toInteger | fromIntegral |
Integer | fromIntegral | fromIntegral | N/A | fromIntegral |
Rational | fromRational | truncate | truncate | N/A |
We've already talked about the arithmetic operators such as
+
that can be used for all sorts of different
numbers. But there are some even more widely-applied operators in
Haskell. The most obvious, of course, are the equality tests:
==
and /=
. Any type that can
be evaluated for equality is a member of Eq
, which defines those
operators.
There are also comparison operators such as >=
and
<=
. These are defined by the Ord
typeclass.
These are in a separate typeclass because there are some types, such
as Handle
, where an equality test makes sense, but there is no way
to express a particular ordering. Anything that is an instance of
Ord
can be sorted by Data.List.sort
.
Virtually all Haskell types are instances of Eq
, and almost as many
are instances of Ord
.
For many simple data types, the Haskell compiler can automatically
derive instances of Read
, Show
, Bounded
, Eq
, and Ord
for you.
This saves you the effort of having to manually write parsers and
display code for each type. Here's an example:
data Color = Red | Green | Blue deriving (Read, Show, Eq, Ord)data Color = Red | Green | Blue deriving (Read, Show, Eq, Ord)
Let's take a look at how these derived instances work for us:
ghci> show Red "Red" ghci> (read "Red")::Color Red ghci> (read "[Red,Red,Blue]")::[Color] [Red,Red,Blue] ghci> (read "[Red, Red, Blue]")::[Color] [Red,Red,Blue] ghci> Red == Red True ghci> Red == Blue False ghci> Data.List.sort [Blue,Green,Blue,Red] [Red,Green,Blue,Blue] ghci> Red < Blue Trueghci>
show Red
"Red"ghci>
(read "Red")::Color
Redghci>
(read "[Red,Red,Blue]")::[Color]
[Red,Red,Blue]ghci>
(read "[Red, Red, Blue]")::[Color]
[Red,Red,Blue]ghci>
Red == Red
Trueghci>
Red == Blue
Falseghci>
Data.List.sort [Blue,Green,Blue,Red]
[Red,Green,Blue,Blue]ghci>
Red < Blue
True
Notice that the derived instance of Read
actually works better than
our hand-written version did: it successfully parsed a list with
embedded whitespace.
Automatic derivation is not always possible. For instance, if you
defined a type Data MyType = MyType (Int -> Bool)
,
the compiler will not be able to derive an instance of Show
because
it doesn't know how to render a function. You will get a compilation
error in such a situation.
[1] We provided a default implementation of both functions, which gives implementators of instances choice: they can pick which one they implement. We could have provided a default for only one function, which would have forced users to implement the other every time.
[2] As you will see in FIXME: insert ref, Haskell doesn't actually read the entire file at this point. But for the purposes of this example, we can ignore that distinction.