Resuming My Journey Toward an Understanding of Haskell Monads (Yet Again)
Table of Contents
1 Type creation (data, type, newtype)
The type keyword is for making type synonyms.
The newtype keyword is for taking existing types and wrapping them in new types, mostly so that it's easier to make them instances of certain type classes.
The data keyword is for making your own data types and with them, you can go hog wild.
1.1 Data
data Maybe a = Nothing | Just a
Note: "value constructor" is on the right side of the "=" sign. "Type constructor" is on the left side.
1.1.1 Record syntax
data Car = Car {company :: String, model :: String, year :: Int} deriving (Show) carAge :: Car -> Int carAge car = 2019 - year car -- Hard-coding current year, so what? ghci> Car {company="Ford", model="Mustang", year=1967} Car {company = "Ford", model = "Mustang", year = 1967} λ *Car> :t year year :: Car -> Int
Each of the "fields" is actually a function that returns the value of that field. (See the use of
year
in carAge
.)
1.2 Type synonym (alias)
type String = [Char]
The [Char] and String types are equivalent and interchangeable.
1.3 Newtype
newtype Pair b a = Pair { getPair :: (a,b) }
The newtype keyword in Haskell is made exactly for these cases when we want to just take one type and wrap it in something to present it as another type.
When you make a new type from an existing type by using the newtype keyword, you can only have one value constructor and that value constructor can only have one field. [Example above has two-parameter type constructor, but value constructor has only one parameter (a tuple).]
We can also use the deriving keyword with newtype just like we would with data. We can derive instances for Eq, Ord, Enum, Bounded, Show and Read. If we derive the instance for a type class, the type that we're wrapping has to be in that type class to begin with. It makes sense, because newtype just wraps an existing type.
2 Functor
2.1 fmap :: (a -> b) -> f a -> f b
Where 'f' in this case represents a functor, not a function.
2.2 Functor laws
Implementations of fmap SHOULD follow these laws.
2.2.1 fmap id = id
2.2.2 fmap (f . g) = fmap f . fmap g
3 Applicative functor
class (Functor f) => Applicative f where
3.1 pure :: a -> f a
Turns an 'a' into an 'f a'. I.e. 'pure a' yields 'f a'.
3.2 (<*>) :: f (a -> b) -> f a -> f b
Contrast with 'fmap'. Can't chain this operator because left operand is function within functor (f (a -> b), but output is not (f b).
3.3 <$>
Control.Applicative exports a function called <$>, which is just fmap as an infix operator.
(<$>) :: (Functor f) => (a -> b) -> f a -> f b f <$> x = fmap f x
Same precedence as <*>, and both are left-associative. (Meaning: well, nothing in this case, because the operands are different types.)
3.4 Examples
3.4.1 Maybe
instance Applicative Maybe where pure = Just Nothing <*> _ = Nothing (Just f) <*> something = fmap f something
3.4.2 Lists
instance Applicative [] where pure x = [x] fs <*> xs = [f x | f <- fs, x <- xs]
"Cross product" of list of functions with list of values.
3.4.3 IO
instance Applicative IO where pure = return a <*> b = do f <- a x <- b return (f x)
3.4.4 ((->) r)
instance Applicative ((->) r) where pure x = (\_ -> x) f <*> g = \x -> f x (g x)
λ Prelude> (+) <$> (3+) <*> (100*) $ 5 508 λ Prelude> (\x y z -> [x,y,z]) <$> (3+) <*> (2*) <*> (/2) $ 5 [8.0,10.0,2.5] λ Prelude> :t (\x y z -> [x,y,z]) (\x y z -> [x,y,z]) :: t -> t -> t -> [t] λ Prelude> :t (\x y z -> [x,y,z]) <$> (3+) (\x y z -> [x,y,z]) <$> (3+) :: Num t => t -> t -> t -> [t] λ Prelude> :t (\x y z -> [x,y,z]) <$> (3+) <*> (2*) (\x y z -> [x,y,z]) <$> (3+) <*> (2*) :: Num a => a -> a -> [a] λ Prelude> :t (\x y z -> [x,y,z]) <$> (3+) <*> (2*) <*> (2-) (\x y z -> [x,y,z]) <$> (3+) <*> (2*) <*> (2-) :: Num a => a -> [a]
The only thing that matters here is the type of the return value of the function: [a], in the latter case. So, because precedence is the same for <$> and <*>, and they're both left-associative, we apply them from left to right and get different-arity functions each time, but we don't care, because the return type is always [a].
So, in the case of (\x y z -> [x,y,z]) <$> (3+)
, the input is a plain function. It happens to
take a t and return something scary (a 2-arg function that returns a list), but we don't care,
it's a plan function.
Then we apply that lambda with <$> to (3+) and we get something else horrific (a 3-arg function
that returns a list), but we don't care, because it ends with "returns a list", which is that (
(->) r)
we started with, so we're happy, we're in Functor-land.
We keep tacking on <*> operators (with right-hand operands), and we keep getting functions that return [a], so we're still in the same Functor.
Eventually, we get down to a function that takes a single argument and returns a list, and we apply that function to a number (5).
In execution, in the definition of Applicative for the case of functions, f <*> g
above, we
have this weird syntax, f x (g x)
. f and g are both functions that return an r (a list
of a's, in this case). We apply f to x and the result is a function, and then we apply
that function to the result of g x
. So, applying f to x basically "eats" an argument,
producing a function of one less argument than f had (but also at least one argument that
can be the result of g x
).
So, the question "how many <*>s can we have?" is "as many as are necessary to satisfy the function on the left side of <$>". Actually, we need exactly that many.
3.5 Applicative [Functor] laws
3.5.1 pure f <*> x = fmap f x
Most important.
(f
is a function here, I believe.)
Breakdown:
pure f
returns your applicative functor (the one you're defining when you implement pure
) containing the
function f
.
Then, <*>
is used to apply the applicative functor to x. That should be the same as calling fmap f x
.
3.5.2 Others
pure id <*> v = v pure (.) <*> u <*> v <*> w = u <*> (v <*> w) pure f <*> pure x = pure (f x) u <*> pure y = pure ($ y) <*> u
3.6 (Continue at "Useful Functions for Applicatives")
4 Monoid
(Defined in Data.Monoid)
class Monoid m where
4.1 mempty :: m
Identity value.
4.2 mappend :: m -> m -> m
4.3 mconcat :: [m] -> m
mconcat = foldr mappend mempty
(Default implementation)
4.4 Monoid laws
mempty `mappend` x = x -- identity x `mappend` mempty = x -- identity (x `mappend` y) `mappend` z = x `mappend` (y `mappend` z) -- associativity
4.5 "Any" type instance of "Monoid"
newtype Any = Any { getAny :: Bool } deriving (Eq, Ord, Read, Show, Bounded) instance Monoid Any where mempty = Any False Any x `mappend` Any y = Any (x || y)
"Any" is just "Bool" with some specific behavior. getAny
is kind of a cast operator.
ghci> getAny . mconcat . map Any $ [False, False, False, True] True
(map Any
happens first (function application has highest precedence), then all the .s (function composition operator) yield a single function, which is applied ($, lowest precedence) to the list.)
5 Foldable
5.1 foldMap :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
5.2 Sample application: folding a tree
data Tree a = Empty | Node a (Tree a) (Tree a) deriving (Show, Read, Eq) import qualified Foldable as F instance F.Foldable Tree where foldMap f Empty = mempty foldMap f (Node x l r) = F.foldMap f l `mappend` f x `mappend` F.foldMap f r testTree = Node 5 (Node 3 (Node 1 Empty Empty) (Node 6 Empty Empty) ) (Node 9 (Node 8 Empty Empty) (Node 10 Empty Empty) ) ghci> getAny $ F.foldMap (\x -> Any $ x == 3) testTree True
So, the "a -> m
" function is the Any
value constructor applied to the Boolean value x =
3=, yielding an Any
, which is a Monoid. Then we apply foldMap
to essentially a tree of Booleans (as defined for Tree) and get a single result.
6 Monad
Most important function is >>=
("bind"). 2nd argument is most important: a function that takes a
"raw" argument and returns a Monad.
(>>=) :: m a -> (a -> m b) -> m b
class Monad m where return :: a -> m a -- Like Applicative 'pure' (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b x >> y = x >>= \_ -> y fail :: String -> m a -- Primarily used internally by Haskell fail msg = error msg
Learn You a Haskell says: "Every monad is an applicative functor, even if the Monad class
declaration doesn’t say so." But this isn't true at this point; apparently Applicative
is now
formally declared to be a prerequisite for Monad
.
6.1 Maybe as Monad
instance Monad Maybe where return x = Just x Nothing >>= f = Nothing Just x >>= f = f x fail _ = Nothing
Implementation of >>= is particularly important.
6.2 "do" notation
ghci> Just 3 >>= (\x -> Just "!" >>= (\y -> Just (show x ++ y))) Just "3!"
x gets 3; y gets "!"; it's all pulled together in the final expression (Just (show x ++ y)
).
Note that the above can be written w/out so many parens, as follows:
Just 3 >>= \x -> Just "!" >>= \y -> Just (show x ++ y)
Because lamda expression definition goes to the end of the line. So, the lambda expression beginning with "\x"
includes the lambda subexpression beginning with "\y". This is why x
remains "in scope" in the 2nd lambda
containing Just (show x ++ y)
.
Rewrite, with line breaks:
foo :: Maybe String foo = Just 3 >>= (\x -> -- x gets 3 Just "!" >>= (\y -> -- y gets "!" Just (show x ++ y))) -- final value (obviously)
Rewrite, with "do" notation, so we don't need all those nested lambdas:
foo :: Maybe String foo = do x <- Just 3 y <- Just "!" Just (show x ++ y)
There's still a ">>=" between every line, so if something evaluates to Nothing (since we're in
the Maybe
monad), the Nothing will propagate on through.
6.2.1 Failure in "do"
When pattern matching fails in a do expression, the fail function is called. It's part of the Monad type class and it enables failed pattern matching to result in a failure in the context of the current monad instead of making our program crash. Its default implementation is this:
fail :: (Monad m) => String -> m a fail msg = error msg
So by default it does make our program crash, but monads that incorporate a context of possible failure (like Maybe) usually implement it on their own. For Maybe, its implemented like so:
fail _ = Nothing
In the following:
wopwop :: Maybe Char wopwop = do (x:xs) <- Just "" -- pattern match will fail return x
We wind up injecting Nothing
, so the attempt to invoke return x
is short-circuited by the
Nothing
(because of the implicit ">>=" between each line).
Note that, for the List monad, failure is an empty list, and the attempt to use ">>=" on an empty list will return an empty list, no matter what function we're attempting to apply. (See Knight's Quest, below.)
6.3 Stricter interpretation of "do"
The do syntax provides a simple shorthand for chains of monadic operations. The essential translation of do is captured in the following two rules:
do e1 ; e2 = e1 >> e2 do p <- e1; e2 = e1 >>= \p -> e2
7 MonadPlus
The MonadPlus type class is for monads that can also act as monoids.
class Monad m => MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a
8 Knight's Quest (List as Monad, Nondeterminism)
8.1 List classes
8.1.1 Functor
instance Functor [] where fmap = map
8.1.2 Applicative Functor
instance Applicative [] where pure x = [x] fs <*> xs = [f x | f <- fs, x <- xs]
f
is the a -> b
part of the Applicative definition. In the following definition
(<*>) :: fr (a -> b) -> fr a -> fr b
fr
is the "list-ifier" []
. So, we have a list of functions (a -> b)
, and a list of
a's, and the result is a list of b's, where each b
is generated by applying one of the f's
to one of the a's.
So, it's kind of a cross-product between functions and arguments.
8.1.3 Monad
instance Monad [] where return x = [x] xs >>= f = concat (map f xs) fail _ = []
(>>) has a default implementation:
(>>) :: m a -> m b -> m b x >> y = x >>= \_ -> y
So, in the definition of class Monad, m a
is a list of a's. And f
is a function from a
single a
to a list of results (a -> m b). Since we apply a function that generates a list
to a list of arguments (m a
is [a]
), we wind up with a list of lists, so we use concat
to
flatten them out into a single list.
So, if the input m a
(a.k.a. xs
) is the empty list (which is the same as fail
, I guess),
the result will also be the empty list, no matter what f
is.
Finally, for >>
, if the "input" x is the empty list (fail
, again, I guess), then the
function \_ -> y
applied to the empty list will be the empty list, not a bunch of y's (or even
a single one). It doesn't matter that the function doesn't care about its input (_
), there's
nothing to apply it to.
8.1.3.1 Application
ghci> [1,2] >>= \n -> ['a','b'] >>= \ch -> return (n, ch) [(1,'a'),(1,'b'),(2,'a'),(2,'b')]
Can be rewritten as
[1,2] >>= (\n -> ['a','b'] >>= (\ch -> return (n, ch)))
This is because lambda expressions go to the end of the line, so the parens aren't necessary. (See "do" notation.)
So, we are mapping 1 to [a,b], then 2 to [a,b] (so we get two occurrences of [a,b], but we also still have the 1 and 2 in scope). Then we map each of a, b to a function that uses return
(pure
) to put a single tuple (n, ch) into a one-element list, and then those all get concat'd into a list of tuples.
8.1.3.2 Laws (Invariants?)
8.1.3.2.1 Left identity: return x >>= f is the same as f x
8.1.3.2.2 Right identity: m >>= return is the same as simply m.
8.1.3.2.3 Associativity
when we look at the law as a law of compositions, it states that f <=< (g <=< h) should be the same as (f <=< g) <=< h. This is just another way of saying that for monads, the nesting of operations shouldn’t matter.
8.1.4 MonadPlus, guard
instance MonadPlus [] where mzero = [] mplus = (++)
(Kind of duh.)
guard :: (MonadPlus m) => Bool -> m () guard True = return () guard False = mzero
All default implementations. The interpretation for List:
m ()
: m
is List, so m ()
is really [()]
.
return
is like pure
: a "minimal wrapping" of its argument. In this case, return ()
is
really [()]
, a list containing a single empty tuple (the empty tuple, ()
is also known as
"unit").
mzero
is just the empty list.
So, for Lists, guard
returns either [()]
or just []
.
8.1.4.1 Sample application(s)
ghci> guard (5 > 2) >> return "cool" :: [String] ["cool"] ghci> guard (1 > 2) >> return "cool" :: [String] []
If guard succeeds, the result contained within it is an empty tuple. So then, we use >> to ignore that empty tuple and present something else as the result. However, if guard fails, then so will the return later on, because feeding an empty list to a function with >>= always results in an empty list.
8.2 DONE Solution & how it works
- CLOSING NOTE
I think I've explained this to myself to death now.
type KnightPos = (Int,Int) moveKnight :: KnightPos -> [KnightPos] moveKnight (c,r) = do (c',r') <- [(c+2,r-1),(c+2,r+1),(c-2,r-1),(c-2,r+1) ,(c+1,r-2),(c+1,r+2),(c-1,r-2),(c-1,r+2) ] guard (c' `elem` [1..8] && r' `elem` [1..8]) return (c',r') in3 :: KnightPos -> [KnightPos] in3 start = do first <- moveKnight start second <- moveKnight first moveKnight second canReachIn3 :: KnightPos -> KnightPos -> Bool canReachIn3 start end = end `elem` in3 start
See the code at https://github.com/JohnL4/LearnHaskell/blob/main/KnightMoves.lhs (warning: literate
Haskell, a crazy mixture of LaTeX and Haskell that I may never repeat) and the writeup at
KnightMoves.pdf (the result of processing KnightMoves.lhs
with LaTeX) somewhere around here.
This is not how I'd normally write moveKnight
, but Lipovača is enamored at this point with the
possibility of nondeterminism being the result: moveKnight
returns an indeterminate answer as to
where the knight goes next.
The reason I was so taken aback by this function is that it's supposed to return a list of possible
moves, but, instead, (a) it returns only a single move (c',r')
, and (b) even if we realize that,
for the List
monad, return
does result in a list, it still looks like the list only contains
one position, instead of a list of many positions. It seems to me that use of this idiom requires
an immediate (deep?) understanding of how the List
monad functions. Maybe that'll become second
nature later; I have no way of knowing now.
The alternative definition below feels much more natural to me. (Although the implementation of
in3
also seems a little weird. Maybe I just need more practice.)
8.2.1 Alternatively (and maybe better?), could also write moveKnight as follows
moveKnight :: KnightPos -> [KnightPos] moveKnight (c,r) = filter onBoard [(c+2,r-1),(c+2,r+1),(c-2,r-1),(c-2,r+1) ,(c+1,r-2),(c+1,r+2),(c-1,r-2),(c-1,r+2) ] where onBoard (c,r) = c `elem` [1..8] && r `elem` [1..8]
But it doesn't make any difference.