Skip to content

Instantly share code, notes, and snippets.

@khuldraeseth
Last active July 30, 2024 03:09
Show Gist options
  • Save khuldraeseth/5508f20936ff21b69280f48d2187b211 to your computer and use it in GitHub Desktop.
Save khuldraeseth/5508f20936ff21b69280f48d2187b211 to your computer and use it in GitHub Desktop.
The Haskell rite of passage
{-
A Haskell source file begins with zero or more file-scope pragmas that tell tools how to treat the file.
Pragmas look like multiline comments `{- ... -}` that begin and end with `#`.
The LANGUAGE pragma is a common one. it enables language extensions.
Oh, yeah. Haskell allows nested multiline comments, by the way.
-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use foldr" #-}
{-# HLINT ignore "Use <$>" #-}
{-# HLINT ignore "Eta reduce" #-}
{-# HLINT ignore "Use id" #-}
{-# HLINT ignore "Avoid lambda" #-}
{-# HLINT ignore "Use const" #-}
{-
Every source file defines a module. The module's name matches the file's name minus the extension.
Then come imports, in a few forms:
- import Module -- import everything
- import Module (names) -- import only particular names
- import Module hiding (names) -- import everything except particular names
- import qualified Module -- import and require Module.name scope resolution
- import qualified Module (names) -- import specific stuff and require Module.name scope resolution
- import qualified Module as Name -- import and give a different name in this file
With {-# LANGUAGE ImportQualifiedPost #-}, `qualified` can appear after `Module`. I like that.
-}
module MonadsAndMTL where
import Data.Bits (xor)
import Prelude hiding (
Applicative (..),
Either (..),
Foldable (..),
Functor (..),
Maybe (..),
Monad (..),
Monoid (..),
Product (..),
Semigroup (..),
Sum (..),
Traversable (..),
)
{-
A little something for use in exercises
-}
type Unimplemented = forall a. a
unimplemented :: Unimplemented
unimplemented = error "implement me"
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------------ Semigroup ------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Now, a typeclass!
A typeclass is a class of types. Shocker, right?
Let's define `Semigroup`. In math, a [semigroup](https://en.wikipedia.org/wiki/Semigroup) is a set
equipped with an associative binary operation. The integers and addition, for example. Strings and concatenation.
In order for a type `a` to satisfy the constraint `Semigroup a` (read: "`a` is a semigroup"), it must have
this operation (named `(<>)`) defined.
The associativity law `a <> (b <> c) === (a <> b) <> c` is not expressed here.
-}
class Semigroup a where
(<>) :: a -> a -> a
{-
Now, we make some types instances of this typeclass.
First, let's notice that `Integer` should not be a semigroup, since there are multiple sensible ways
to implement `(<>)`. Addition? Multiplication? Bitwise XOR?
What we do instead is define a new type that looks exactly like `Integer`.
-}
newtype Sum = Sum' Integer
{-
Now each `Sum` is of the form `Sum n` for some `n :: Integer`, but `Sum` and `Integer` are still distinct types.
Let's make `Sum` a `Semigroup` instance.
-}
instance Semigroup Sum where
(Sum' m) <> (Sum' n) = Sum' $ m + n
{-
Let's do another. Bitwise XOR :)
Two differences here!
- One, the names of the type constructor and data constructor are identical. The compiler will know based on context
which one is used each time `Xor` appears.
- Two, `Xor` is a unary type constructor rather than a concrete type in its own right, so `Xor Integer` is analogous to
`Sum`.
-}
newtype Xor a = Xor a
instance Semigroup (Xor Integer) where
(Xor m) <> (Xor n) = Xor $ m `xor` n
{-
Now, `Product`. This newtype looks just like `Xor`...
-}
newtype Product a = Product a
{-
... but the `Semigroup` instance we define will be a little more general. For any type `a` that allows multiplication,
we want to make `Product a` a semigroup under that multiplication operation.
Try out `:t (*)` in GHCi and you'll see that it's constrained by the typeclass `Num`, so we write:
-}
instance (Num a) => Semigroup (Product a) where
(Product m) <> (Product n) = Product $ m * n
{-
The fat right arrow `=>` reads like implication.
-}
{-
Now an exercise. For any type `a`, the type `[a]` is a sensible `Semigroup`. Complete the definition below.
`[a]` is known as the _free semigroup_ over `a`. Verify that `<>` is associative.
-}
instance Semigroup [a] where
(<>) :: [a] -> [a] -> [a]
xs <> ys = unimplemented
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------------- Monoid --------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Let's now consider `Monoid`. A [https://en.wikipedia.org/wiki/Monoid](monoid) is a semigroup whose operation has an
identity.
The definition reads exactly like that! If you know how to read it, at least.
For some reason, the same fat right arrow has almost the opposite meaning here. It indicates that the constraint
`Semigroup a` is a _prerequisite_ for `Monoid a`.
For a type to be a monoid, this definition says that it must be a semigroup and have one special inhabitant that is an
identity element for `<>`.
`Monoid` has an additional law not expressed in the code: `identity <> x === x === x <> identity`
-}
class (Semigroup a) => Monoid a where
identity :: a
{-
The identity element for integer addition is zero.
-}
instance Monoid Sum where
identity = Sum' 0
{-
Exercise: implement the `Monoid` instance for `Xor Integer`.
-}
instance Monoid (Xor Integer) where
identity :: Xor Integer
identity = unimplemented
{-
Exercise: given that `a` satisfies `Num`, implement the `Monoid` instance for `Product a`.
-}
instance (Num a) => Monoid (Product a) where
identity :: Num a => Product a
identity = unimplemented
{-
Exercise: implement the `Monoid` instance for `[a]`. Verify that it satisfies the monoid law according to the
`Semigroup` instance you implemented above.
-}
instance Monoid [a] where
identity :: [a]
identity = unimplemented
{-
Now, how do we use typeclasses?
We put them on the left-hand sides of fat arrows.
The following declaration means "when `a` satisfies `Monoid`, `concatenate` has type `[a] -> a`."
It's assumed in the definition that `a` satisfies `Monoid`, so the compiler lets us use `identity` and `(<>)`.
The compiler is pretty good at deducing constraints from definitions. Even without the declaration, `concatenate` would
have the same type.
-}
-- concatenate [foo, bar, baz, ...] === foo <> bar <> baz <> ...
concatenate :: (Monoid a) => [a] -> a
concatenate [] = identity
concatenate (y : ys) = y <> concatenate ys
{-
One final note on monoids: `identity` is named `mempty` in the Haskell standard library, and class `Monoid` also
introduces `mappend` as an alias for `(<>)`.
Ah, and `concatenate` is defined as a method `mconcat` of `Monoid` rather than an ordinary constrained function. This
is to let programmers give a more efficient implementation if they can.
Check it out! `:i Monoid` in GHCi should show you all that and some more.
-}
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------------- Functor -------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Now for a more fun typeclass.
First things first: `f` below is not a concrete type like `Sum` or `Xor Integer`. You cannot instantiate an `f`; you
can only apply it to a concrete type to produce a concrete type. Notice `f a` and `f b` below in the type signature
of `fmap`.
Formally, we say concrete types have _kind_ `*`, pronounced "type". A kind is a type of types, more or less. And since
`f` below transforms a concrete type `a` into the concrete type `f a`, we say `f` has kind `* -> *`.
This can be explicitly annotated, as you see below. Without the annotation, the compiler will still figure it out.
-}
class Functor (f :: * -> *) where
fmap :: (a -> b) -> f a -> f b
{-
So, what is a functor? A functor is a unary type constructor `f` (a type constructor that yields a concrete type when
applied to one type argument) equipped with an operation `fmap` that lifts a function of type `a -> b` into one of
type `f a -> f b`. Recall that `->` in types is right-associative, so the type signature below is equivalent to
`(a -> b) -> (f a -> f b)`.
Here's a very simple functor.
-}
newtype Identity a = Identity a
instance Functor Identity where
fmap f (Identity x) = Identity (f x)
{-
Here's a slightly less simple functor.
A `Maybe a` is either nothing or something. When it is something, it is an `a`.
When we don't have an `a`, we can't use `f` to make a `b` to put in a `Just`. The only possible result here is
`Nothing`.
When we do have an `a`, we can do interesting things! So we do.
-}
data Maybe a = Nothing | Just a
instance Functor Maybe where
fmap f Nothing = Nothing
fmap f (Just x) = Just (f x)
{-
Note that `fmap f (Just x) = Nothing` would be a valid implementation according to the type system. It's obviously not
the right one, though. There are two laws each functor must obey:
- `fmap id === id`
- fmap (g . f) === fmap g . fmap f
The identity function defined `id x = x` returns its argument unchanged. Mapping over any structure using this function
must return that structure unchanged. That's why the bad implementation of `fmap @Maybe` is wrong. With it, we have:
`fmap id (Just 0) === Nothing !== Just 0 === id (Just 0)`
Mapping using a function `f` and then using `g` is equivalent to mapping using the composition of `g` with `f`.
-}
{-
Exercise: implement the `Functor` instance for `[]`, the list type.
Verify that it satisfies the functor laws.
-}
instance Functor [] where
fmap :: (a -> b) -> [a] -> [b]
fmap = unimplemented
{-
Exercise: implement the `Functor` instance for `Either l`.
Verify that it satisfies the functor laws.
-}
data Either l r = Left l | Right r
instance Functor (Either l) where
fmap :: (a -> b) -> Either l a -> Either l b
fmap = unimplemented
{-
Exercise: implement the `Functor` instance for `(,) l`, where `(,) l r` is the type of pairs `(l, r)`.
Verify that it satisfies the functor laws.
-}
instance Functor ((,) l) where
fmap :: (a -> b) -> (l, a) -> (l, b)
fmap = unimplemented
{-
Exercise: implement the `Functor` instance for `(->) a`, where `(->) a b` is the type of functions `a -> b`.
Verify that it satisfies the functor laws.
-}
instance Functor ((->) a) where
fmap :: (a2 -> b) -> (a1 -> a2) -> a1 -> b
fmap = unimplemented
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------------ Foldable -------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
`Foldable` is like `Functor` in that it's a class of types of kind `* -> *`. The next few will be as well, so get used
to it.
A foldable structure is one that can be reduced to a single value by a _fold_, (possibly) repeated application of a
single function. A right fold places an initial accumulator at the far right of the structure and then collapses it
all from right to left like so: `foldr (#) a [..., x, y, z] === ... # (x # (y # (z # a)))`
-}
class Foldable (f :: * -> *) where
foldr :: (a -> b -> b) -> b -> f a -> b
{-
One very simple instance as a demonstration:
-}
instance Foldable Identity where
foldr f y (Identity x) = f x y
{-
And now it's your turn :)
Exercise: implement the `Foldable` instance for `Maybe`.
-}
instance Foldable Maybe where
foldr :: (a -> b -> b) -> b -> Maybe a -> b
foldr = unimplemented
{-
Exercise: implement the `Foldable` instance for `[]`.
-}
instance Foldable [] where
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr = unimplemented
{-
Exercise: implement `foldMap`.
-}
foldMap :: (Foldable f, Monoid b) => (a -> b) -> f a -> b
foldMap = unimplemented
{-
Exercise: using `foldMap` (NOT `foldr`), implement `product`.
-}
product :: (Foldable f, Num a) => f a -> a
product = unimplemented
{-
Exercise: implement `length`.
-}
length :: (Foldable t) => t a -> Integer
length = unimplemented
-----------------------------------------------------------------------------------------------------------------------
----------------------------------------------------- Applicative -----------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Okay, from here on things get pretty funky. Applicative functors are a little tricky to wrap your head around, but
they're also quite powerful.
-}
class (Functor f) => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
{-
`Applicative` has a lot of laws. Don't worry about these yet except for the first two, I'd say.
- `pure f <*> x === fmap f x`
- `pure f <*> pure x === pure (f x)`
- `g <*> pure y === pure (\f -> f y) <*> g`
- `g <*> (f <*> x) === pure (.) <*> g <*> f <*> x
The pattern `pure f <*> x <*> y <*> ...` is very common, so we give it a nicer name, `liftA`. We do have to specify
arity in the name, though:
-}
liftA2 :: (Applicative f) => (a -> b -> c) -> f a -> f b -> f c
liftA2 f x y = pure f <*> x <*> y
liftA3 :: (Applicative f) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 f x y z = pure f <*> x <*> y <*> z
{-
We can count down, too:
-}
liftA1 :: (Applicative f) => (a -> b) -> f a -> f b
liftA1 f x = pure f <*> x
{-
Wait a moment, that signature looks familiar...
An equivalent definition would have been `liftA1 = fmap`, by the first applicative law.
`Applicative` (as opposed to `Functor`) allows us to lift functions of arities other than 1.
-}
liftA0 :: (Applicative f) => a -> f a
liftA0 = pure
{-
Okay, let's see some instances.
-}
instance Applicative Identity where
pure x = Identity x
Identity f <*> Identity x = Identity (f x)
instance Applicative Maybe where
pure x = Just x
Nothing <*> _ = Nothing
_ <*> Nothing = Nothing
Just f <*> Just x = Just (f x)
{-
And now it's your turn.
Exercise: implement an `Applicative` instance for `[]`.
There are multiple correct answers!
-}
instance Applicative [] where
pure :: a -> [a]
pure = unimplemented
(<*>) :: [a -> b] -> [a] -> [b]
(<*>) = unimplemented
{-
Exercise: compute the Cartesian product of lists:
`[a1 .. am] `ctimes` [b1 .. bn] = [(a1, b1) .. (a1, bn) .. (am, b1) .. (am, bn)]`
Order of the result does not matter.
If this is not possible using your `Applicative []` instance, well done! You've accidentally discovered `ZipList`.
Remember what you did, then write another instance that does allow you to implement `ctimes`.
-}
ctimes :: [a] -> [b] -> [(a, b)]
ctimes = unimplemented
{-
Exercise: implement the `Applicative` instance for `Either l`.
There are multiple correct answers! All do roughly the same thing.
-}
instance Applicative (Either l) where
pure :: a -> Either l a
pure = unimplemented
(<*>) :: Either l (a -> b) -> Either l a -> Either l b
(<*>) = unimplemented
{-
Exercise: implement the following error-checking version of `\x -> log x + sqrt (x^2 - 4)`.
In the case of `log` and `sqrt` both getting invalid arguments, choose the error arbitrarily.
`Ord` lets you compare for relational inequality with `(<)` and the like. `Floating` lets you perform all the
computation necessary: `log`, `sqrt`, `(^)`, `(-)`.
-}
data MathError = LogOfNonpositive | SqrtOfNegative
deriving (Show)
unnamed1 :: (Ord c, Floating c) => c -> Either MathError c
unnamed1 x = unimplemented
{-
Exercise: implement the `Applicative` instance for `(->) a`.
-}
instance Applicative ((->) a) where
pure :: a2 -> a1 -> a2
pure = unimplemented
(<*>) :: (a1 -> a2 -> b) -> (a1 -> a2) -> a1 -> b
(<*>) = unimplemented
{-
Exercise: use `(<*>)` as defined above to compute triangle numbers pointfree.
Pointfree means you can't refer to parameters by name, so the easy solution `triangle n = (n * (n - 1)) / 2` is
forbidden. No `let`- or `where`-bindings, either!
Your solution must have the form `triangle = {some expression meaningfully involving (<*>)}`.
Don't worry about `Fractional`. That just lets you use `(/)` for division instead of `div` from class `Integral`.
-}
triangle :: (Fractional a) => a -> a
triangle = unimplemented
{-
Exercise: implement an `Applicative` instance for `(,) a`, given that `a` is a monoid.
There are multiple correct answers! All do roughly the same thing.
-}
instance (Monoid a) => Applicative ((,) a) where
pure :: Monoid a => a1 -> (a, a1)
pure = unimplemented
(<*>) :: Monoid a => (a, a1 -> b) -> (a, a1) -> (a, b)
(<*>) = unimplemented
{-
Exercise: implement the following error-checking version of `\x -> log x + sqrt (x^2 - 4)`.
In the case of `log` and `sqrt` both getting invalid arguments, place the logarithm error first in the list.
Use `nan` for the result of invalid computation. `Floating` has `Fractional` as a prerequisite.
-}
nan :: Fractional a => a
nan = 0 / 0
unnamed2 :: (Ord c, Floating c) => c -> ([MathError], c)
unnamed2 x = unimplemented
{-
A value of type `f a` where `f` satisfies `Applicative` represents what we call an effectful computation. It yields
(zero or more) results of type `a` and has effects in the context of the applicative functor `f`.
`pure x` is the computation that produces `x` as its only result and has no effects.
What makes `Aplicative` more powerful than `Functor` is its ability to combine contexts. Recall:
- `fmap :: (Functor f) => (a -> b) -> f a -> f b`
- `(<*>) :: (Applicative f) => f (a -> b) -> f a -> f b`
Notice that the type of `fmap` has only one `f` on the left of the final arrow. `fmap` only preserves effects. It does
not do anything interesting with them.
On the other hand, `(<*>)` takes two effectful computations and produces only one. This means somehow combining the
effects of the two. Effects are combined by sequencing; one effect happens and then the other.
By convention, in `f <*> x` the effects of `f` are sequenced before the effects of `x`, whatever that means in the
context of the particular applicative functor. For example:
- `Left foo <*> Left bar === Left foo`, since the effect of failing with error `foo` happens before failing with `bar`.
- `(foo, f) <*> (bar, x) === (foo <> bar, f x)`. Not `(bar <> foo, f x)`.
Exercise: check the `Applicative` instances you've written to make sure they follow this convention. Pay particularly
close attention to the ones I said have multiple correct implementations.
-}
{-
So, what if we only care about the effect and not the result of a computation?
Exercise: implement the applicative sequencing operators.
-}
(<*) :: (Applicative f) => f a -> f b -> f a
(<*) = unimplemented
(*>) :: (Applicative f) => f a -> f b -> f b
(*>) = unimplemented
-----------------------------------------------------------------------------------------------------------------------
----------------------------------------------------- Alternative -----------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
This one is a little less wacky, you'll be relieved to learn.
An alternative is an applicative functor with a monoid structure. That's about it.
Three laws:
- `x <|> (y <|> z) === (x <|> y) <|> z`
- `empty <|> x === x === x <|> empty`
- `empty <*> x === empty`
`Alternative` encodes choice. `empty` is the worst choice possible, so we always avoid it when `(<|>)` lets us choose.
Once we're stuck with `empty`, it corrupts everything until we have the opportunity to choose something else instead.
-}
class (Applicative f) => Alternative f where
empty :: f a
(<|>) :: f a -> f a -> f a
{-
Exercise: implement an `Alternative` instance for `Maybe`.
There are multiple correct answers! All do roughly the same thing.
-}
instance Alternative Maybe where
empty :: Maybe a
empty = unimplemented
(<|>) :: Maybe a -> Maybe a -> Maybe a
(<|>) = unimplemented
{-
Exercise: implement an `Alternative` instance for `[]`.
There are multiple correct answers! See if you can come up with more than one.
-}
instance Alternative [] where
empty :: [a]
empty = unimplemented
(<|>) :: [a] -> [a] -> [a]
(<|>) = unimplemented
{-
Exercise: implement `some` and `many`. `some` repeats an action one or more times and collects the results. `many`
repeats an action zero or more times and collects the results.
Think about why I'm giving these here, and think about why I'm giving them together. A very elegant solution exists.
-}
some :: (Alternative f) => f a -> f [a]
some = unimplemented
many :: (Alternative f) => f a -> f [a]
many = unimplemented
-----------------------------------------------------------------------------------------------------------------------
-------------------------------------------------------- Monad --------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
This is it. The big one. Monad.
A monad is just a monoid in the category of endofunctors. What's the problem?
The type signature of `(>>=)` (pronounced "bind" for reasons you'll learn soon) is so beautifully powerful. Where
`Functor` and `Applicative` allow transforming data within the context of some structure, `Monad` allows so much more.
`(a -> m b)` does not transform data into data; it transforms data into a _computation_ that can produce data.
Three laws:
- `pure x >>= f === f x`
- `x >>= pure === x`
- `x >>= (\y -> f y >>= g) === x >>= f >>= g`
-}
class (Applicative m) => Monad m where
(>>=) :: m a -> (a -> m b) -> m b
{-
Exercise: implement the `Monad` instance for `Identity`.
-}
instance Monad Identity where
(>>=) :: Identity a -> (a -> Identity b) -> Identity b
(>>=) = unimplemented
{-
Exercise: implement the `Monad` instance for `Maybe`.
-}
instance Monad Maybe where
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
(>>=) = unimplemented
{-
Exercise: implement the `Monad` instance for `Either l`.
-}
instance Monad (Either l) where
(>>=) :: Either l a -> (a -> Either l b) -> Either l b
(>>=) = unimplemented
{-
Exercise: implement the following error-checking version of `\x -> sqrt (log x)`.
-}
unnamed3 :: (Ord b, Floating b) => b -> Either MathError b
unnamed3 = unimplemented
{-
Exercise: implement the `Monad` instance for `[]`.
-}
instance Monad [] where
(>>=) :: [a] -> (a -> [b]) -> [b]
(>>=) = unimplemented
{-
Exercise: implement `knightMoves`, which takes a number `n` and returns the list of locations a knight can occupy after
exactly `n` moves starting from `(0, 0)`. With multiplicity, so `knightMoves 2` should contain two copies of `(0, 0)`.
-}
type Square = (Integer, Integer)
knightMoves :: Integer -> [Square]
knightMoves = unimplemented
{-
Exercise: implement the `Monad` instance for `(->) a`.
-}
instance Monad ((->) a) where
(>>=) :: (a1 -> a2) -> (a2 -> a1 -> b) -> a1 -> b
(>>=) = unimplemented
{-
Exercise: implement `join`.
-}
join :: (Monad m) => m (m a) -> m a
join = unimplemented
{-
One last thing before we move on from `Monad` is `do`-notation. The keyword `do` introduces a block of code that looks
imperative. You might have seen in before when dealing with the `IO` monad. I thought Haskell was declarative!
That's what makes monads so great. An applicative functor allows sequencing effects, so imperative-like code might make
sense in the contect of one, but it's not until you have a monad that the result of one computation can be used to
decide the next computation to perform.
What I'm getting at is that monads are expressive enough to allow arbitrary chains of fully dependent computations.
`do`-notation provides a convenient syntactic sugar for this.
do
e
is equivalent to `e`.
do
x <- e1
e2...
is equivalent to `e1 >>= (\x -> e2...)`.
do
e1
e2...
is equivalent to `e1 >>= (\_ -> e2...)`.
do
let x = e1
e2...
is equivalent to `let x = e1 in e2...`.
Feel free to use `do`-notation in your implementations going forward. It may or may not play nice with these custom
typeclasses taking the place of the regular `Functor`, `Applicative`, and `Monad`. GHC probably won't be all too
pleased, alas.
Sometimes the full power of `(>>=)` is not necessary and we can get away with only `fmap` or `(<*>)`. The compiler is
able to detect this and use the least restrictive operations if you enable the ApplicativeDo language extension.
-}
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------------ MonadPlus ------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
MonadPlus is easy. Really easy. Literally just Alternative and Monad. No new behavior.
Here we see defaults. When methods can be implemented in terms of other methods, this is how.
-}
class (Alternative m, Monad m) => MonadPlus m where
mzero :: m a
mzero = empty
mplus :: m a -> m a -> m a
mplus = (<|>)
-----------------------------------------------------------------------------------------------------------------------
----------------------------------------------------- Traversable -----------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
A traversable structure is one we can traverse.
surprised-pikachu.jpg
Traversal is a lot like mapping (`fmap`). Visit each thing in the structure and transform using a function. The key
difference is that traversal allows this function to produce effects in an applicative functor with that `f b`.
Effects in an applicative functor can be sequenced, as you've seen. Traversal sequences all the effects produced and
returns the mapped result (of type `t b`) in the applicative context in which these effects occur.
-}
class (Functor t, Foldable t) => Traversable t where
traverse :: (Applicative f) => (a -> f b) -> t a -> f (t b)
{-
Exercise: implement the `Traversable` instance for `Maybe`.
-}
instance Traversable Maybe where
traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b)
traverse = unimplemented
{-
Exercise: implement the `Traversable` instance for `[]`.
-}
instance Traversable [] where
traverse :: Applicative f => (a -> f b) -> [a] -> f [b]
traverse = unimplemented
{-
`sequenceA` turns a structure of effectful actions into an effectful action producing a structure of results.
Exercise: implement `sequenceA`.
-}
sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
sequenceA = unimplemented
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------- Some Useful Monads --------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Now I'll give you some type definitions and tell you which typeclasses they should satisfy. You're tasked with
implementing _all_ the necessary instances. Some may look extremely familiar. Some likely will not.
Something interesting to notice is that `a` appears only on the right side of arrows in all these types. No need to
spend time thinking about that now; it's just something interesting I thought I might as well point out.
-}
{-
The Reader monad: an action of type `Reader r a` is one that produces a result of type `a` after being allowed to read
from an immutable state of type `r`.
What you see here is called _record syntax_. The definition below is more or less equivalent to the non-record
definition `newtype Reader r a = Reader (r -> a)` coupled with a function `runReader :: Reader r a -> r -> a`.
When you have a `Reader r a` action `ma`, you can run it on a state `r :: r` with `runReader ma r`.
Exercise: For `Reader r`, implement instances of `Functor`, `Applicative`, and `Monad`.
-}
newtype Reader r a = Reader {runReader :: r -> a}
instance Functor (Reader r) where
fmap :: (a -> b) -> Reader r a -> Reader r b
fmap = unimplemented
instance Applicative (Reader r) where
pure :: a -> Reader r a
pure = unimplemented
(<*>) :: Reader r (a -> b) -> Reader r a -> Reader r b
(<*>) = unimplemented
instance Monad (Reader r) where
(>>=) :: Reader r a -> (a -> Reader r b) -> Reader r b
(>>=) = unimplemented
{-
I'll also give you a couple primitives for `Reader` as a small example of how to use the type. You can combine these to
form more interesting actions for testing your instances :)
- `askR` is an action that reads the immutable state and returns it.
- `localR` takes a function and uses it to transform the state, then runs a `Reader` action under the locally
transformed state.
Don't worry about the ugly names just yet. There's a good reason for that. You'll see soon :)
-}
askR :: Reader r r
askR = Reader{runReader = \r -> r}
localR :: (r -> r) -> Reader r a -> Reader r a
localR f ma = Reader{runReader = \r -> runReader ma (f r)}
{-
`asksR` transforms a function `f` into an action that returns `f` applied to the state.
Exercise: implement `asksR` using the two `Reader` primitives defined above.
-}
asksR :: (r -> a) -> Reader r a
asksR = unimplemented
{-
The Writer monad: an action of type `Writer w a` is one that produces a result of type `a` and appends a `w` to a log
using `(<>)` from `Semigroup`.
When you have a `Writer w a` action `ma`, you can run it with `runWriter ma` to get a pair of result and log.
For `Writer w`, implement an instance of `Functor`.
For `Writer w`, implement instances of `Applicative` and `Monad` given that `w` is a monoid.
-}
newtype Writer w a = Writer {runWriter :: (a, w)}
instance Functor (Writer w) where
fmap :: (a -> b) -> Writer w a -> Writer w b
fmap = unimplemented
instance (Monoid w) => Applicative (Writer w) where
pure :: Monoid w => a -> Writer w a
pure = unimplemented
(<*>) :: Monoid w => Writer w (a -> b) -> Writer w a -> Writer w b
(<*>) = unimplemented
instance (Monoid w) => Monad (Writer w) where
(>>=) :: Monoid w => Writer w a -> (a -> Writer w b) -> Writer w b
(>>=) = unimplemented
{-
And again, some primitives.
- `tellW` takes `w :: w` and turns it into an action that produces no meaningful result and appends `w` to the log.
- `listenW` transforms an action into a nearly-identical action that just produces the entire log as an additional
result.
- `passW` is a little wacky. It transforms an action that produces a result and a function into an action that produces
the same result but transforms the entire log using the function.
For example, `tell "foo" *> passW Writer{runWriter = ((), reverse)}` is an action that produces result `()` and log
`"oof"`.
-}
tellW :: w -> Writer w ()
tellW w = Writer{runWriter = ((), w)}
listenW :: Writer w a -> Writer w (a, w)
listenW ma = Writer{runWriter = ((x, log), log)}
where
(x, log) = runWriter ma
passW :: Writer w (a, w -> w) -> Writer w a
passW maf = Writer{runWriter = (x, f log)}
where
((x, f), log) = runWriter maf
{-
`listensW` is analogous to `asksR`. It extends `listenW` with the ability to invoke a function on the result before
returning it.
Exercise: implement `listensW` using the three `Writer` primitives defined above.
-}
listensW :: (w -> b) -> Writer w a -> Writer w (a, b)
listensW = unimplemented
{-
`censorW` allows arbitary transformation of the log after it's fully written.
Exercise: implement `censorW` using the three `Writer` primitives defined above.
-}
censorW :: (w -> w) -> Writer w a -> Writer w a
censorW = unimplemented
{-
The State monad: an action of type `State s a` is one that produces a result of type `a` and is allowed to read and
modify a mutable state of type `s`.
The state is passed through functions. Each stateful action is a transformation `oldState |-> (result, newState)`.
When you have a `State s a` action `ma`, you can run it on initial state `s :: s` with `runState s ma` to get a pair
of result and final state.
For `State s`, implement instances of `Functor`, `Applicative`, and `Monad`.
-}
newtype State s a = State {runState :: s -> (a, s)}
instance Functor (State s) where
fmap :: (a -> b) -> State s a -> State s b
fmap = unimplemented
instance Applicative (State s) where
pure :: a -> State s a
pure = unimplemented
(<*>) :: State s (a -> b) -> State s a -> State s b
(<*>) = unimplemented
instance Monad (State s) where
(>>=) :: State s a -> (a -> State s b) -> State s b
(>>=) = unimplemented
{-
State primitives, much like before:
- `getS` is an action that reads and returns the current state.
- `putS` turns a value of type `s` into an action that sets the state to that value.
-}
getS :: State s s
getS = State{runState = \s -> (s, s)}
putS :: s -> State s ()
putS s = State{runState = \_ -> ((), s)}
{-
`getsS` is analogous to `asksR` and `listensW`. No explanation necessary.
Exercise: implement `getsS` using the two `State` primitives defined above.
-}
getsS :: (s -> a) -> State s a
getsS = unimplemented
{-
`modifyS` performs an arbitrary modification on the state.
Exercise: implement `modifyS` using the two `State` primitives defined above.
-}
modifyS :: (s -> s) -> State s ()
modifyS = unimplemented
{-
The RWS monad: a `RWS r w s a` acts simultaneously like a `Reader r a`, a `Writer w a`, and a `State s a`.
For `RWS r w s`, implement an instance of `Functor`.
For `RWS r w s`, implement instances of `Applicative and `Monad` given that `w` is a monoid.
-}
newtype RWS r w s a = RWS {runRWS :: r -> s -> (a, s, w)}
instance Functor (RWS r w s) where
fmap :: (a -> b) -> RWS r w s a -> RWS r w s b
fmap = unimplemented
instance Applicative (RWS r w s) where
pure = unimplemented
(<*>) = unimplemented
instance Monad (RWS r w s) where
(>>=) :: RWS r w s a -> (a -> RWS r w s b) -> RWS r w s b
(>>=) = unimplemented
{-
Exercise: implement all the `Reader`, `Writer`, and `State` primitives for `RWS`.
-}
askRWS :: RWS r w s r
askRWS = unimplemented
localRWS :: (r -> r) -> RWS r w s a -> RWS r w s a
localRWS = unimplemented
tellRWS :: w -> RWS r w s ()
tellRWS = unimplemented
listenRWS :: RWS r w s a -> RWS r w s (a, w)
listenRWS = unimplemented
passRWS :: RWS r w s (a, w -> w) -> RWS r w s a
passRWS = unimplemented
getRWS :: RWS r w s s
getRWS = unimplemented
putRWS :: s -> RWS r w s ()
putRWS = unimplemented
{-
Exercise: verify your implementations of `asksR`, `listensW`, `censorW`, `getsS`, and `modifyS` by implementing
`asksRWS`, `listensRWS`, `censorRWS`, `getsRWS`, and `modifyRWS` in exactly the same way, just using a different set
of primitives.
-}
asksRWS :: (r -> a) -> RWS r w s a
asksRWS = unimplemented
listensRWS :: (w -> b) -> RWS r w s a -> RWS r w s (a, b)
listensRWS = unimplemented
censorRWS :: (w -> w) -> RWS r w s a -> RWS r w s a
censorRWS = unimplemented
getsRWS :: (s -> a) -> RWS r w s a
getsRWS = unimplemented
modifyRWS :: s -> RWS r w s ()
modifyRWS = unimplemented
{-
The Parser monad: an action of type `Parser t a` is one that consumes tokens of type `t` from a stream in order to
produce either an error of type `ParseError` or a result of type `a`.
For `Parser t`, implement instances of `Functor`, `Applicative`, `Alternative`, and `Monad`.
-}
data ParseError
= UnexpectedEof
| UnexpectedNotEof
| WrongToken
newtype Parser t a = Parser {runParser :: [t] -> ([t], Either ParseError a)}
instance Functor (Parser t) where
fmap :: (a -> b) -> Parser t a -> Parser t b
fmap = unimplemented
instance Applicative (Parser t) where
pure :: a -> Parser t a
pure = unimplemented
(<*>) :: Parser t (a -> b) -> Parser t a -> Parser t b
(<*>) = unimplemented
instance Alternative (Parser t) where
empty :: Parser t a
empty = unimplemented
(<|>) :: Parser t a -> Parser t a -> Parser t a
(<|>) = unimplemented
instance Monad (Parser t) where
(>>=) :: Parser t a -> (a -> Parser t b) -> Parser t b
(>>=) = unimplemented
{-
As always, here are some primitives:
- `anyTokenP` parses the next token if there is one and fails with `UnexpectedEof` otherwise.
- `tokenP` parses a specific token if it is next. It fails with `UnexpectedEof` if there is no next token and with
`WrongToken` if there is a next token but it is not the specific token `tokenP` expects. Notice that `tokenP` consumes
no input when it fails.
- `eofP` succeeds if there is no next token and fails without consuming any input otherwise.
-}
anyTokenP :: Parser t t
anyTokenP = Parser{runParser = go}
where
go [] = ([], Left UnexpectedEof)
go (x : xs) = (xs, Right x)
tokenP :: (Eq t) => t -> Parser t t
tokenP t = Parser{runParser = go}
where
go [] = ([], Left UnexpectedEof)
go (x : xs)
| x == t = (xs, Right x)
| otherwise = (x : xs, Left WrongToken)
eofP :: Parser t ()
eofP = Parser{runParser = go}
where
go [] = ([], Right ())
go (x : xs) = (x : xs, Left UnexpectedNotEof)
{-
Not as always, there are a lot more primitives that could be implemented here.
Open-ended exercise: think of more primitives and implement them. Feel free to extend `ParseError` as you see fit.
Extra credit: that `Eq t` constraint on `tokenP` is ugly. Replace `tokenP` with a simpler primitive, then implement
`tokenP` using that primitive.
-}
-----------------------------------------------------------------------------------------------------------------------
------------------------------------------------- Monad Transformers --------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
Now you understand monads! Enough to implement a few important monads, at least.
I'd like to call attention to one thing: `RWS`. It's pretty ugly, don't you think? And its implementation is pretty
much all repeated code from the individual `Reader`, `Writer`, and `State` monads. Furthermore, what if I only want
`Reader` and `State` functionality? Should I use `RWS r () s` and suffer the code smell of lugging a meaningless log
around everywhere? Should I implement `RS` and suffer the code smell of replicating the `Reader` and `State` code
_again_?
Nope, we can do better than either. What we'd really like is composable components that can add functionality to a
monad. Then `RS r s` is just the `Reader r` component and the `State s` component added to the trivial `Identity`
monad. `RWS r w s` is just `Writer w` added on top of that.
Let's examine the typeclass of _monad transformers_.
-}
class MonadTrans (t :: (* -> *) -> * -> *) where
lift :: (Monad m) => m a -> t m a
{-
A monad transformer is a type that transforms a type of kind `* -> *` (the same kind as monads) into another such type.
This class's vital `lift` method is constrained by `Monad m`, so as far as `MonadTrans` is concerned, we can only
meaningfully apply monad transformers to monads.
Similarly, a monad transformer should transform every monad into a monad. That is, in the type signature for `lift`
there are two monads named: `m` and `t m`.
Two laws:
- `lift (pure x) === pure x`
- `lift (m >>= f) === lift m >>= (\x -> lift (f x))`
-}
{-
Let's take a look at a trivial monad transformer. By convention, monad transformers' names end with a capital T.
-}
newtype IdentityT m a = IdentityT {runIdentityT :: m a}
{-
This type's kind checks out Apply it first to a monad of kind `* -> *` and then to a concrete type of kind `*`, and you
end up with a concrete type.
`IdentityT m a` is exactly like `m a`. It adds no functionality whatsoever.
Time to make it a transformer. Remember that a transformer must turn a monad into a monad, so we first define a `Monad`
instance for `IdentityT m`, when `m` is some arbitrary monad. This is easy; just use the existing `Monad` instance for
`m`.
-}
instance (Functor f) => Functor (IdentityT f) where
fmap f x = IdentityT{runIdentityT = fmap f (runIdentityT x)}
instance (Applicative f) => Applicative (IdentityT f) where
pure x = IdentityT{runIdentityT = pure x}
f <*> x = IdentityT{runIdentityT = runIdentityT f <*> runIdentityT x}
instance (Monad m) => Monad (IdentityT m) where
x >>= f = IdentityT{runIdentityT = runIdentityT x >>= \y -> runIdentityT (f y)}
instance MonadTrans IdentityT where
lift ma = IdentityT{runIdentityT = ma}
{-
In addition to all that, monad transformers will have some sort of mapping function. This is kinda hard to express in
the `MonadTrans` typeclass as a method named something like `mapT`, so we just do it outside.
-}
mapIdentityT :: (m a -> n b) -> IdentityT m a -> IdentityT n b
mapIdentityT f x = IdentityT{runIdentityT = f (runIdentityT x)}
{-
So that's what a monad transformer looks like.
How about a more interesting one now?
-}
newtype ReaderT r m a = ReaderT {runReaderT :: r -> m a}
{-
As for where to place the `m` in a monad transformer, I'm not quite sure. Just get a feel for transformers and use
intuition or something. Seems to be around the return type of the non-transformer variant often.
-}
instance (Functor f) => Functor (ReaderT r f) where
fmap f x = ReaderT{runReaderT = \r -> fmap f (runReaderT x r)}
instance (Applicative f) => Applicative (ReaderT r f) where
pure x = ReaderT{runReaderT = \r -> pure x}
f <*> x = ReaderT{runReaderT = \r -> runReaderT f r <*> runReaderT x r}
instance (Monad m) => Monad (ReaderT r m) where
x >>= f = ReaderT{runReaderT = \r -> runReaderT x r >>= \y -> runReaderT (f y) r}
instance MonadTrans (ReaderT r) where
lift ma = ReaderT{runReaderT = \_ -> ma}
mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT f x = ReaderT{runReaderT = \r -> f (runReaderT x r)}
{-
Spooky stuff, I know. But it's quite patterned! Note the striking similarity to `IdentityT`'s instances. I've pretty
much just replaced `runIdentityT e` with `runReaderT e r` and added the `\r ->` where needed.
This will come pretty naturally once you have some practice with monads behind you.
We can also define the `Reader` primitives for `ReaderT`...
-}
askRT :: (Monad m) => ReaderT r m r
askRT = ReaderT{runReaderT = \r -> pure r}
localRT :: (r -> r) -> ReaderT r m a -> ReaderT r m a
localRT f x = ReaderT{runReaderT = \r -> runReaderT x (f r)}
{-
... and the nonprimitives in terms of the primitives.
Exercise: implement `asksRT` using the two `ReaderT` primitives defined above.
-}
asksRT :: (Monad m) => (r -> a) -> ReaderT r m a
asksRT f = unimplemented
{-
Want to see an alternative definition of `Reader`?
-}
type Reader' r a = ReaderT r Identity a
askR' :: Reader' r r
askR' = askRT
localR' :: (r -> r) -> Reader' r a -> Reader' r a
localR' = localRT
{-
Take the trivial identity monad and add some Reader functionality on top of it. This definition is equivalent to the
simpler definition above. Nifty, huh?
Now I'll throw you into the deep end. Here's `WriterT`.
-}
newtype WriterT w m a = WriterT {runWriterT :: m (a, w)}
{-
Exercise: implement
- a `Functor` instance for `WriterT w f`, given that `f` is a functor
- an `Applicative` instance for `WriterT w f`, given that `f` is an applicative and `w` is a monoid
- a `Monad` instance for `WriterT w m`, given that `m` is a monad and `w` is a monoid
- a `MonadTrans` instance for `WriterT w`, given that `w` is a monoid
-}
instance (Functor f) => Functor (WriterT w f) where
fmap :: Functor f => (a -> b) -> WriterT w f a -> WriterT w f b
fmap = unimplemented
instance (Applicative f, Monoid w) => Applicative (WriterT w f) where
pure :: (Applicative f, Monoid w) => a -> WriterT w f a
pure = unimplemented
(<*>) :: (Applicative f, Monoid w) => WriterT w f (a -> b) -> WriterT w f a -> WriterT w f b
(<*>) = unimplemented
instance (Monad m, Monoid w) => Monad (WriterT w m) where
(>>=) :: (Monad m, Monoid w) => WriterT w m a -> (a -> WriterT w m b) -> WriterT w m b
(>>=) = unimplemented
instance (Monoid w) => MonadTrans (WriterT w) where
lift :: (Monoid w, Monad m) => m a -> WriterT w m a
lift = unimplemented
{-
Exercise: implement `mapWriterT`. I've given you the type.
-}
mapWriterT :: (m (a, v) -> n (b, w)) -> WriterT v m a -> WriterT w n b
mapWriterT = unimplemented
{-
Exercise: implement the `Writer` primitives for `WriterT`.
- `tellWT`
- `listenWT`
- `passWT`
-}
tellWT :: (Monad m) => w -> WriterT w m ()
tellWT w = unimplemented
listenWT :: (Monad m) => WriterT w m a -> WriterT w m (a, w)
listenWT ma = unimplemented
passWT :: (Monad m) => WriterT w m (a, w -> w) -> WriterT w m a
passWT maf = unimplemented
{-
Exercise: implement the `Writer` nonprimitives for `WriterT` in terms of the primitives.
- `listensWT`
- `censorWT`
-}
listensWT :: (Monad m) => (w -> b) -> WriterT w m a -> WriterT w m (a, b)
listensWT f x = unimplemented
censorWT :: (Monad m) => (w -> w) -> WriterT w m a -> WriterT w m a
censorWT f m = unimplemented
{-
Very nice. And just like before, we can now add `WriterT w` on top of `Identity` to produce an implementation of the
`Writer` monad equivalent to the one introduced before.
One more, then it'll be time to get into using monad transformers.
-}
newtype StateT s m a = StateT {runStateT :: s -> m (a, s)}
{-
Exercise: implement
- a `Functor` instance for `StateT s f`, given that `f` is a functor
- an `Applicative` instance for `StateT s f`, given that `f` is an applicative
- a `Monad` instance for `StateT s m`, given that `m` is a monad
- a `MonadTrans` instance for `StateT s`
-}
instance (Functor f) => Functor (StateT s f) where
fmap :: Functor f => (a -> b) -> StateT s f a -> StateT s f b
fmap = unimplemented
instance (Applicative f) => Applicative (StateT s f) where
pure :: Applicative f => a -> StateT s f a
pure = unimplemented
(<*>) :: Applicative f => StateT s f (a -> b) -> StateT s f a -> StateT s f b
(<*>) = unimplemented
instance (Monad m) => Monad (StateT s m) where
(>>=) :: Monad m => StateT s m a -> (a -> StateT s m b) -> StateT s m b
(>>=) = unimplemented
instance MonadTrans (StateT s) where
lift :: Monad m => m a -> StateT s m a
lift = unimplemented
{-
Exercise: implement `mapStateT`. I've given you the type.
-}
mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
mapStateT = unimplemented
{-
Exercise: implement the `State` primitives for `StateT`.
- `getST`
- `putST`
-}
getST :: (Monad m) => StateT s m s
getST = unimplemented
putST :: (Monad m) => s -> StateT s m ()
putST = unimplemented
{-
Exercise: implement the `State` nonprimitives for `StateT` in terms of the primitives.
- `getsST`
- `modifyST`
-}
getsST :: Monad m => (s -> a) -> StateT s m a
getsST = unimplemented
modifyST :: Monad m => (s -> s) -> StateT s m ()
modifyST = unimplemented
{-
Whew, that was a lot. Well done getting through it all!
Remember why we got into monad transformers in the first place? It was the unsatisfying `RWS` implementation. I think
it's about time we finally fix that. It should be as easy as stacking three monad transformers on top of `Identity`.
-}
type RWS' r w s a = ReaderT r (WriterT w (StateT s Identity)) a
{-
We could make that type alias even more elegant by dropping the `a` from both sides. Types can eta-convert too :)
Since a `RWS' r w s a` is a `ReaderT r m a` for some `m`, the reader functionality is there already.
The `Monoid w` constraint feels a little funky, but without it `WriterT w m` is not a monad and neither, therefore, is
`RWS' r w s`.
-}
askRWS' :: (Monoid w) => RWS' r w s r
askRWS' = askRT
localRWS' :: (Monoid w) => (r -> r) -> RWS' r w s a -> RWS' r w s a
localRWS' = localRT
{-
Writer functionality is in the `Writer w`, underneath the `Reader r`. Fortunately, `Reader r` is a monad transformer.
We can just lift/map stuff up through it!
-}
tellRWS' :: (Monoid w) => w -> RWS' r w s ()
tellRWS' w = lift (tellWT w)
listenRWS' :: (Monoid w) => RWS' r w s a -> RWS' r w s (a, w)
listenRWS' ma = mapReaderT listenWT ma
passRWS' :: (Monoid w) => RWS' r w s (a, w -> w) -> RWS' r w s a
passRWS' maf = mapReaderT passWT maf
{-
And similarly, to bring state functionality to the top, we just lift/map twice to get through two monad transformers.
-}
getRWS' :: (Monoid w) => RWS' r w s s
getRWS' = lift (lift getST)
putRWS' :: (Monoid w) => s -> RWS' r w s ()
putRWS' s = lift (lift (putST s))
{-
There we go! That's a more `RWS` implementation complete. If we now want only two (or one, or zero... or FOUR?) pieces
of functionality, it's really easy to define a type alias for a custom transformer stack, throw a little `lift` and
`mapWhateverT` at it, and have a nice monad that does exactly what we want. And all at no runtime cost.
-}
{-
Oh, yeah. I should mention that monad transformers compose to create monad transformers. Let's make that `RWS'`
definition a little bit more abstract.
-}
newtype RWST r w s m a = RWST {runRWST :: ReaderT r (WriterT w (StateT s m)) a}
instance (Functor f) => Functor (RWST r w s f) where
fmap f x = RWST{runRWST = fmap f (runRWST x)}
instance (Applicative f, Monoid w) => Applicative (RWST r w s f) where
pure x = RWST{runRWST = pure x}
f <*> x = RWST{runRWST = runRWST f <*> runRWST x}
instance (Monad f, Monoid w) => Monad (RWST r w s f) where
x >>= f = RWST{runRWST = runRWST x >>= \y -> runRWST (f y)}
instance (Monoid w) => MonadTrans (RWST r w s) where
lift x = RWST{runRWST = lift (lift (lift x))}
mapRWST :: (m ((a, v), s) -> n ((b, w), s)) -> RWST r v s m a -> RWST r w s n b
mapRWST f x = RWST{runRWST = mapReaderT (mapWriterT (mapStateT f)) (runRWST x)}
type RWS'' r w s a = RWST r w s Identity a
{-
One final note before we wrap up this section on monad transformers.
If you look closely, you'll see that a lot of the declarations in this section (and a couple in the last) give types
that are less general than they need to be.
[mtl](https://hackage.haskell.org/package/mtl) and [transformers](https://hackage.haskell.org/package/transformers)
bear the blame for that. If I knew this stuff a little better, I would either have an explanation for why those
libraries give overly specific types or be working to update them with more relaxed types. This sort of stuff really
should be as generic as possible, I think.
Exercise: find the declarations I'm talking about and figure out their minimally restrictive types.
-}
{-
On a related note, I did a little cleanup early on. There is some stuff from the Haskell standard library that is more
specific than what I introduced:
- `(>>)` is just `(*>)` with a `Monad` constraint
- `return` is just `pure` with a `Monad` constraint
- `mapM` is just `traverse` with a `Monad` constraint
- `mappend` is just `(<>)` with a `Monoid` constratint
- probably some others
That's all from the early days of Haskell, before `Applicative` was a requirement for `Monad` and before `Semigroup`
was a requirement for `Monoid`. You'll still see it all in code even now in 2023. I don't like using the less generic
forms. Some people do.
-}
{-
Ooh, almost forgot to write some exercises.
Exercise: Implement a monad named `Bistate` equivalent to `Bistate'` given below. Use monad transformers instead of the
`(,)` type to maintain two states at once. Implement the primitives for `Bistate`.
-}
type Bistate' s t a = State (s, t) a
getL' :: Bistate' s t s
getL' = getsS fst
getR' :: Bistate' s t t
getR' = getsS snd
putL' :: s -> Bistate' s t ()
putL' s = getR' >>= \t -> putS (s, t)
putR' :: t -> Bistate' s t ()
putR' t = getL' >>= \s -> putS (s, t)
{-
Exercise: Implement `ParserT` as a monad transformer stack.
You will have to devise and inplement another monad transformer not yet mentioned.
-}
-----------------------------------------------------------------------------------------------------------------------
--------------------------------------------------------- MTL ---------------------------------------------------------
-----------------------------------------------------------------------------------------------------------------------
{-
MTL stands for Monad Transformer Library or something. It's a pretty popular library that makes monad transformer
stacks _extremely_ pleasant to use. The key is typeclasses with functional dependencies.
Before functional dependencies, we have to talk about multi-parameter typeclasses. They're pretty straightfoward.
Imagine typeclasses that express relationships between types rather than properties of individual types.
-}
class Genred a b where
genre :: a -> b
{-
It's not enough to say that a type `a` is genred. You have to say that it's genred by a certain genre type `b`.
-}
data BookGenre = Mystery | SciFi | Fantasy
data Author = Author {authorName :: String, authorGenre :: BookGenre}
data MusicGenre = Classical | Rap | Metal
data Musician = Musician {musicianName :: String, musicianGenre :: MusicGenre}
instance Genred Author BookGenre where
genre Author{authorGenre = g} = g
instance Genred Musician MusicGenre where
genre Musician{musicianGenre = g} = g
{-
Like I said, pretty straightforward.
Functional dependencies extend this. They tell the compiler that some subset of the parameters can be deduced from the
others. For example, here we know that `Author`s always have genres of type `BookGenre` and `Musician`s have genres of
type `MusicGenre`. So we can give `Genre` a functional dependency:
-}
class Genred' a b | a -> b where
genre' :: a -> b
instance Genred' Author BookGenre where
genre' Author{authorGenre = g} = g
instance Genred' Musician MusicGenre where
genre' Musician{musicianGenre = g} = g
{-
Functional dependencies let the compiler get away with doing a little less when deducing types, since they tell the
compiler explicitly some types that can easily be deduced from others. They give some more expressive power, too, in a
way that's really hard to describe without going off on a long tangent. Instead, I'll just refer you to a nice little
blog post: [Typing the Technical Interview](https://aphyr.com/posts/342-typing-the-technical-interview).
Enough of that. You've seen functional dependencies now. It's time to see what MTL does with them.
Behold `MonadReader`.
-}
class (Monad m) => MonadReader r m | m -> r where
ask :: m r
local :: (r -> r) -> m a -> m a
{-
A type satisfying `MonadReader r` is a monad with `Reader r`-like capabilities. And indeed:
-}
instance MonadReader r (Reader r) where
ask = askR
local = localR
{-
We can do the same for `ReaderT`, too:
-}
instance (Monad m) => MonadReader r (ReaderT r m) where
ask = askRT
local = localRT
{-
At this point, every transformer stack with `ReaderT r` as its outermost layer is an instance of `MonadReader`. But we
want monad transformers anywhere in the stack to provide their capabilities to the entire stack!
This brings us to one ugly truth in MTL: the n^2 instances problem. Each capability we want to be able to bestow upon a
transformer stack comes as a bundle of a monad transformer and a typeclass. `ReaderT` and `MonadReader` here, for
example. And each typeclass needs an instance for each transformer. Yikes.
It won't be too bad here with just reader, writer, and state monads. In the real world, though, code size balloons:
https://github.com/haskell/mtl/blob/afd548d9f6f45eae241bc9f1683ccf09c279e275/Control/Monad/Reader/Class.hs#L139-L193
And it's really repetitive, too. Quite nice for a user, but not so much for a library implementer.
Ah, and these instance declarations also need the UndecidableInstances language extension.
Anyway, let's go ahead and lift `MonadReader` instances through `WriterT` and `StateT` transformers.
-}
instance (MonadReader r m, Monoid w) => MonadReader r (WriterT w m) where
ask = lift ask
local f = mapWriterT (local f)
instance (MonadReader r m) => MonadReader r (StateT s m) where
ask = lift ask
local f = mapStateT (local f)
{-
Yeah, it's pretty much all exactly like that.
-}
class (Monad m, Monoid w) => MonadWriter w m | m -> w where
tell :: w -> m ()
listen :: m a -> m (a, w)
pass :: m (a, w -> w) -> m a
{-
Exercise: implement the `MonadWriter w` instance for `WriterT w m`, given that `m` is a monad and `w` is a monoid.
-}
instance (Monad m, Monoid w) => MonadWriter w (WriterT w m) where
tell :: (Monad m, Monoid w) => w -> WriterT w m ()
tell = unimplemented
listen :: (Monad m, Monoid w) => WriterT w m a -> WriterT w m (a, w)
listen = unimplemented
pass :: (Monad m, Monoid w) => WriterT w m (a, w -> w) -> WriterT w m a
pass = unimplemented
{-
Exercise: implement the `MonadWriter w` instances for `ReaderT r m` and `StateT s m`, given that `m` satisfies
`MonadWriter w`.
-}
instance (MonadWriter w m) => MonadWriter w (ReaderT r m) where
tell :: MonadWriter w m => w -> ReaderT r m ()
tell = unimplemented
listen :: MonadWriter w m => ReaderT r m a -> ReaderT r m (a, w)
listen = unimplemented
pass :: MonadWriter w m => ReaderT r m (a, w -> w) -> ReaderT r m a
pass = unimplemented
instance (MonadWriter w m) => MonadWriter w (StateT s m) where
tell :: MonadWriter w m => w -> StateT s m ()
tell = unimplemented
listen :: MonadWriter w m => StateT s m a -> StateT s m (a, w)
listen = unimplemented
pass :: MonadWriter w m => StateT s m (a, w -> w) -> StateT s m a
pass = unimplemented
{-
Just a little more slog to get through, and then we'll be able to reap the benefits of these MTL-style typeclasses.
-}
class (Monad m) => MonadState s m | m -> s where
get :: m s
put :: s -> m ()
{-
Exercise: implement the `MonadState s` instance for `StateT s m`, given that `m` is a monad.
-}
instance (Monad m) => MonadState s (StateT s m) where
get :: Monad m => StateT s m s
get = unimplemented
put :: Monad m => s -> StateT s m ()
put = unimplemented
{-
Exercise: implement the `MonadState s` instances for `ReaderT r m` and `WriterT w m`, given that `m` satisfies
`MonadState s` and `w` is a monoid.
-}
instance (MonadState s m) => MonadState s (ReaderT r m) where
get :: MonadState s m => ReaderT r m s
get = unimplemented
put :: MonadState s m => s -> ReaderT r m ()
put = unimplemented
instance (MonadState s m, Monoid w) => MonadState s (WriterT w m) where
get :: (MonadState s m, Monoid w) => WriterT w m s
get = unimplemented
put :: (MonadState s m, Monoid w) => s -> WriterT w m ()
put = unimplemented
{-
And that's it!
Let's put these typeclasses to use, starting with one final visit to `RWS`. We implemented `RWST` in terms of
`ReaderT`, `WriterT`, and `StateT` earlier. Why not `MonadRWS` in terms of `MonadReader`, `MonadWriter`, and
`MonadState`?
Turns out this is extremely easy. Commas in parentheses serve as conjunction for constraints. Oh, and because
constraints are themselves just types, we can define `MonadRWS` with a type alias rather than as a typeclass of its
own.
-}
type MonadRWS r w s m = (MonadReader r m, MonadWriter w m, MonadState s m)
{-
Exercise: define an action that reads the field `password` of an immutable user and sets a mutable state to the length
of that password.
This action must work for both `ReaderT User (StateT Integer Identity)` and `StateT Integer (ReaderT User Identity)`,
as well as for any other transformer stack for which it could reasonably work.
-}
data User = User {username :: String, password :: String}
putPasswordLength :: Unimplemented
putPasswordLength = unimplemented
{-
Congratulations, you've made it through! I hope this has been helpful.
I have one last exercise before you go. See all those HLINT pragmas at the top of the file? Get yourself a working
installation of [HLS](https://github.com/haskell/haskell-language-server) and delete those pragmas. I deliberately
wrote a lot of the code in a style that I thought would be more approachable to newcomers, but HLS has some very good
suggestions for making it look more like what a seasoned Haskell veteran might write.
Pay attention to the fixes it proposes and make sure you understand what's happening and why. Then you're finally free
of me!
-}
@khuldraeseth
Copy link
Author

This started as a general guide to typeclasses (and a bit of syntax) in Haskell, but then I got way too into it. Everyone has to write a monad guide at some point, right? Now I've gotten mine out of the way. Enjoy!

I know naming and formatting conventions changed a few times over the course of the file. Planning on going through at some point and making things a little more consistent.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment