Concept:

Sum monoid

Headline

A monoid leveraging addition for the associative operation

Illustration

Number types may be completed into monoids in different ways. The sum monoid favors addition for the associative operation of the monoid. We illustrate the sum monoid in Language:Haskell on the grounds of the type class Monoid with the first two members needed for a minimal complete definition:

-- The type class Monoid
class Monoid a
  where
    mempty :: a -- neutral element
    mappend :: a -> a -> a -- associative operation
    mconcat :: [a] -> a -- fold
    mconcat = foldr mappend mempty

The sum monoid relies on a designated type which essentially wraps a number type:

-- The type of the sum monoid
newtype Sum a = Sum { getSum :: a }

Here is the type-class instance for the sum monoid:

-- The Monoid instance for numbers under addition
instance Num a => Monoid (Sum a)
  where
    mempty = Sum 0
    x `mappend` y = Sum (getSum x + getSum y)

For further illustration, we can reconstruct the standard sum function in a monoidal way. To this end, we first review the normal definition in terms of foldr:

-- A foldr-based definition of sum
sum' :: Num a => [a] -> a
sum' = foldr (+) 0

-- A monoidal definition of sum
sum'' :: Num a => [a] -> a
sum'' = getSum . mconcat . map Sum


Concept:

Monoid

Headline

A type with an associative operation and a neutral element

Illustration

The notion of monoid is precisely defined in group theory, but we focus here on its illustration in a programming setting. Specifically, in functional programming, a monoid is essentially a type with an associative operation and a neutral element. For instance, lists form a monoid with the empty list as neutral element and list append as the associative operation. Monoids are useful, for example, in aggregating results.

In Language:Haskell, monoids are modeled through the type class Monoid with first two members needed for a minimal complete definition:

-- The type class Monoid
class Monoid a
  where
    mempty :: a -- neutral element
    mappend :: a -> a -> a -- associative operation
    mconcat :: [a] -> a -- fold
    mconcat = foldr mappend mempty

Algebraically, the following properties are required for any monoid (given in Haskell notation):

mempty `mappend` x = x -- left unit
x `mappend` mempty = x -- right unit
x `mappend` (y `mappend` z) = (x `mappend` y) `mappend` z -- associativity

See the following monoids for continued illustration:


Language:

Haskell

Headline

The functional programming language Haskell

Details

101wiki hosts plenty of Haskell-based contributions. This is evident from corresponding back-links. More selective sets of Haskell-based contributions are organized in themes: Theme:Haskell data, Theme:Haskell potpourri, and Theme:Haskell genericity. Haskell is also the language of choice for a course supported by 101wiki: Course:Lambdas_in_Koblenz.

Illustration

The following expression takes the first 42 elements of the infinite list of natural numbers:

> take 42 [0..]
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41]

In this example, we leverage Haskell's lazy evaluation.


Concept:

Type class

Headline

An abstraction mechanism for bounded polymorphism

Illustration

Type classes are not to be confused with OO classes. In fact, type classes may be somewhat compared with OO interfaces. Type classes have been popularized by Haskell. Similar constructs exist in a few other languages. Type classes capture operations that may be defined for many types. The operations can be defined differently for each type, i.e., for each instance of a type class.

All subsequent illustrations leverage Haskell. Let us consider the following datatypes of bits and bitstreams which represent unsigned binary numbers. We are going to enrich these datatypes with some functionality eventually, with the help of type classes:

-- A bit can be zero or one
data Bit = Zero | One

-- Bit streams of any length
newtype Bits = Bits { getBits :: [Bit] }

Thus, the binary number "101" would be represented as follows:

Bits [One,Zero,One]

Now suppose that we want to define some standard operations for bits and bitstreams: equality, total order, unparsing to text, parsing from text, and possibly others. Let us begin with unparsing (conversion) to text. To this end, we should implement Haskell's type-class-polymorphic function show so that it produces text like this:

> show (Bits [One,Zero,One])
"101"

Here is the type class Show which declares indeed the polymorphic show function:

class Show a
  where
    show :: a -> String

In reality, the type class has not just one member, show, as shown, but we omit the discussion of the other members here for brevity. The type class is parameterized in a type a for the actual type for which to implement the members. Here are the type-class instances for bits and bit streams:

-- Show bits
instance Show Bit 
  where
    show Zero = "0"
    show One = "1"

-- Show bit streams
instance Show Bits
  where
    show = concat . map show . getBits

Thus, the instance fills the position of the type parameter with an actual type such as Bit and Bits. Also, the member function show is actually defined, while assuming the specific type. We show a bit as either "0" or "1". We show a bit stream by showing all the individual bits and concatenating the results.

The inverse of show is read. There is also a corresponding type class Read, which we skip here for brevity. Let us consider equality instead. There is again a type class which captures the potential of equality for many types:

class Eq a
  where 
    (==) :: a -> a -> Bool

The member "(==)" is the infix operation for testing two bit streams to be equal. Arguably, bit streams are equal, if they are of the same length and they agree on each other bit by bit. In fact, the following definition is a bit more general in that it also trims away preceding zero bits:

-- Test bits for equality
instance Eq Bit
  where
    Zero == Zero = True
    Zero == One = False
    One == One = True
    One == Zero = False

-- Test bit streams for equality
instance Eq Bits
  where
    x == y =  length x' == length y'
           && and (map (uncurry (==)) (zip x' y'))
      where
        x' = trim (getBits x)
        y' = trim (getBits y)
        trim [] = []
        trim z@(One: ) = z
        trim (Zero:z) = trim z

For instance:

-- Test bit streams for equality
> let b101 = read "101" :: Bits
> let b0101 = read "0101" :: Bits
> let b1101 = read "1101" :: Bits
> b101 == b0101
True
> b101 == b1101
False

Actually, bit streams are (unsigned) binary numbers. Thus, we should also instantiate the corresponding type classes for number types. Operations on number types are grouped in multiple type classes. The type class Num deals with addition, subtraction, multiplication, and a few other operations, but notably no division:

class (Eq a, Show a) => Num a
  where
    (+) :: a -> a -> a
    (*) :: a -> a -> a
    (-) :: a -> a -> a
    negate :: a -> a
    abs :: a -> a
    signum :: a -> a
    fromInteger :: Integer -> a

We would like to instantiate the Num type class for bit streams. There are different ways of doing this. For instance, we could define addition by bitwise addition, right at the level of bit streams, or we could instead resort to existing number types. For simplicity, we do indeed conversions from and to Integer, in fact, any integral type:

-- Convert bits to an integer
bits2integral :: Integral a => Bits -> a
bits2integral = foldl f 0 . getBits 
  where
    f a b = a * 2 + (bit2int b)
    bit2int Zero = 0
    bit2int One = 1

-- Convert a (non-negative) integral to bits
integral2bits :: Integral a => a -> Bits
integral2bits i | i < 0 = error "Bits are unsigned"
integral2bits i = Bits (f [] i)
  where
    f xs 0 = xs
    f xs i = f (x:xs) (i `div` 2) 
      where
        x = if odd i then One else Zero

On these grounds, we can trivially instantiate the Num type class for Bits by simply reusing the existing instance for Integer through systematic conversions.

-- Bits as a Num type
instance Num Bits
  where
    x + y = integral2bits z'
      where
        x' = bits2integral x
        y' = bits2integral y
        z' = x' + y'
    x * y = integral2bits z'
      where
        x' = bits2integral x
        y' = bits2integral y
        z' = x' * y'
    x - y = integral2bits z'
      where
        x' = bits2integral x
        y' = bits2integral y
        z' = x' - y'
    abs = id
    signum = integral2bits
           . signum
           . bits2integral
    fromInteger = integral2bits

The examples given so far are concerned with predefined type classes. However, type classes can also be declared by programmers in their projects. Let's assume that we may need to convert data from different formats into ``Ints. Here is a corresponding type class with a few instances:

class ToInt a
  where
    toInt :: a -> Maybe Int

instance ToInt Int
  where
    toInt = Just

instance ToInt Float
  where
    toInt = Just . round

instance ToInt String
  where
    toInt s =
      case reads s of
        [(i, "")] -> Just i
        _ -> Nothing

The conversion can be illustrated like this:

*Main> toInt "5"
Just 5
*Main> toInt "foo"
Nothing
*Main> toInt (5::Int)
Just 5
*Main> toInt (5.5::Float)
Just 6

In Haskell, type-class parameters are not limited to types, but, in fact, type classes may be parameterized in type constructors. Consider the following type class which models different notions of size for container types:

-- Notions of size for container types
class Size f
  where
    -- Number of constructors
    consSize :: f a -> Int
    -- Number of elements
    elemSize :: f a -> Int

Here is a straightforward instance for lists:

instance Size []
  where
    consSize = (+1) . length
    elemSize = length

Let's also consider sizes for rose trees:

-- Node-labeled rose trees
data NLTree a = NLTree a [NLTree a]
  deriving (Eq, Show, Read)

instance Size NLTree
  where
    consSize (NLTree _ ts) =
        1
      + consSize ts
      + sum (map consSize ts)
    elemSize (NLTree _ ts) =
        1
      + sum (map elemSize ts)

-- Leaf-labeled rose trees
data LLTree a = Leaf a | Fork [LLTree a]
  deriving (Eq, Show, Read)

instance Size LLTree
  where
    consSize (Leaf _) = 1
    consSize (Fork ts) =
        consSize ts
      + sum (map consSize ts)
    elemSize (Leaf _) = 1
    elemSize (Fork ts) =
      sum (map elemSize ts)

A few illustrations are due:

*Main> let list = [1,2,3]
*Main> let nltree = NLTree 1 [NLTree 2 [], NLTree 3 []]
*Main> let lltree = Fork [Leaf 1, Fork [Leaf 2, Leaf 3]]
*Main> consSize list
4
*Main> elemSize list
3
*Main> consSize nltree 
8
*Main> elemSize nltree 
3
*Main> consSize lltree 
9
*Main> elemSize lltree 
3


Concept:

Type-class instance

Headline

Type-specific function definitions for a type class

Illustration

See the concept of type classes for an illustration.