Week 4 Exercises
Once more, these exercises feature examples and counterexamples. They also provide an opportunity to elaborate the previously seen applications.
Exercise 1
Some of the following types admit monads, while others do not.
- 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 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
!
It is no longer possible to define the instances for IO
using do
notation, since do
notation merely offers a different syntax for using the operations of the Monad
type class. Thus, you have to use the primitive operations from the GHC.IO
module, which in turn requires the MagicHash
and UnboxedTuples
extensions.
{-# LANGUAGE MagicHash, UnboxedTuples #-}
module Week4.Exercise1 where
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NonEmpty
import GHC.IO (IO (..))
import Week2.Exercise1
import Week3.Exercise1
Exercise 2
Some of the following types admit monads, while others do not.
- Instances for
Sum m n a
, given instances form
andn
. - Instances for
Product m n a
, given instances form
andn
. - Instances for
Identity a
. - Instances for
Compose m n a
, given instances form
andn
. - Instances for
Const a b
. - Instances for
Proxy a
. - Instances for
State a b
. - Instances for
Cont a b
. - Instances for
Star m a b
, given instances form
. - Instances for
Costar m a b
. - Instances for
Yoneda m a
, given instances form
. - Instances for
Coyoneda m a
, given instances form
.
Figure out which ones do, implement the corresponding type class instances and prove that your instances are coherent. Your code must compile, but your proofs may be as informal as you wish.
Most of the same considerations apply as in exercise 1.
Exercise 3
Semirings are algebraic structures made up of two monoids, one of which distributes over the other. They are often obtained by combining the canonical addition and multiplication monoids of various types, such as natural numbers, integers, rational numbers, polynomials or functions. The Num
type class in Haskell is customarily assumed to represent a semiring. The class has more than enough structure to represent an ordered ring or more, but this assumption would invalidate most of its instances, so it is avoided. We will ignore this concern, but note that it is a thing that people still fight about.
Let us now consider the question of finding representations for expressions in an arbitrary semiring. There are two notable ways to approach this problem.
- One way is to observe that, if
Num
indeed represents a semiring, any nonrecursive Haskell program built up from applications of+
,0
,*
and1
is a valid expression in some semiring. This is called a shallow embedding, because the semantics of Haskell are automatically transported to the expressions. - Another way is to make a new type
Expr
with the constructorsAdd
,Zero
,Mul
andOne
and observe that any inhabitant of this type is an expression in some semiring. This is called a deep embedding, because any semantics we want the expressions to have must be given to them manually.
If we extend the shallow embedding by allowing nonrecursive let
bindings and variables, we will have to adjust the deep embedding accordingly by adding the constructors Let
and Var
to Expr
.
Given a shallowly-embedded closed term representing 31 (built optimally according to OEIS sequence A005245), a shallowly-embedded open term and an evaluator for shallowly-embedded terms, implement the corresponding constructions for deeply-embedded terms.
We will need these to do exercise 4 as well.
module Week4.Exercise3 where
import Control.Exception
import Data.Map (Map (..))
import qualified Data.Map as Map
import System.IO.Unsafe (unsafePerformIO)
closedShallow :: Num a => a
closedShallow = let
two :: Num a => a
two = 1 + 1 in let
three :: Num a => a
three = 1 + two in let
nine :: Num a => a
nine = three * three in
1 + three * (1 + nine)
openShallow :: Num a => a
openShallow = 1 + undefined
evalShallow :: Num a => a -> Maybe a
evalShallow x = unsafePerformIO (catch (seq x (pure (Just x)))
(\ e -> seq (e :: SomeException) (pure Nothing)))
data Expr = Add Expr Expr | Zero | Mul Expr Expr | One |
Let String Expr Expr | Var String
deriving Show
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.
The most important feature that monads have and applicative functors lack is context-sensitivity. To use parsers as an example, context-sensitivity means that, when parsing any part of the input, choosing the parser to use next may depend on any other part of the input that has been parsed so far. While context-sensitive grammars like this provide significantly more expressive power than context-free ones, people often try to avoid their use, because with great power comes great loss of other useful properties. Let us explore this through a familiar example.
Extend your simple framework for applicative-alternative recursive-descent parsers to become monadic-alternative and use the result to parse expressions in an arbitrary semiring. That is, implement the Monad
instance for parsers and translate the following ANTLR 4 specification of a grammar for expressions into a recursive-descent parser.
grammar ExprLL ;
expr : add ;
add : mul adds ;
adds : ( '+' mul adds ) ? ;
mul : other muls ;
muls : ( '*' other muls ) ? ;
other : sub | zero | one | let | var ;
sub : '(' add ')' ;
zero : '0' ;
one : '1' ;
let : 'let' Ident '=' add 'in' add ;
var : Ident ;
Ident : Small ( Small | Large | Digit | Prime ) *
{ ! getText().equals("let") && ! getText().equals("in") }? ;
Small : [a-z] | [_] ;
Large : [A-Z] ;
Digit : [0-9] ;
Prime : ['] ;
Space : [\t\n\u000b\f\r ] + -> skip ;
This specification is actually a preprocessed version of the following less convoluted specification. Going through the preprocessing is necessary, because translating the original specification into a recursive-descent parser would produce a program that never terminates due to the left recursion in the add
and mul
productions. While replacing applicative functors with monads got us from context-free \(\mathrm{LL} (\ast)\) grammars to context-sensitive \(\mathrm{LL} (\ast)\) grammars, it did not get us any closer to being able to handle \(\mathrm{LR} (\ast)\) grammars.
grammar ExprLR ;
expr : add ;
add : add '+' mul | mul ;
mul : mul '*' other | other ;
other : sub | zero | one | let | var ;
sub : '(' add ')' ;
zero : '0' ;
one : '1' ;
let : 'let' Ident '=' add 'in' add ;
var : Ident ;
Ident : Small ( Small | Large | Digit | Prime ) *
{ ! getText().equals("let") && ! getText().equals("in") }? ;
Small : [a-z] | [_] ;
Large : [A-Z] ;
Digit : [0-9] ;
Prime : ['] ;
Space : [\t\n\u000b\f\r ] + -> skip ;
Your parser should be able to recognize the shallowly-embedded terms from exercise 3, as long as you remove the type signatures beforehand.
Make sure you understand how do
notation can be used to replace <$>
, <$
, <*>
, <*
and *>
before making a big mess.
module Week4.Exercise4 where
import Control.Applicative
import Week3.Exercise3
import Week4.Exercise3
closedString :: String
closedString = "let \
\ two = 1 + 1 in let \
\ three = 1 + two in let \
\ nine = three * three in \
\ 1 + three * (1 + nine)"
openString :: String
openString = "1 + undefined"
showsPrecExpr :: Int -> Expr -> ShowS
showsPrecExpr n (Add x y) = showParen (n > 6) $
showsPrecExpr 7 x . showString " + " . showsPrecExpr 7 y
showsPrecExpr _ Zero = showString "0"
showsPrecExpr n (Mul x y) = showParen (n > 7) $
showsPrecExpr 8 x . showString " * " . showsPrecExpr 8 y
showsPrecExpr _ One = showString "1"
showsPrecExpr n (Let cs x y) = showParen (n > 0) $
showString "let " . showString cs .
showString " = " . showsPrecExpr 0 x .
showString " in " . showsPrecExpr 0 y
showsPrecExpr _ (Var cs) = showString cs
showsExpr :: Expr -> ShowS
showsExpr = showsPrecExpr 0