In class exercise: Semigroup, Monoid and Foldable
> module MonoidFoldable where
> -- https://www.seas.upenn.edu/~cis5520/current/lectures/stub/04-classes/MonoidFoldable.html> import Prelude hiding (all, any, and, or)
> import qualified Data.List as List
> import Test.HUnitMonoids
First, make sure that you have read the 'Semigroups and Monoids' section of HW 02's SortedList module.
Note that this section defines the following function that tailors a fold
operation to a specific instance of the Monoid class.
> foldList :: Monoid b => [b] -> b
> foldList = List.foldr (<>) memptyFor example, because the String type is an instance of this class
(using ++ for mappend) we can foldList a list of Strings to
a single string.
> -- >>> foldList ["C", "I", "S", "5", "5", "2" ]
> -- "CIS552"Having instances of the Monoid type class available makes the foldList function
more powerful because we can use it with more types. The result type b above
must be an instance of this class. For the String type, that is good news!
There is really only way to make the String type an instance of the
Monoid type class. As a result, Haskell includes this type class instance in
the Prelude---it is available in any module and foldList above just works with
Strings.
However, for some types, there are multiple but equally reasonable instances of
the Monoid class.
The homework assignment shows you that numbers can instantiate this class in multiple
ways. We have 0 as an identity element for the associative operator + and 1 as an
identity element for the associative operator *. The assignment resolves this tension
by introducing two new types.
Like numbers, Booleans can also be made an instance of the Monoid class
in two different ways. So for practice, we will do the same thing here.
First, we define two newtype -- i.e. wrappers for the Bool type.
> newtype And = MkAnd { getAnd :: Bool } deriving (Eq,Show)
> newtype Or = MkOr { getOr :: Bool } deriving (Eq,Show)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).
Make sure that you understand these 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 Bools to And and
back.
> -- >>> :t MkAnd
> -- MkAnd :: Bool -> And> -- >>> :t getAnd
> -- getAnd :: And -> BoolYour 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.)
> -- >>> getOr (foldList (fmap MkOr [True, False, True]))
> -- True> -- >>> getAnd (foldList (fmap MkAnd [True, False, True]))
> -- False> instance Semigroup And where
> (<>) :: And -> And -> And
> (<>) = \x y -> MkAnd (getAnd x && getAnd y) > instance Monoid And where
> mempty :: And
> mempty = MkAnd True > instance Semigroup Or where
> (<>) :: Or -> Or -> Or
> (<>) = \x y -> MkOr (getOr x || getOr y) > instance Monoid Or where
> mempty :: Or
> mempty = MkOr False 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 [
> MkAnd False <> (MkAnd False <> MkAnd False) ~?= (MkAnd False <> MkAnd False) <> MkAnd False,
> MkAnd False <> (MkAnd False <> MkAnd True) ~?= (MkAnd False <> MkAnd False) <> MkAnd True,
> MkAnd False <> (MkAnd True <> MkAnd False) ~?= (MkAnd False <> MkAnd True) <> MkAnd False,
> MkAnd False <> (MkAnd True <> MkAnd True) ~?= (MkAnd False <> MkAnd True) <> MkAnd True,
> MkAnd True <> (MkAnd False <> MkAnd False) ~?= (MkAnd True <> MkAnd False) <> MkAnd False,
> MkAnd True <> (MkAnd False <> MkAnd True) ~?= (MkAnd True <> MkAnd False) <> MkAnd True,
> MkAnd True <> (MkAnd True <> MkAnd False) ~?= (MkAnd True <> MkAnd True) <> MkAnd False,
> MkAnd True <> (MkAnd True <> MkAnd True) ~?= (MkAnd True <> MkAnd True) <> MkAnd True,
> MkAnd True <> mempty ~?= MkAnd True,
> MkAnd False <> mempty ~?= MkAnd False,
> mempty <> MkAnd True ~?= MkAnd True,
> mempty <> MkAnd False ~?= MkAnd False ]> monoidOr :: Test
> monoidOr = TestList [
> MkOr False <> (MkOr False <> MkOr False) ~?= (MkOr False <> MkOr False) <> MkOr False,
> MkOr False <> (MkOr False <> MkOr True) ~?= (MkOr False <> MkOr False) <> MkOr True,
> MkOr False <> (MkOr True <> MkOr False) ~?= (MkOr False <> MkOr True) <> MkOr False,
> MkOr False <> (MkOr True <> MkOr True) ~?= (MkOr False <> MkOr True) <> MkOr True,
> MkOr True <> (MkOr False <> MkOr False) ~?= (MkOr True <> MkOr False) <> MkOr False,
> MkOr True <> (MkOr False <> MkOr True) ~?= (MkOr True <> MkOr False) <> MkOr True,
> MkOr True <> (MkOr True <> MkOr False) ~?= (MkOr True <> MkOr True) <> MkOr False,
> MkOr True <> (MkOr True <> MkOr True) ~?= (MkOr True <> MkOr True) <> MkOr True,
> MkOr True <> mempty ~?= MkOr True,
> MkOr False <> mempty ~?= MkOr False,
> mempty <> MkOr True ~?= MkOr True,
> mempty <> MkOr False ~?= MkOr False ]Foldable
Now, make sure that you have 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 that is in the Foldable type class.
The Foldable type class requires an implementation of the foldMap
operation. This operation takes a function that can convert any element
in the data structure to a Monoid type, and then uses the Monoid operations
to combine all of the elements together.
> -- >>> :t foldMap
> -- foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> mFor example, the definition of foldMap for the list type looks
something like this.
foldMap :: (Monoid m) => (a -> m) -> [a] -> m
foldMap f l = case l of
[] -> mempty -- use identity element
x:xs -> f x <> foldMap f xs -- use combining functionUsing foldMap we can compute whether all of the booleans stored in a data structure are True
> -- >>> and [True,True,False]
> -- False> and :: Foldable t => t Bool -> Bool
> and x = getAnd (foldMap MkAnd x)Your job is to define these three related operations
> or :: Foldable t => t Bool -> Bool
> or = getOr . foldMap MkOr > all :: Foldable t => (a -> Bool) -> t a -> Bool
> all f = getAnd . foldMap (MkAnd . f)> any :: Foldable t => (a -> Bool) -> t a -> Bool
> any f = getOr . foldMap (MkOr . f)so that the following tests pass
> -- >>> or [True, False, False, True]
> -- True> -- >>> all (>0) [1::Int,2,4,18]
> -- True> -- >>> all (>0) [1::Int,-2,4,18]
> -- False> -- >>> any (>0) [1::Int,2,4,18]
> -- True> -- >>> any (>0) [-1::Int,-2,-4,-18]
> -- FalseTrees are Foldable
Recall our familiar Tree type. Haskell can derive the Functor instance for this type so we ask it to do so.
> data Tree a = Empty | Branch a (Tree a) (Tree a) deriving (Eq)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 EmptyWe could make this type an instance of Foldable using the definition of
foldrTree from the TreeFolds module.
But, for practice, complete the instance using foldMap.
> instance Foldable Tree where
> foldMap :: (Monoid m) => (a -> m) -> Tree a -> m
>
> foldMap _f Empty = mempty
> foldMap f (Branch k l r) = foldMap f l <> f k <> foldMap f r
> With this instance, we can for example, verify that all of the sample strings above have length 1.
> -- >>> all (\x -> length x == 1) t1
> -- TrueFinally, look at the documentation for the Foldable class and find some other tree operations that we get automatically for free.
> -- >>> :info FoldableOblig-main
> main :: IO ()
> main = do
> _ <- runTestTT $ TestList [monoidAnd, monoidOr]
> return ()
CIS 5520: Advanced Programming