On this page:
3.1 Mastermind in Haskell
3.2 Oh right, types are complicated
3.2.1 Monads, functors, and applicative functors
3.3 It’s types all the way down
3.3.1 Build your own instances… maybe?
3.4 Back to Mastermind

3 Day 2: Into the rabbit hole

Okay. Time to keep going. Hopefully things will get a little more interesting this time.

The next section is entitled Polymorphism and Functional Programming. This at least sounds more interesting! Let’s take a look at what it has to offer.

3.1 Mastermind in Haskell

Apparently, this homework assignment is based on the Mastermind puzzle game, which is actually a pretty cool concept. The introduction mentions something about typeclass constraints, which I actually remember from my pervious dabblings, though it looks like they haven’t been formally introduced in this class yet.

The first assignment is to write a function that takes two Code instances, which are just lists of colors, and finds how many "exact" matches they share. To me, this sounds like a useful time to use zip! Then I guess I could use foldl and sum everything manually, but I’m sure there’s a nicer way.

Well, first, I can use map with zip to get a list of Bools, right? Although then I’d need a function of type (a, a) -> Bool. To Hoogle I go again.

Hrm. Still nothing. Well, I’m sure there’s a nice way of doing it, but for now I can just write my own helper function.

pairEq :: (a, a) -> Bool

pairEq (a, b) = a == b

Nope, that still complains about types. Oh, this is where typeclasses come in, right? I seem to remember the relevant typeclass is called Eq, let’s see if I remember the syntax.

pairEq :: Eq a => (a, a) -> Bool

pairEq (a, b) = a == b

There we go. GHC is happy now. Now things should be fairly easy...

exactMatches :: Code -> Code -> Int

exactMatches xs ys = map pairEq pairs

  where pairs = zip xs ys

Wait, no, now I have a [Bool]. I need to count up all the True values. In Racket, I’d use count. Does Haskell have something similar? A quick query for [Bool] -> Int doesn’t give me anything helpful (c’mon Hoogle, I talked about how cool you were and you’ve done nothing but let me down), though I guess it wouldn’t be hard to piece together with some simple function composition.

exactMatches :: Code -> Code -> Int

exactMatches xs ys = length . filter id $ map pairEq pairs

  where pairs = zip xs ys

There we go! It’s even pretty elegant, too, except perhaps for the pairEq function in there. Moving on, the next step is to write a function that counts how many of each color there are within a list. The code provided includes a colors list that simply contains all of the possible elements.

colors :: [Peg]

colors = [Red, Green, Blue, Yellow, Orange, Purple]

I have mixed feelings about that, I guess. It feels a little redundant to have to manually list out all the elements when the information is known statically, and updating the list will be necessary if the Peg type changes. In Racket, writing a macro for this would be trivial, but alas, this is Haskell. Perhaps there is a way, I’m just not aware of it.

Anyway, this isn’t really a hard problem. Here’s my solution.

countColors :: Code -> [Int]

countColors ps = map countColor colors

  where countColor c = length $ filter (== c) ps

Maybe it could be better? I don’t know. It looks fine to me. Now I’m supposed to use that function to find all possible matches between two codes, but order doesn’t matter. This is pretty simple, too.

matches :: Code -> Code -> Int

matches xs ys = sum $ map (\(a, b) -> min a b) pairs

  where pairs = zip (countColors xs) (countColors ys)

The lambda still feels annoying. In fact... looks like ghc-mod is telling me something about a function called uncurry. What’s its type?

(a -> b -> c) -> (a, b) -> c

Oh, awesome. This is perfect. In fact... I think this makes my pairEq function redundant!

exactMatches :: Code -> Code -> Int

exactMatches xs ys = length . filter id $ map (uncurry (==)) pairs

  where pairs = zip xs ys

 

matches :: Code -> Code -> Int

matches xs ys = sum $ map (uncurry min) pairs

  where pairs = zip (countColors xs) (countColors ys)

Much nicer on both counts. Of course, this only works on pairs, not other tuples. I seem to remember that the usual approach to this in Haskell is just to add more functions (or use typeclasses). Maybe there’s an equivalent for three-tuples?

Well, searching for (a -> b -> c -> d) -> (a, b, c) -> d gives me nothing, as does uncurry3. Maybe it’s just not common enough to warrant a built-in function? I’ll look into it more if I ever find myself actually wanting that function.

3.2 Oh right, types are complicated

The assignment defines a Move type that consists of a Code and two Ints, which correspond to the number of exact and inexact matches, respectively. It wants me to implement a function to build a Move given a guess Code and the "secret" Code.

Well, I already have a function to get the exact matches and another function to get all the matches, so writing an inexactMatches function should be pretty simple.

inexactMatches :: Code -> Code -> Int

inexactMatches xs ys = matches xs ys - exactMatches xs ys

You know what, that sucks. To me, this looks like simple composition between the -, matches, and exactMatches functions. There has to be a way to write this more nicely, right? I seem to remember that "lambdabot" on #haskell has a point-free generation function (amusingly named "pointless"), so maybe that will help?

<lexi-lambda> @pl \a b -> f a b - g a b

<lambdabot> ap (ap . ((-) .) . f) g

haskell

Eww. That’s not helpful at all. So much for that idea. Time to actually ask people who know what they’re doing.

<lexi-lambda> Fiddling with Haskell, had a random question:

<lexi-lambda> is there a nicer way to write a function like this?

<lexi-lambda> \a b -> f a b - g a b

haskell

I had a few people suggest it looked pretty nice as-is, so maybe I’m just being silly. But still, there has to be a nice way to do this, right? It’s so simple! I got a few more suggestions, none of which were any nicer than the original. Here are a few:

curry $ (-) <$> uncurry f <*> uncurry g

 

curry $ liftA2 (-) $ uncurry f $ uncurry g

 

up op f g x = f x `op` g x

(^-^) = up (up (-))

Meh. None of those are nice at all.

<mniip> getCompose (liftA2 (-) (Compose max) (Compose min))

haskell

Oh hey, that looks neat! Even if it’s not what I’d like it to be, that’s getting closer. Maybe if I check out how it works I can bang it into shape. So what exactly are getCompose and Compose and why are they necessary?

Apparently, Compose is for "composition of functors". What am I getting myself into?

So the documentation says that Compose has a single data constructor, Compose. It also lists a value on the same page called getCompose that has the type f (g a). Wait, getCompose doesn’t even appear to be a function type? Maybe f is a partially-applied function type? Or maybe that doesn’t make any sense and I’m making a fool of myself and demonstrating that I don’t really get how Haskell’s type system works.

I think it’s time to do some reading.

3.2.1 Monads, functors, and applicative functors

I decided to go back and ask some more questions on IRC. My immediate confusion was resolved— Compose is a record type, so getCompose just gets at the field. That makes sense, sort of, though I still don’t really understand how it works. It still feels awfully verbose to me. Why can’t I just do liftA2 (-) max min?

Let’s hop into GHCi and see if it can help me. What are the types of these two long expressions?

> :t getCompose (liftA2 (-) (Compose max) (Compose min))

getCompose (liftA2 (-) (Compose max) (Compose min))

  :: (Ord a, Num a) => a -> a -> a

> :t liftA2 (-) max min

liftA2 (-) max min :: (Ord a, Num (a -> a)) => a -> a -> a

Alright, so the first one is obviously the type I want. Why does the second one have a constraint Num (a -> a) (and can that ever even be possibly instantiated?)? I guess I don’t even really know what liftA2 does.

> :t liftA2

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c

> :t liftA2 (-)

liftA2 (-) :: (Applicative f, Num c) => f c -> f c -> f c

Okay, so the first argument is pretty obvious, but what is Applicative and what does it mean here?

A functor with application, providing operations to
  • embed pure expressions (pure), and

  • sequence computations and combine their results (<*>).

Okay, so Applicative has a function like Monad’s return to "lift" values, called pure. Then it can also sequence values using <*>. I still have no idea what that means here. What is f getting instantiated with?

Well, I’m providing min and max, which are functions, and it looks like there’s an instance of Applicative for ((->) a). But what does that instance do?

A quick search has found me a Stack Overflow question, which in turn has redirected me to Chapter 11 of Learn You a Haskell. It would probably be helpful for me to read through all of this patiently but I don’t want to do that. Show me the code!

instance Applicative ((->) r) where

    pure x = (\_ -> x)

    f <*> g = \x -> f x (g x)

Aha! That’s helpful. How was I supposed to know that, anyway? Whatever. It looks like <*> is just simple function composition for functions. Or wait, no, that’s what fmap is. This passes f two arguments, x and (g x). How is this useful at all?

(Oh, also, I just learned that <$> is an abbreviation for fmap, so that’s good to know.)

Phew. So I’ve been reading around on this page for quite a long while now. I sort of understand how various individual instances of these typeclasses work, but I feel like I’m utterly failing to see any "bigger picture" about what all instances of a particular typeclass do. How would I have any idea what fmap does with IO if I didn’t know the implementation?

I guess I really just don’t see the purpose of having these "general-purpose" typeclasses if the operations they define are so different in each case that they’re really just separate functions for different types. Or am I missing something that ties them together?

3.3 It’s types all the way down

Alright, I finally bit the bullet and took the time to read a fair portion of the LYAH chapter. I’m sure I still barely understand anything, but I think I have enough of an idea to at least reason about things. From what I can tell, the reason I can’t do liftA2 (-) max min is because my functions are binary.

While I do now understand how instances of Applicative can work with fmap to great utility, I’m still not entirely sure how the whole process works. If I understood the concepts more, I think just looking at the types of things would be more helpful, but unfortunately, I’m not there yet.

So this does a thing.

> (,) <$> (Just) <*> (not) $ True

(Just True,False)

Which is... cool, I guess? I understand what it does—it applies the two functions to True, then applies the first function to both of them. But why?

Let’s see. Both <$> and <*> are left-associative and have the same precedence. What’s the result of the first operation? Well, it’s just fmap (,) Just. What’s the implementation of fmap on functions? It’s just composition, so we get (,) . Just.

To make this easier on myself, I’ll visualize this as the following:

\a b -> (Just a, b)

So now what? Now we get to <*>. What’s (<*>) (\a b -> (Just a, b)) not?

> :t (<*>) (\a b -> (Just a, b)) not

(<*>) (\a b -> (Just a, b)) not :: Bool -> (Maybe Bool, Bool)

> :t (,) <$> (Just) <*> not

(,) <$> (Just) <*> not :: Bool -> (Maybe Bool, Bool)

Okay. So a <*> b for functions is just \x -> a x (b x). Expanding that out, we get:

\x -> (\a b -> (Just a, b)) x (not x)

Well that’s remarkably simple. Why is it so hard for me to understand? Maybe because I just don’t get why it’s a useful function to have. Why is this such a general pattern? It seems awfully arbitrary.

I guess all this does is take a function of arity 2 and pass it the result of a single argument threaded through two functions of arity 1. Why is this so important? I don’t understand. I’m confused. What about a function of arity 3?

> :t (,,) <$> (Just) <*> (Left) <*> (*3)

(,,) <$> (Just) <*> (Left) <*> (*3)

  :: Num a => a -> (Maybe a, Either a b, a)

Alright, that... actually makes sense. Cool. Just to understand how the extra argument affects things, let me expand this all out again.

(,,) <$> Just = \a b c -> (Just a, b, c)

     <*> Left = \x -> (\a b c -> (Just a, b, c)) x (Left x)

              = \x c -> (Just x, Left x, c)

     <*> (*3) = \y -> (\x c -> (Just x, Left x, c)) y (y * 3)

              = \y -> (Just y, Left y, y * 3)

Well. I guess the values are proliferated through the argument list by alpha-conversion as the tree expands, eventually collapsing down to a single-argument function.

None of this makes my original problem any simpler, though, does it? In all of these cases, the functions passed in need to be unary. It’s been so long I’ve almost forgotten my original function.

\a b -> (f a b) - (g a b)

Now I’m sort of curious... how can I generalize some system for transforming (-) into a function that will accept four arguments: two functions and two values to apply to those functions. Wouldn’t this be theoretically pretty similar to <*>? Obviously the simple way would be doing this:

lift op f g x y = op (f x y) (g x y)

But that’s terribly uninteresting and specialized. Ideally what I’d want would be some series of operations that would compound a function that takes n values with n functions of arity 2 and produce a function that accepts 2 values and produces a result.

Well, let’s call my magic operator <**>, and the lifting operator (the equivalent of pure) will be called pure2. Do these names make sense? Probably not. I don’t care.

Therefore, my function should look like this:

inexactMatches = pure2 (-) <**> matches <**> exactMatches

(Wow, I really had to think for a moment there to remember what I was originally trying to solve.)

So how should this expand, ideally? Well, maybe if I write out the expansion steps like I did above, a more general pattern will appear.

pure2 o = \_ _ a b -> (o a b)

 <**> f = \x y -> (\_ _ a b -> (o a b)) x y (f x y)

        = \x y -> (\a b -> (o a b)) (f x y)

 <**> g = \p q -> (\x y -> (\a b -> (o a b)) (f x y)) p q (g p q)

        = \p q -> (\a b -> (o a b)) (f p q) (g p q)

        = \p q -> o (f p q) (g p q)

Hey! That’s not special at all, that’s actually just a different implementation of Applicative for functions. It may have taken me thirty minutes just to figure out how that should properly expand, but now that I’ve done it, it seems pretty obvious.

3.3.1 Build your own instances… maybe?

So then how can I make this "alternate" instance for the same type? Well, I don’t think I can, but maybe I can do it by making a small wrapper type. I seem to remember reading something like that ages ago.

Okay, so first I need to define my wrapper type.

newtype BinaryFunction a b = BinaryFunction (a -> b)

That seems right. Now I need to implement a Functor instance for it, which should still just be function composition.

instance Functor (BinaryFunction a) where

  fmap a (BinaryFunction b) = BinaryFunction (a . b)

Then all that’s left to do is implement Applicative.

instance Applicative (BinaryFunction a) where

  pure f = BinaryFunction (\_ _ -> f)

  (BinaryFunction f) <*> (BinaryFunction g) = BinaryFunction (\x y -> f x y (g x y))

Hmm, that doesn’t work, but I’m not sure why. I think it’s because g’s type implies it can only be applied to one argument and f’s type implies it can only be applied to one. So maybe I need to modify my newtype wrapper to explicity declare it can take two arguments?

newtype BinaryFunction a b c = BinaryFunction (a -> b -> c)

 

instance Functor (BinaryFunction a b) where

  fmap a (BinaryFunction b) = BinaryFunction (a . b)

Wait, no, now fmap is giving me errors. It seems that now, since a can only be applied to a single argument, this no longer works. Darn.

Is it possible that this isn’t an Applicative after all? What if I tried implementing my own typeclass with the slightly different behavior? Would that work, or is my conclusion incorrect?

class BinaryFunctor a where

  fmap2 ::

Wait, how does this even work? I think the original Applicative law should have an analogue here.

fmap2 f g = pure2 f <*> g

Reasoning backwards from my "definitions" for pure2 and <*>...

pure2 f <*> g = \x y -> (\_ _ a b -> (f a b)) x y (g x y)

That seems right... although honestly at this point I don’t have any idea if what I’m doing makes any sense anymore. Anyway, if I define fmap2 just for functions, I get this.

fmap2 :: (a -> b -> c) -> (d -> e -> a) -> d -> e -> b -> c

fmap2 f g = \x y -> (\_ _ -> f) x y (g x y)

Wow. That was much more complicated than I expected, honestly. Maybe this is a little less generalizable than I thought. In fact, is it even possible? The type of fmap is pretty simple.

> :t fmap

fmap :: Functor f => (a -> b) -> f a -> f b

Specialized for function types, that’s still pretty straightforward.

fmap :: (a -> b) -> (r -> a) -> (r -> b)

But with my fmap2, the arity of the resulting function is different from the arity of the second argument, so it doesn’t seem like they could possibly be represented by the same type, anyway.

It’s clear I’m in way over my head on this one. I don’t really have any idea what I’m doing. What was I supposed to be doing in the first place?

3.4 Back to Mastermind

Right. Mastermind. That was a quite the detour. Maybe I’ll come back to it later, or maybe I’ll just realize that what I was trying to do was misguided and didn’t make any sense anyway. Who knows? Whatever. I should probably just finish what I was working on before all this nonsense got me distracted.

inexactMatches :: Code -> Code -> Int

inexactMatches xs ys = matches xs ys - exactMatches xs ys

Fine. You know what? It’s good enough. Moving on.

A Move is a new datatype that is constructed with a Code and two Ints. The first Int is the number of exact matches that the Code has with the secret and the second Int is the number of nonexact matches.

Alright, this is pretty stupidly easy compared to what I was just dealing with.

getMove :: Code -> Code -> Move

getMove secret guess = Move secret e i

  where e = exactMatches secret guess

        i = inexactMatches secret guess

Is it beautiful? No. Does it work? Yes. Good.

We will now define a concept that will be important in playing the Mastermind game. This is the concept of consistency; we say that a Code is consistent with a Move if the Code could have been the secret that generated that move. In other words, if the guess inside the Move has the same number of exact and non-exact matches with the provided Code as it did with the actual secret, then the Code is consistent with the Move.

isConsistent :: Move -> Code -> Bool

isConsistent (Move guess e i) guess' = e == e' && i == i'

  where e' = exactMatches guess' guess

        i' = inexactMatches guess' guess

Easy stuff. Now we just implement a function to filter out all the remaining viable codes.

filterCodes :: Move -> [Code] -> [Code]

filterCodes m = filter $ isConsistent m

Now we just need to create a function that will generate all possible permutations of a list of colors given a certain code length.

allCodes :: Int -> [Code]

allCodes 0 = []

allCodes 1 = map (:[]) colors

allCodes n = concatMap (\c -> map (c:) $ allCodes (n - 1)) colors

Now we can write a function that actually solves Mastermind puzzles. The assignment wants me to always start by guessing purely Red just for consistency.

solve :: Code -> [Move]

solve secret = loop [initialMove]

  where codeLen = length secret

        initialMove = getMove secret $ replicate codeLen Red

        isConsistentWithAll ms c = all (`isConsistent` c) ms

        nextMove ms = getMove secret $ head $ filter (isConsistentWithAll ms) $ allCodes codeLen

        loop ms@(Move _ e _ : _)

          | e == codeLen = ms

          | otherwise    = loop (nextMove ms : ms)

I’m sure that could be much more efficient (it filters through the entire list of moves every time instead of just threading a list of remaining options through), but I don’t really care for this small problem. I’ve overengineered this assignment enough, and honestly, I’m ready to move on.