undefined
.
Eventually, the complete
version will be made available.
In class exercise: Semigroup, Monoid and Foldable
> {-# LANGUAGE DeriveFunctor #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# OPTIONS_GHC -fdefer-type-errors #-}
> import Prelude hiding (all,any, and, or)
> import Data.Foldable hiding (and, or, any, all)
> import Data.Monoid hiding (All, getAll, Any, getAny)
> import Test.HUnit
Monoids
First, read just the 'Semigroups and Monoids' section of HW 03's SortedList module.
Note that this section defines the following function that tailors a fold operation to a specific instance of the Monoid
class.
For example, because the String
type is an instance of this class (using ++
for mappend
) we can reduce
a list of String
s to a single string.
The assignment shows you that numbers can instantiate this class in multiple ways. Like numbers, Booleans
can be made an instance of the Monoid
class in two different ways.
> newtype And = And { getAnd :: Bool } deriving (Eq,Show)
> newtype Or = Or { getOr :: Bool } deriving (Eq,Show)
Make sure that you understand these type definitions. We are defining a type And
with single data constructor (also called And
). The argument of this data constructor is a record with a single field, called getAnd
. What this means is that And
and getAnd
allow us to convert Bool
s to And
and back.
λ> :t And
And :: Bool -> And
λ> :t getAnd
getAnd :: And -> Bool
Above, newtype
is like data, but is restricted to a single variant. It is typically used to create a new name for an existing type. This new name allows us to have multiple instances for the same type (as below) or to provide type abstraction (like SortedList
in the HW).
Your job is to complete these instances that can tell us whether any of the booleans in a list are true, or whether all of the booleans in a list are true. (See two test cases below for an example of the behavior.)
Because And
and Or
wrap boolean values, we can be sure that our instances have the right properties by testing the truth tables. (There are more concise to write these tests, but we haven't covered them yet.)
> monoidAnd :: Test
> monoidAnd = TestList [
> And False <> (And False <> And False) ~?= (And False <> And False) <> And False,
> And False <> (And False <> And True) ~?= (And False <> And False) <> And True,
> And False <> (And True <> And False) ~?= (And False <> And True) <> And False,
> And False <> (And True <> And True) ~?= (And False <> And True) <> And True,
> And True <> (And False <> And False) ~?= (And True <> And False) <> And False,
> And True <> (And False <> And True) ~?= (And True <> And False) <> And True,
> And True <> (And True <> And False) ~?= (And True <> And True) <> And False,
> And True <> (And True <> And True) ~?= (And True <> And True) <> And True,
> And True <> mempty ~?= And True,
> And False <> mempty ~?= And False,
> mempty <> And True ~?= And True,
> mempty <> And False ~?= And False ]
> monoidOr :: Test
> monoidOr = TestList [
> Or False <> (Or False <> Or False) ~?= (Or False <> Or False) <> Or False,
> Or False <> (Or False <> Or True) ~?= (Or False <> Or False) <> Or True,
> Or False <> (Or True <> Or False) ~?= (Or False <> Or True) <> Or False,
> Or False <> (Or True <> Or True) ~?= (Or False <> Or True) <> Or True,
> Or True <> (Or False <> Or False) ~?= (Or True <> Or False) <> Or False,
> Or True <> (Or False <> Or True) ~?= (Or True <> Or False) <> Or True,
> Or True <> (Or True <> Or False) ~?= (Or True <> Or True) <> Or False,
> Or True <> (Or True <> Or True) ~?= (Or True <> Or True) <> Or True,
> Or True <> mempty ~?= Or True,
> Or False <> mempty ~?= Or False,
> mempty <> Or True ~?= Or True,
> mempty <> Or False ~?= Or False ]
Foldable
Now, read the section marked The Foldable Typeclass
in the MergeSort module.
We can use your Monoid instances for Or
and And
to generalize operations to any data structure.
For example, we can generalize the and
operation to any Foldable data structure using foldMap
.
Your job is to define these three related operations
so that the following tests pass
Application
Recall our familiar Tree
type. Haskell can derive the Functor
instance for this type so we ask it to do so.
And here is an example Tree
.
> t1 :: Tree String
> t1 = Branch "d" (Branch "b" (l "a" ) (l "c")) (Branch "f" (l "e") (l "g")) where
> l x = Branch x Empty Empty
We could make this type an instance of Foldable
using the definition of foldrTree
from hw02.
But, for practice, complete the instance using foldMap
.
With this instance, we can for example, verify that all of the sample strings above have length 1.
Finally, look at the documentation for the Foldable class and find some other tree operations that we get automatically for free.