Week 5 Exercises
Besides featuring a few remaining examples and counterexamples, the purpose of these exercises is to present the most common abstractions that help organize large projects. While they are theoretically rather uninteresting and often quite verbose, they make practical work bearable.
Exercise 1
Some of the following types admit foldables or traversables, while others do not admit any.
- Instances for
Bool
. - Instances for
Maybe a
. - Instances for
Either a b
. - Instances for
(,) a b
. - Instances for
Endo a
. - Instances for
(->) a b
andOp a b
. - Instances for
()
. - Instances for
[] a
. - Instances for
NonEmpty a
. - Instances for
Void
. - Instances for
IO a
. - Instances for
Map k a
.
Figure out which ones do, implement the corresponding type class instances in terms of foldMap
or sequenceA
and prove that your instances are coherent. Your code must compile, but your proofs may be as informal as you wish.
Since some of these instances already exist in Prelude
, you may need to use the following wrappers or introduce new ones to avoid duplicate instance declaration errors. However, be mindful not to accidentally use the existing instances from Prelude
!
module Week5.Exercise1 where
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Map (Map (..))
import qualified Data.Map as Map
import Week1.Exercise1
import Week2.Exercise1
import Week3.Exercise1
Exercise 2
If we compose two functors, we get another functor, but, if we compose two monads, we do not necessarily get another monad. Monad transformers provide a way to classify some of those cases, where composing two monads actually produces another monad.
We shall motivate the use of monad transformers through an experimental investigation into a simple problem from number theory.
Let the Collatz function \[\begin{eqnarray} c & : & \mathbb Z \to \mathbb Z \\ c (n) & \equiv & \begin{cases} n / 2, & n \bmod 2 = 0 \\ 1 + 3 \times n, & n \bmod 2 = 1. \end{cases} \end{eqnarray}\] The Collatz conjecture states that, for all \(n : \mathbb Z\) satisfying \(n > 0\), there exists such \(p : \mathbb N\), that \(c^p (n) = 1\).
The conjecture easier to understand when posed as a question. Starting from a positive initial value, does repeatedly applying the Collatz function eventually reach unity?
While this problem has remained unsolved for almost a century, it has been experimentally verified for all integers up to 256 bits in length.
We shall now consider a toy program that replicates the verification process for small integers. The program
- returns the number of iterations needed for the Collatz function to reach unity,
- throws a loop exception if a cycle is detected,
- throws a value bound exception if an intermediate value exceeds its upper bound,
- throws a counter bound exception if the number of steps exceeds its upper bound, or
- throws a cache bound exception if the cache size of the cycle detector exceeds its upper bound, but also catches it and tries again with a postulated least upper bound.
The program is composed from the Except Problem
monad, the Reader (Maybe Int)
monad and the State (Set a)
monad, whose associated transformers can be stacked in six different ways, two of which are given. Figure out what the different stacks do, decide which one makes the most sense for this application and write a helper function that runs the stack and returns the result. You should be able to reproduce OEIS sequence A006577 in this way.
{-# LANGUAGE ConstraintKinds #-}
module Week5.Exercise2 where
import Data.Int (Int8 (..), Int16 (..))
import Data.Set (Set (..))
import qualified Data.Set as Set
import Control.Monad.Trans.Class
import Control.Monad.Trans.Except
import Control.Monad.Trans.Reader as Reader
import Control.Monad.Trans.State.Strict as State
type Intlike a = (Bounded a, Integral a)
count :: Intlike a => a -> a
count n = 1 + n
safeToCount :: Intlike a => a -> Bool
safeToCount n = n < maxBound
collatz :: Intlike a => a -> a
collatz n
| even n = n `div` 2
| otherwise = 1 + 3 * n
safeToCollatz :: Intlike a => a -> Bool
safeToCollatz n
| even n = True
| otherwise = n > minBound `div` 3 && n < maxBound `div` 3
collatzBound :: Intlike a => Maybe a
collatzBound = Just 18
data Variable = Value | Counter | Cache
deriving Show
data Problem = Loop | Bound Variable
deriving Show
checkCollatzSRE :: (Intlike a, Intlike b) =>
a -> ExceptT Problem (ReaderT (Maybe Int) (State (Set a))) b
checkCollatzSRE = let
f :: (Intlike a, Intlike b) =>
a -> ExceptT Problem (ReaderT (Maybe Int) (State (Set a))) b
f n = do
ps <- (lift . lift) get
if Set.member n ps then
throwE Loop else do
ms <- lift ask
case ms of
Nothing -> if Set.size ps >= maxBound then
throwE (Bound Cache) else
(lift . lift) (put (Set.insert n ps))
Just m -> if Set.size ps >= m then
pure () else
(lift . lift) (put (Set.insert n ps))
if abs n == 1 then
pure 0 else do
if not (safeToCollatz n) then
throwE (Bound Value) else let
p = collatz n in do
q <- f p
if not (safeToCount q) then
throwE (Bound Counter) else
pure (count q) in
\ n -> catchE (f n) $ \ e -> case e of
Bound Cache -> mapExceptT (local (const collatzBound)) (f n)
_ -> throwE e
checkCollatzERS :: (Intlike a, Intlike b) =>
a -> StateT (Set a) (ReaderT (Maybe Int) (Except Problem)) b
checkCollatzERS = let
f :: (Intlike a, Intlike b) =>
a -> StateT (Set a) (ReaderT (Maybe Int) (Except Problem)) b
f n = do
ps <- get
if Set.member n ps then
(lift . lift) (throwE Loop) else do
ms <- lift ask
case ms of
Nothing -> if Set.size ps >= maxBound then
(lift . lift) (throwE (Bound Cache)) else
put (Set.insert n ps)
Just m -> if Set.size ps >= m then
pure () else
put (Set.insert n ps)
if abs n == 1 then
pure 0 else
if not (safeToCollatz n) then
(lift . lift) (throwE (Bound Value)) else let
p = collatz n in do
q <- f p
if not (safeToCount q) then
(lift . lift) (throwE (Bound Counter)) else
pure (count q) in
\ n -> (State.liftCatch . Reader.liftCatch) catchE (f n) $ \ e -> case e of
Bound Cache -> mapStateT (local (const collatzBound)) (f n)
_ -> (lift . lift) (throwE e)
Exercise 3
Monad transformers in the form provided by the transformers
package are somewhat unpleasant to use, because the way the monads are stacked is rigid and thus requires explicit lifting. Alleviating this pain is one of the main motivations behind effect systems.
The most widespread effect system is currently monad transformers with functional dependencies in the form provided by the mtl
package. It works by representing the monads in the stack as type classes, so that the stacking order does not need to be fixed until instance resolution.
Take the programs from exercise 2 and translate them into a single program that uses monad transformers with functional dependencies. That is, find the appropriate type classes for the monads, give the programs a common type that does not fix the stacking order, remove the explicit lifts and run the resulting program with the old helper function.
Note that you cannot rely on type inference here, because it will aggressively unfold the type alises and produce a mess involving the Identity
monad.
{-# LANGUAGE FlexibleContexts #-}
module Week5.Exercise3 where
import Data.Int (Int8 (..), Int16 (..))
import Data.Set (Set (..))
import qualified Data.Set as Set
import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.State.Strict
import Week5.Exercise2
Exercise 4
This is a bonus exercise, which means that you can get stars from it just like you could from any other exercise, but the stars have not been taken into account when calculating the maximum number of stars you can get. Thus, this exercise will be ignored in the unlikely event that not ignoring it would make your grade overflow.
Write a tool to check whether web services are online.
The program should read and parse the provided configuration files, each of which specifies which address to check, how many times to repeat the check in case of recoverable failure, what kind of delay to use between repetitions and whether to present the results in color. The configuration files could be formatted arbitrarily, but the following run command file format is customary.
URL = https://example.com/
NumberOfRepeats = 5
DelayBetweenRepeats = 200 ms
UseColor = yes
The program should then issue a HEAD
request to each address and see what status code the response contains. If the status code indicates a recoverable failure and the maximum number of repetitions has not been exhausted, the program should try again after a short delay. Otherwise, the program should stop making requests to the address.
HEAD / HTTP/1.1
User-Agent: ties341/0.0.0
Host: example.com
Accept: */*
The program should finally collect the results and print a nicely formatted summary into the terminal. If so requested and supported by the terminal, the summary should be decorated with bright colors.
https://duckduckgo.com/ 200 =----
http://endless.horse/ 500 =-
https://example.com/ 200 =----
https://google.com/ 200 =----
https://haskell.org/ 200 =--
https://kernel.org/ 200 =--
http://localhost/ 200 ==-----
https://otherhost/ 500 =======
https://remotehost/ 500 =======
You can choose any detail not specified here to your advantage, so there is a lot of room for creativity. Still, you might find some of the following modules useful.
ansi-terminal
base
containers
directory
filepath
http-client
http-client-tls
http-types
megaparsec
mtl
parser-combinators
text
transformers