Difference between revisions of "Type"

From HaskellWiki
Jump to navigation Jump to search
m (Moving "See Also" to end.)
m (Haskell formatting)
Line 13: Line 13:
 
which probably explains nothing if you don't already know Haskell!
 
which probably explains nothing if you don't already know Haskell!
   
The essence of the above statement is that you use the keyword <code>data</code>,
+
The essence of the above statement is that you use the keyword <hask>data</hask>,
 
supply an optional context, give the type name and a variable number of
 
supply an optional context, give the type name and a variable number of
 
[[type variable]]s. This is then followed by a variable number of [[constructor]]s, each of which has a list of [[type variable]]s or [[type constant]]s. At the end, there is an optional <code>deriving</code>.
 
[[type variable]]s. This is then followed by a variable number of [[constructor]]s, each of which has a list of [[type variable]]s or [[type constant]]s. At the end, there is an optional <code>deriving</code>.
Line 23: Line 23:
   
 
Let's look at some examples. The Haskell standard data type [[Maybe]] is typically declared as:
 
Let's look at some examples. The Haskell standard data type [[Maybe]] is typically declared as:
  +
<haskell>
 
data Maybe a = Just a | Nothing
 
data Maybe a = Just a | Nothing
  +
</haskell>
 
 
What this means is that the type '''Maybe''' has one type variable, represented by the ''a'' and two [[constructor]]s '''Just''' and '''Nothing'''. (Note that Haskell requires type names and constructor names to begin with an uppercase letter). The '''Just''' constructor takes one parameter, ''a''.
 
What this means is that the type '''Maybe''' has one type variable, represented by the ''a'' and two [[constructor]]s '''Just''' and '''Nothing'''. (Note that Haskell requires type names and constructor names to begin with an uppercase letter). The '''Just''' constructor takes one parameter, ''a''.
   
 
As another example, consider binary [[Tree]]s. They could be represented by:
 
As another example, consider binary [[Tree]]s. They could be represented by:
  +
<haskell>
 
data Tree a = Branch (Tree a) (Tree a) | Leaf a
 
data Tree a = Branch (Tree a) (Tree a) | Leaf a
  +
</haskell>
 
 
Here, one of the constructors, '''Branch''' of '''Tree''' takes two trees as
 
Here, one of the constructors, '''Branch''' of '''Tree''' takes two trees as
 
parameters to the constructor, while '''Leaf''' takes the type variable ''a''. This type of recursion is a very common [[:Category:Idioms |pattern]] in Haskell.
 
parameters to the constructor, while '''Leaf''' takes the type variable ''a''. This type of recursion is a very common [[:Category:Idioms |pattern]] in Haskell.
Line 36: Line 38:
   
 
The other two ways one may introduce types to Haskell programs are via the
 
The other two ways one may introduce types to Haskell programs are via the
<code>type</code> and <code>newtype</code> statements.
+
<hask>type</hask> and <hask>newtype</hask> statements.
   
<code>type</code> introduces a synonym for a type and uses the same data
+
<hask>type</hask> introduces a synonym for a type and uses the same data
constructors. <code>newtype</code> introduces a renaming of a type and
+
constructors. <hask>newtype</hask> introduces a renaming of a type and
 
requires you to provide new constructors.
 
requires you to provide new constructors.
   
When using a <code>type</code> declaration, the type synonym and its base type
+
When using a <hask>type</hask> declaration, the type synonym and its base type
 
are interchangeble almost everywhere (There are some restrictions when dealing with [[instance]] declarations). For example, if you had the declaration:
 
are interchangeble almost everywhere (There are some restrictions when dealing with [[instance]] declarations). For example, if you had the declaration:
  +
<haskell>
 
 
type Name = String
 
type Name = String
  +
</haskell>
 
then any [[function]] you had declared that had <code>String</code> in its
+
then any [[function]] you had declared that had <hask>String</hask> in its
 
signature could be used on any element of type <code>Name</code>
 
signature could be used on any element of type <code>Name</code>
   
 
However, if one had the declaration:
 
However, if one had the declaration:
  +
<haskell>
 
 
newtype FirstName = FirstName String
 
newtype FirstName = FirstName String
  +
</haskell>
 
 
this would no longer be the case. Functions would have to be declared that
 
this would no longer be the case. Functions would have to be declared that
 
actually were defined on '''FirstName'''. Often, one creates a deconstructor
 
actually were defined on '''FirstName'''. Often, one creates a deconstructor
 
at the same time which helps alleviate this requirement. e.g.:
 
at the same time which helps alleviate this requirement. e.g.:
  +
<haskell>
 
 
unFirstName :: FirstName -> String
 
unFirstName :: FirstName -> String
 
unFirstName (FirstName s) = s
 
unFirstName (FirstName s) = s
  +
</haskell>
 
 
This is often done by the use of [[field]]s in the <code>newtype</code>. (Note
 
This is often done by the use of [[field]]s in the <code>newtype</code>. (Note
 
that many consider the Haskell field implementation sub-optimal, while
 
that many consider the Haskell field implementation sub-optimal, while
Line 70: Line 72:
   
 
First, create data types for the suit and card number.
 
First, create data types for the suit and card number.
  +
<haskell>
 
 
data Suit = Club | Diamond | Heart | Spade
 
data Suit = Club | Diamond | Heart | Spade
 
deriving (Read, Show, Enum, Eq, Ord)
 
deriving (Read, Show, Enum, Eq, Ord)
Line 78: Line 80:
 
| Jack | Queen | King | Ace
 
| Jack | Queen | King | Ace
 
deriving (Read, Show, Enum, Eq, Ord)
 
deriving (Read, Show, Enum, Eq, Ord)
  +
</haskell>
 
Each of these uses a [[deriving]] clause to allow us to convert them from / to [[String]] and Int, test the for equality and ordering. With types like this,
+
Each of these uses a [[deriving]] clause to allow us to convert them from / to [[String]] and Int, test them for equality and ordering. With types like this,
 
where there are no [[type variable]]s, equality is based upon which constructor is used and order by the order you wrote them. e.g. <code>Three</code> is less than <code>Queen</code>.
 
where there are no [[type variable]]s, equality is based upon which constructor is used and order by the order you wrote them. e.g. <code>Three</code> is less than <code>Queen</code>.
   
 
Now we define an actual <code>Card</code>
 
Now we define an actual <code>Card</code>
  +
<haskell>
 
 
data Card = Card {value::CardValue,
 
data Card = Card {value::CardValue,
 
suit::Suit}
 
suit::Suit}
 
deriving (Read, Show, Eq)
 
deriving (Read, Show, Eq)
  +
</haskell>
 
 
In this definition, we use [[field]]s, which give us ready made functions to
 
In this definition, we use [[field]]s, which give us ready made functions to
 
access the two parts of a <code>Card</code>. Again, [[type variables]] were not
 
access the two parts of a <code>Card</code>. Again, [[type variables]] were not
Line 94: Line 96:
   
 
The deriving clause here only specifies three of our desired [[Class]]es, we supply [[instance]] declarations for [[Ord]] and [[Enum]].
 
The deriving clause here only specifies three of our desired [[Class]]es, we supply [[instance]] declarations for [[Ord]] and [[Enum]].
  +
<haskell>
 
 
instance Ord Card where
 
instance Ord Card where
 
compare c1 c2 | (value c1 == (value c2)) = compare (suit c1) (suit c2)
 
compare c1 c2 | (value c1 == (value c2)) = compare (suit c1) (suit c2)
Line 102: Line 104:
 
toEnum n = Card (toEnum (n `div` 4)) (toEnum (n `mod` 4))
 
toEnum n = Card (toEnum (n `div` 4)) (toEnum (n `mod` 4))
 
fromEnum c = 4*(fromEnum (value c)) + (fromEnum (suit c))
 
fromEnum c = 4*(fromEnum (value c)) + (fromEnum (suit c))
  +
</haskell>
 
 
Finally, we alias the type <code>Deck</code> to a list of <code>Card</code>s
 
Finally, we alias the type <code>Deck</code> to a list of <code>Card</code>s
 
and populate the deck with a [[list comprehension]]
 
and populate the deck with a [[list comprehension]]
  +
<haskell>
 
 
type Deck = [Card]
 
type Deck = [Card]
   
 
deck::Deck
 
deck::Deck
 
deck = [Card val su | val <- [Two .. Ace], su <- [Club .. Spade]]
 
deck = [Card val su | val <- [Two .. Ace], su <- [Club .. Spade]]
  +
</haskell>
 
   
 
==Please add==
 
==Please add==

Revision as of 01:46, 9 March 2006

In Haskell, types are how you describe the data your program will work with.

Data declarations

One introduces, or declares, at type in Haskell via the data statement. In general a data declaration looks like:

data [context =>] type tv1 ... tvi = con1  c1t1 c1c2... c1tn |
                      ... | conm cmt1 ... cmtq
                    [deriving]

which probably explains nothing if you don't already know Haskell!

The essence of the above statement is that you use the keyword data, supply an optional context, give the type name and a variable number of type variables. This is then followed by a variable number of constructors, each of which has a list of type variables or type constants. At the end, there is an optional deriving.

There are a number of other subtelties associated with this, such as requiring parameters to the data constructors to be eager, what classes are allowed in the deriving, use of field names in the constructors and what the context actually does. Please refer to the specific articles for more on each of those.

Let's look at some examples. The Haskell standard data type Maybe is typically declared as:

 data Maybe a = Just a | Nothing

What this means is that the type Maybe has one type variable, represented by the a and two constructors Just and Nothing. (Note that Haskell requires type names and constructor names to begin with an uppercase letter). The Just constructor takes one parameter, a.

As another example, consider binary Trees. They could be represented by:

 data Tree a = Branch (Tree a) (Tree a) | Leaf a

Here, one of the constructors, Branch of Tree takes two trees as parameters to the constructor, while Leaf takes the type variable a. This type of recursion is a very common pattern in Haskell.

Type and newtype

The other two ways one may introduce types to Haskell programs are via the type and newtype statements.

type introduces a synonym for a type and uses the same data constructors. newtype introduces a renaming of a type and requires you to provide new constructors.

When using a type declaration, the type synonym and its base type are interchangeble almost everywhere (There are some restrictions when dealing with instance declarations). For example, if you had the declaration:

 type Name = String

then any function you had declared that had String in its signature could be used on any element of type Name

However, if one had the declaration:

 
  newtype FirstName = FirstName String

this would no longer be the case. Functions would have to be declared that actually were defined on FirstName. Often, one creates a deconstructor at the same time which helps alleviate this requirement. e.g.:

  unFirstName :: FirstName -> String
  unFirstName (FirstName s) = s

This is often done by the use of fields in the newtype. (Note that many consider the Haskell field implementation sub-optimal, while others use it extensively. See Programming guidelines and Future)

A simple example

Suppose you want to create a program to play bridge. You need something to represent cards. Here is one way to do that.

First, create data types for the suit and card number.

 data Suit = Club | Diamond | Heart | Spade
     deriving (Read, Show, Enum, Eq, Ord)

 data CardValue = Two | Three | Four
     | Five | Six | Seven | Eight | Nine | Ten 
     | Jack | Queen | King | Ace
    deriving (Read,  Show, Enum, Eq, Ord)

Each of these uses a deriving clause to allow us to convert them from / to String and Int, test them for equality and ordering. With types like this, where there are no type variables, equality is based upon which constructor is used and order by the order you wrote them. e.g. Three is less than Queen.

Now we define an actual Card

 
 data Card = Card {value::CardValue, 
                    suit::Suit}
    deriving (Read, Show, Eq)

In this definition, we use fields, which give us ready made functions to access the two parts of a Card. Again, type variables were not used, but the data constructor requires its two parameters to be of specific types, CardValue and Suit.

The deriving clause here only specifies three of our desired Classes, we supply instance declarations for Ord and Enum.

 instance Ord Card where
      compare c1 c2  | (value c1 == (value c2)) = compare (suit c1) (suit c2)
                     | otherwise = compare (value c1) (value c2)

 instance Enum Card where
      toEnum n = Card (toEnum (n `div` 4)) (toEnum (n `mod` 4))
      fromEnum c =  4*(fromEnum (value c)) + (fromEnum (suit c))

Finally, we alias the type Deck to a list of Cards and populate the deck with a list comprehension

 type Deck = [Card]

 deck::Deck
 deck = [Card val su | val <- [Two .. Ace], su <- [Club .. Spade]]

Please add

Further illustrative examples would be most appreciated.

See Also

Read the (wanted) articles about data constructors and classes. As well the Haskell 98 report and your chosen implementation (e.g. GHC/Documentation) have the latest words.