Week 3 Exercises
The theme of these exercises is, again, examples and counterexamples. They also give rise to a very nice practical application.
Exercise 1
Some of the following types admit applicative functors, 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 bandOp 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!
While it is fine to define the instances for IO using do notation, the morally correct way requires primitive operations from the GHC.IO module, which in turn requires the MagicHash and UnboxedTuples extensions. If you implement the instances in this way, they should look a lot like State in exercise 3.
module Week3.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 Data.Void
import Week2.Exercise1Exercise 2
Some of the following types admit applicative functors, while others do not.
- Instances for
Sum m n a, given instances formandn. - Instances for
Product m n a, given instances formandn. - Instances for
Identity a. - Instances for
Compose m n a, given instances formandn. - Instances for
Const a b, given instances fora. - 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.
The language extensions are required to be able to use universal quantifiers more freely with Yoneda and Coyoneda.
Exercise 3
In certain cases, it is possible to endow applicative functors with additional monoidal structure. This gives us alternative functors, so called because they capture the idea of choosing the result of a computation from zero or more alternatives. The corresponding type class is the following.
class Applicative m => Alternative m where
empty :: m a
(<|>) :: m a -> m a -> m a
The monoidal structure is apparent by observing that we can form a monoid, where
- the type is
m a, - the binary operator is
<|>and - the point is
empty.
The monoid laws obviously follow, but there are other laws, such as distributivity, that people still fight about. We will let them do that and, instead, focus on using alternative functors to process text.
Create a simple framework for applicative-alternative recursive-descent parsers. That is, define parsers as inhabitants of the type String -> Either ParseError (String, a) for any type a, implement the Functor, Applicative and Alternative instances for parsers and define at least the following basic building blocks.
- A primitive end-of-file parser
eofof typeParser ()should consume no input and succeed precisely when there is nothing left to parse. - A primitive predicate parser family
satisfyof type(Char -> Bool) -> Parser Charshould consume a single character and succeed precisely when the character satisfies the given predicate. - A derived parser family
singleof typeChar -> Parser Charshould consume a single character and succeed precisely when the character is equal the given character. - A derived parser family
anySingleButof typeChar -> Parser Charshould consume a single character and succeed precisely when the character is not equal the given character. - A derived parser family
oneOfof type[Char] -> Parser Charshould consume a single character and succeed precisely when the character is equal to any of the given characters. - A derived parser family
noneOfof type[Char] -> Parser Charshould consume a single character and succeed precisely when the character is not equal to any of the given characters. - A derived parser family
chunkof typeString -> Parser Stringshould consume a chunk of characters and succeed precisely when the chunk is equal to the given string.
We will need these to do exercise 4 as well.
module Week3.Exercise3 where
import Control.Applicative
data ParseError = SomethingWentWrong
deriving ShowExercise 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.
Applicative-alternative recursive-descent parsers can handle a considerable subset of context-free grammars. In particular, they can handle nonrecursive (finite) grammars, regular grammars, visibly-pushdown (nested word) grammars, context-free \(\mathrm{LL} (k)\) grammars for any given \(k : \mathbb N\) and, at the limit, context-free \(\mathrm{LL} (\ast)\) grammars. Context-free grammars are especially common in applications, because they strike a good balance between expressive power, amenability to static analysis and resource usage when implemented. One simple example is the grammar of comma-separated values.
Translate the following ANTLR 4 specification of a grammar for comma-separated values into a recursive-descent parser. The grammar is already in \(\mathrm{LL} (2)\) form, so you do not need to preprocess it before doing the translation.
grammar CSV ;
group : record * ;
record : unit ( UnitSeparator unit ) * RecordSeparator ;
unit : QuotedValue | UnquotedValue ? ;
RecordSeparator : '\n' | '\r' '\n' ? ;
UnitSeparator : ',' ;
UnquotedValue : ( ~ ( '\n' | '\r' | '"' | ',' ) ) + ;
QuotedValue : '"' ( '""' | ~ '"' ) * '"' ;Your parser should be able to recognize the following file.
#0,#1,#2,#3,#4,#5,#6,#7,#8,#9
0,1,2,3,4,5,6,7,8
1,1,1,1,one as a string,1,1,1,1
2,1,2,1,2,1,2,1,2
3,1,1,3,"one, but with a comma",1,3,1,1
4,1,2,1,4,1,2,1,4
5,1,1,1,"one accompanied by
a line break",5,1,1,1
6,1,2,3,2,1,6,1,2
7,1,1,1,"one involving ""quotation"" marks",1,1,7,1
8,1,2,1,4,1,2,1
,,,,"one among missing values",,,,,9Make sure you understand how <$>, <$, <*>, <*, *>, <|>, many, some, optional and empty can be used to combine the basic building blocks from exercise 3 before making a big mess.
module Week3.Exercise4 where
import Control.Applicative
import Data.List (intersect)
import Week2.Exercise3
import Week3.Exercise3
type Unit = String
type Record = [Unit]
type Group = [Record]
fromEither :: Either a a -> a
fromEither (Left x) = x
fromEither (Right x) = x
showsEscaped :: String -> ShowS
showsEscaped [] = id
showsEscaped (c : cs)
| c == '"' = mappend (replicate 2 '"') . showsEscaped cs
| otherwise = (c :) . showsEscaped cs
showsQuoted :: String -> ShowS
showsQuoted cs = ('"' :) . showsEscaped cs . ('"' :)
showsGroup :: Group -> ShowS
showsGroup xsss = flip (foldr (\ xss ->
fromEither . runJoin . flip (foldr (\ xs css -> let
f = case intersect ['\n', '\r', '"', ','] xs of
[] -> mappend xs
_ : _ -> showsQuoted xs
x = case css of
Join (Left cs) -> '\n' : cs
Join (Right cs) -> ',' : cs in
Join (Right (f x)))) xss . Join . Left)) xsss