« Anyone willing to help me get set up with something like miso? » Competitive programming in Haskell: data representation and optimization, with cake

Competitive programming in Haskell: vectors and 2D geometry

Posted on June 24, 2020
Tagged , , ,

In my previous post (apologies it has been so long!) I challenged you to solve Vacuumba, which asks us to figure out where a robot ends up after following a sequence of instructions. Mathematically, this corresponds to adding up a bunch of vectors, but the interesting point is that the instructions are always relative to the robot’s current state, so robot programs are imperative programs.

Vector basics

The first order of business is to code up some primitives for dealing with (2D) vectors. I have accumulated a lot of library code for doing geometric stuff, but it’s kind of a mess; I’m using this as an opportunity to clean it up bit by bit. So there won’t be much code at first, but the library will grow as we do more geometry problems. The code so far (explained below) can be found in the comprog-hs repository.

First, a basic representation for 2D vectors, the zero vector, and addition and subtraction of vectors.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Geom where

------------------------------------------------------------
-- 2D points and vectors

data V2 s = V2 !s !s deriving (Eq, Ord, Show)
type V2D  = V2 Double

instance Foldable V2 where
  foldMap f (V2 x y) = f x <> f y

zero :: Num s => V2 s
zero = V2 0 0

-- Adding and subtracting vectors
(^+^), (^-^) :: Num s => V2 s -> V2 s -> V2 s
V2 x1 y1 ^+^ V2 x2 y2 = V2 (x1+x2) (y1+y2)
V2 x1 y1 ^-^ V2 x2 y2 = V2 (x1-x2) (y1-y2)

A few things to point out:

Angles and rotation

The other thing we are going to need for this problem is angles.

------------------------------------------------------------
-- Angles

newtype Angle = A Double  -- angle (radians)
  deriving (Show, Eq, Ord, Num, Fractional, Floating)

fromDeg :: Double -> Angle
fromDeg d = A (d * pi / 180)

fromRad :: Double -> Angle
fromRad = A

toDeg :: Angle -> Double
toDeg (A r) = r * 180 / pi

toRad :: Angle -> Double
toRad (A r) = r

-- Construct a vector in polar coordinates.
fromPolar :: Double -> Angle -> V2D
fromPolar r θ = rot θ (V2 r 0)

-- Rotate a vector counterclockwise by a given angle.
rot :: Angle -> V2D -> V2D
rot (A θ) (V2 x y) = V2 (cos θ * x - sin θ * y) (sin θ * x + cos θ * y)

Nothing too complicated going on here: we have a type to represent angles, conversions to and from degrees and radians, and then two uses for angles: a function to construct a vector in polar coordinates, and a function to perform rotation.

Incidentally, one could of course define type Angle = Double, which would be simpler in some ways, but after getting bitten several times by forgetting to convert from degrees to radians, I decided it was much better to use a newtype and entirely prevent that class of error.

Solving Vacuumba

Now we just put the pieces together to solve the problem. First, some imports:

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards  #-}

import           Control.Arrow
import           Control.Monad.State
import qualified Data.Foldable       as F
import           Text.Printf

import           Geom
import           Scanner

We make a data type for representing robot instructions, and a corresponding Scanner. Notice how we are forced to use fromDeg to convert the raw input into an appropriate type.

data Instr = I { turn :: Angle, dist :: Double }

instr :: Scanner Instr
instr = I <$> (fromDeg <$> double) <*> double

The high-level solution then reads the input via a Scanner, solves each scenario, and formats the output. The output is a V2D, so we just convert it to a list with F.toList and use printf to format each coordinate.

main = interact $
  runScanner (numberOf (numberOf instr)) >>>
  map (solve >>> F.toList >>> map (printf "%.6f") >>> unwords) >>> unlines

Our solve function needs to take a list of instructions, and output the final location of the robot. Since the instructions can be seen as an imperative program for updating the state of the robot, it’s entirely appropriate to use a localized State computation.

First, a data type to represent the robot’s current state, consisting of a 2D vector recording the position, and an angle to record the current heading. initRS records the robot’s initial state (noting that it starts out facing north, corresponding to an angle of \(90^\circ\) as measured clockwise from the positive \(x\)-axis).

data RobotState = RS { pos :: V2D, heading :: Angle }
initRS = RS zero (fromDeg 90)

Finally, the solve function itself executes each instruction in sequence as a State RobotState computation, uses execState to run the resulting overall computation and extract the final state, and then projects out the robot’s final position. Executing a single instruction is where the geometry happens: we look up the current robot state, calculate its new heading by adding the turn angle to the current heading, construct a movement vector in the direction of the new heading using polar coordinates, and add the movement to the current position.

solve :: [Instr] -> V2D
solve = mapM_ exec >>> flip execState initRS >>> pos
  where
    exec :: Instr -> State RobotState ()
    exec (I θ d) = do
      RS{..} <- get
      let heading' = heading + θ
          move     = fromPolar d heading'
      put $ RS (pos ^+^ move) heading'

For next time

We’ll definitely be doing more geometry, but for the next post I feel like doing something different. I invite you to solve Checking Break.