This article shows an idiomatic, yet beginner-friendly Haskell solution to a coding exercise.

Mike Hadlow tweeted a coding exercise that involves parsing and evaluating instruction sets. Haskell excels at such problems, so I decided to give it a go. Since this was only an exercise for the fun of it, I didn't want to set up a complete Haskell project. Rather, I wanted to write one or two .hs files that I could interact with via GHCi. This means no lenses, monad transformers, or other fancy libraries.

Hopefully, this makes the code friendly to Haskell beginners. It shows what I consider idiomatic, but basic Haskell, solving a problem of moderate difficulty.

The problem #

Mike Hadlow has a detailed description of the exercise, but in short, you're given a file with a set of instructions that look like this:

1 1 E
RFRFRFRF
1 1 E

The first and last lines describe the position and orientation of a robot. The first line, for example, describes a robot at position (1, 1) facing east. A robot can face in one of the four normal directions of the map: north, east, south, and west.

The first line gives the robot's start position, and the last line the expected end position.

The middle line is a set of instructions to the robot. It can turn left or right, or move forward.

The exercise is to evaluate whether journeys are valid; that is, whether the robot's end position matches the expected end position if it follows the commands.

Imports #

I managed to solve the exercise with a single Main.hs file. Here's the module declaration and the required imports:

module Main where
 
import Data.Foldable
import Data.Ord
import Text.Read (readPrec)
import Text.ParserCombinators.ReadP
import Text.ParserCombinators.ReadPrec (readPrec_to_PminPrec)

These imports are only required to support parsing of input. Once parsed, you can evaluate each journey using nothing but the functions available in the standard Prelude.

Types #

Haskell is a statically typed language, so it often pays to define some types. Granted, the exercise hardly warrants all of these types, but as an example of idiomatic Haskell, I think that this is still good practice. After all, Haskell types are easy to declare. Often, they are one-liners:

data Direction = North | East | South | West deriving (EqShowRead)

The Direction type enumerates the four corners of the world.

data Robot = Robot {
    robotPosition :: (Integer, Integer)
  , robotDirection :: Direction }
  deriving (EqShowRead)

The Robot record type represents the state of a robot: its position and the direction it faces.

You'll also need to enumerate the commands that you can give a robot:

data Command = TurnLeft | TurnRight | MoveForward deriving (EqShowRead)

Finally, you can also define a type for a Journey:

data Journey = Journey {
    journeyStart :: Robot
  , journeyCommands :: [Command]
  , journeyEnd :: Robot }
  deriving (EqShowRead)

These are all the types required for solving the exercise.

Parsing #

The format of the input file is simple enough that it could be done in an ad-hoc fashion using lines, word, read, and a few other low-level functions. While the format barely warrants the use of parser combinators, I'll still use some to showcase the power of that approach.

Since one of my goals is to implement the functionality using a single .hs file, I can't pull in external parser combinator libraries. Instead, I'll use the built-in ReadP module, which I've often found sufficient to parse files like the present exercise input file.

First, you're going to have to be able to parse numbers, which can be done using the Read type class. You'll need, however, to be able to compose Integer parsers with other ReadP parsers.

parseRead :: Read a => ReadP a
parseRead = readPrec_to_P readPrec minPrec

This turns every Read instance value into a ReadP value. (I admit that I wasn't sure which precedence number to use, but minPrec seems to work.)

Next, you need a parser for Direction values:

parseDirection :: ReadP Direction
parseDirection =
  choice [
    char 'N' >> return North,
    char 'E' >> return East,
    char 'S' >> return South,
    char 'W' >> return West ]

Notice how declarative this looks. The choice function combines a list of other parsers. When an individual parser in that list encounters the 'N' character, it'll parse it as North, 'E' as East, and so on.

You can now parse an entire Robot using the Applicative <*> and <* operators.

parseRobot :: ReadP Robot
parseRobot =
  (\x y d -> Robot (x, y) d) <$>
  (parseRead <* char ' ') <*>
  (parseRead <* char ' ') <*>
   parseDirection

The <*> operator combines two parsers by using the output of both of them, whereas the <* combines two parsers by running both of them, but discarding the output of the right-hand parser. A good mnemonic is that the operator points to the parser that produces an output. Here', the parseRobot function uses the <* operator to require that each number is followed by a space. The space, however, is just a delimiter, so you throw it away.

parseRead parses any Read instance. Here, the parseRobot function uses it to parse each Integer in a robot's position. It also uses parseDirection to parse the robot's direction.

Similar to how you can parse directions, you can also parse the commands:

parseCommand :: ReadP Command
parseCommand =
  choice [
    char 'L' >> return TurnLeft,
    char 'R' >> return TurnRight,
    char 'F' >> return MoveForward]

Likewise, similar to how you parse a single robot, you can now parse a journey:

parseJourney :: ReadP Journey
parseJourney =
  Journey <$>
  (parseRobot <* string "\n") <*>
  (many parseCommand <* string "\n") <*>
   parseRobot

The only new element compared to parseRobot is the use of the many parser combinator, which looks for zero, one, or many Command values.

This gives you a way to parse a complete journey, but the input file contains many of those, separated by newlines and other whitespace:

parseJourneys :: ReadP [Journey]
parseJourneys = parseJourney `sepBy` skipSpaces

Finally, you can parse a multi-line string into a list of journeys:

parseInput :: String -> [Journey]
parseInput = fst . minimumBy (comparing snd) . readP_to_S parseJourneys

When you run readP_to_S, it'll produce a list of alternatives, as there's more than one way to interpret the file according to parseJourneys. Each alternative is presented as a tuple of the parse result and the remaining (or unconsumed) string. I'm after the alternative that consumes as much of the input file as possible (which turns out to be all of it), so I use minimumBy to find the tuple that has the smallest second element. Then I return the first element of that tuple.

Play around with readP_to_S parseJourneys in GHCi if you want all the details.

Evaluation #

Haskell beginners may still find operators like <*> cryptic, but they're essential to parser combinators. Evaluation of the journeys is, in comparison, simple.

You can start by defining a function to turn right:

turnRight :: Robot -> Robot
turnRight r@(Robot _ North) = r { robotDirection = East }
turnRight r@(Robot _  East) = r { robotDirection = South }
turnRight r@(Robot _ South) = r { robotDirection = West }
turnRight r@(Robot _  West) = r { robotDirection = North }

There's more than one way to write a function that rotates one direction to the right, but I chose one that I found most readable. It trades clarity for verbosity by relying on simple pattern matching. I hope that it's easy to understand for Haskell beginners, and perhaps even for people who haven't seen Haskell code before.

The function to turn left uses the same structure:

turnLeft :: Robot -> Robot
turnLeft r@(Robot _ North) = r { robotDirection = West }
turnLeft r@(Robot _  West) = r { robotDirection = South }
turnLeft r@(Robot _ South) = r { robotDirection = East }
turnLeft r@(Robot _  East) = r { robotDirection = North }

The last command you need to implement is moving forward:

moveForward :: Robot -> Robot
moveForward (Robot (x, y) North) = Robot (x, y + 1) North
moveForward (Robot (x, y)  East) = Robot (x + 1, y) East
moveForward (Robot (x, y) South) = Robot (x, y - 1) South
moveForward (Robot (x, y)  West) = Robot (x - 1, y) West

The moveForward function also pattern-matches on the direction the robot is facing, this time to increment or decrement the x or y coordinate as appropriate.

You can now evaluate all three commands:

evalCommand :: Command -> Robot -> Robot
evalCommand   TurnRight = turnRight
evalCommand    TurnLeft = turnLeft
evalCommand MoveForward = moveForward

The evalCommand pattern-matches on all three Command cases and returns the appropriate function for each.

You can now evaluate whether a Journey is valid:

isJourneyValid :: Journey -> Bool
isJourneyValid (Journey s cs e) = foldl (flip evalCommand) s cs == e

The isJourneyValid function pattern-matches the constituent values out of Journey. I named the journeyStart value s (for start), the journeyCommands value cs (for commands), and the journeyEnd value e (for end).

The evalCommand function evaluates a single Command, but a Journey contains many commands. You'll need to evaluate the first command to find the position from which you evaluate the second command, and so on. Imperative programmers would use a for loop for something like that, but in functional programming, a fold, in this case from the left, is how it's done.

foldl requires you to supply an initial state s as well as the list of commands cs. The entire foldl expression produces a final Robot state that you can compare against the expected end state e.

Execution #

Load the input file, parse it, and evaluate each journey in the main function:

main :: IO ()
main = do
  input <- parseInput <$> readFile "input.txt"
  mapM_ print $ isJourneyValid <$> input

I just load the Main.hs file in GHCi and run the main function:

Prelude> :load Main.hs
[1 of 1] Compiling Main             ( Main.hs, interpreted )
Ok, one module loaded.
*Main> main
True
True
True

I used the same input file as Mike Hadlow, and it turns out that all journeys are valid. That's not what I'd expected from an exercise like this, so I cloned and ran Mike's solution as well, and it seems that it arrives at the same result.

Conclusion #

Haskell is a great language for small coding exercises that require parsing and interpretation. In this article, I demonstrated one solution to the robot journeys coding exercise. My goal was to show some beginner-friendly, but still idiomatic Haskell code.

Granted, the use of parser combinators is on the verge of being overkill, but I wanted to show an example; Haskell examples are scarce, so I hope it's helpful.



Wish to comment?

You can add a comment to this post by sending me a pull request. Alternatively, you can discuss this post on Twitter or somewhere else with a permalink. Ping me with the link, and I may respond.

Published

Monday, 28 October 2019 04:34:00 UTC

Tags



"Our team wholeheartedly endorses Mark. His expert service provides tremendous value."
Hire me!
Published: Monday, 28 October 2019 04:34:00 UTC