Homework 3
Instructions
The source code of this homework can be found here. You should fill in the definitions of the required functions but do not change the types of the functions.
How to submit: Submit this file via the submit server.
> module HW3 where
> import Prelude hiding (sum, Either(..))
> import Data.Monoid
> import Control.Parallel.StrategiesProblem 1: Eithers are Functors, Applicatives & Monads
The data type Either a b contains
- either a
Leftvaluea, - or a
Rightvalueb.
> data Either a b = Left a | Right b
> deriving (Show, Eq)- Functors: Define a functor instance of
Either, that satisfies the functor laws. So that, for example:
ghci> fmap (+42) (Left 0)
Left 0
ghci> fmap (+42) (Right 0)
Right 42 - Applicatives: Define an applicative instance of
Either, that satisfies the applicative laws. So that, for example:
ghci> pure 0 :: Either Int Int
Right 0
ghci> pure (+42) <*> (Left 0)
Left 0
ghci> pure (+42) <*> (Right 0)
Right 42 - Monads: Define a monad instance of
Either, that satisfies the monad laws. So that, for example:
> pairs xs ys = do
> x <- xs
> y <- ys
> return (x,y)ghci> pairs (Right 0) (Right 1)
Right (0,1)
ghci> pairs (Right 0) (Left 1)
Left 1
ghci> pairs (Left 0) (Right 1)
Left 0
ghci> pairs (Left 0) (Left 1)
Left 0Problem 2: Configurations are monoids
A program configuration forms a monoid. For instance, we define the following data type configuration that configures how your Haskell program is compiled:
cOptshould the configurations be enabled? (the default is no)cExtwhat language extensions should be used?cThdhow many threads is the program using?
> data Config
> = Config { cOpt :: Bool
> , cExt :: [String]
> , cThd :: Int
> }
> deriving (Eq, Show)- Monoidal Configurations: Define a monoid instance of
Config.
> instance Monoid Config where
> mempty = error "Define me!"
> mappend = error "Define me!"- Generalized Configurations:
Consider a generalization of the above configuration, where the fields are type variables:
> data GConfig a b c
> = GConfig { gcOpt :: a
> , gcExt :: b
> , gcThd :: c
> }
> deriving (Eq, Show)Now, the instance monoid methods are defined using the monoid methods on the generic configuration’s fields.
> instance (Monoid a, Monoid b, Monoid c) => Monoid (GConfig a b c) where
> mempty = GConfig mempty mempty mempty
> mappend (GConfig o1 e1 t1) (GConfig o2 e2 t2)
> = GConfig (o1 <> o2) (e1 <> e2) (t1 <> t2)In the class we saw that
- lists are monoids, but also
- booleans are monoids (using
AllorAny) and - integers are monoids (using
SumorProduct).
Use the above monoids to properly define a type alias, i.e., replace the Int below with an instantiation of GConfig, so that each MyConfig has the same information as Config, i.e., a “boolean”, a list integer, and an “integer” fields.
> type MyConfig = Int Define the following functions that convert between your monoid configurations
> toMyConfig :: Config -> MyConfig
> toMyConfig = error "Define me!"
>
> fromMyConfig :: MyConfig -> Config
> fromMyConfig = error "Define me!"and use them to check that your monoid methods behave the same, i.e., the following properties are satisfied
toMyConfig mempty == mempty
fromMyConfig mempty == memptyforall x, y. toMyConfig x <> toMyConfig y == x <> y
forall x, y. fromMyConfig x <> fromMyConfig y == x <> y- Functor Configurations: Define an instance
Functorof the generalized configurations, that applies functions to the thread field.
> instance Functor (GConfig a b) where
> fmap f c = error "Define me"In essence, fmap f c maps f to the gcThd field of the configuration c. For example,
gcThd (fmap (+1) (GConfig 1 2 3)) == 4
gcThd (fmap (*42) (GConfig 1 2 3)) == 126 Generally, for each function f and GConfig c:
forall f, c. gcThd (fmap f c) == f (gcThd c) Problem 3: Map Reduce
- Chunkables: The
Chunkabletype class has the methodchunk i xthat cuts its inputxinto lists of length as mosti.
> class Chunkable a where
> chunk :: Int -> a -> [a]Define lists as chunkable instances so that
ghci> chunk 2 [1]
[[1]]
ghci> chunk 2 [1..5]
[[1,2],[3,4],[5]]
ghci> chunk 6 [1..5]
[[1,2,3,4,5]]Generally, each element if chunk i x has length no more than i, and the the chunks exactly reconstruct the list:
forall i, x. mconcat (chunk i x) == x> instance Chunkable [a] where
> chunk = error "Define me!"- Parallel Mapping: Using the parallel functions from the library
Control.Parallel.Strategies, we define a parallel mapping functionpmap f xsthat appliesfto each element inxsin parallel.
> pmap :: (a -> b) -> [a] -> [b]
> pmap = parMap rseqSide-Note 1: If you actually check on the description of rseq, you will discover that pmap is not really really parallel. For the shake of simplicity, let’s assume it is.
Side-Note 2: Parallelization is only possible because the argument function is effect-free, as enforced by the type system. If f had effects, then the order that the effects would be executed, would be undetermined.
Use chunk, pmap and a monoid function to define the mapReduce i f x function below that
- chunks the input
xin chunks of size at mosti, - maps
fto each chunk, in parallel, and - concatenates the result list.
> mapReduce :: (Chunkable a, Monoid b)
> => Int -> (a -> b) -> (a -> b)
> mapReduce = error "Define me!"Hint: This should be an one line definition!
Then for example, you can parallelize the sum function from the lecture:
> sum :: [Int] -> Sum Int
> sum = mconcat . map Sum So that
ghci> sum [1..100]
Sum {getSum = 5050}
mapReduce 10 sum [1..100]
Sum {getSum = 5050}In general:
forall xs, i. sum xs = mapReduce i sum xsWhich generalizes to every function f
forall f, i. f = mapReduce i f- Parallel Reducing: As we parallelized mapping, we can also parallelize the “reduce” stage of map reduce.
Use chunk and pmap from before to define a parallelized version of the monoid mconcat method, so that pmconcat i xs
- if
xshas length less than i, then callsmconcat, otherwise - chunks the input list
xs, - applied
mconcatin parallel, and - recurses on the concatenated chunks.
> pmconcat :: Monoid a => Int -> [a] -> a
> pmconcat = error "Define me!"Hint: pmconcat is recursively defined.
Use pmconcat to define a “two-level” parallel mapReduce, that parallelized both the “map” and “reduce” stages:
> mapReduce2 :: (Chunkable a, Monoid b)
> => Int -> (a -> b) -> (a -> b)
> mapReduce2 = error "Define me!"Hint: mapReduce2 can be defined with an one charactet edit from mapReduce.
So that
mapReduce2 == mapReduce