Smooth as Butter

Our Jam module has served us adequately so far, but input and output are still awkward. We must introduce a name to refer to the rest of the input, to be placed in a tuple at the end of our routine. We often must introduce more names to keep track of where we are in the input when splitting it.

Can’t we hide these details? Can’t our module implicitly take the unread input and feed it to the next function that asks for input?

We can, by writing a monad. The idea is to surreptitiously attach a list of strings to everything we do. The list holds the input that is about to be read, and utility functions manipulate this list behind the scenes, so we can write something like:

-- In this hypothetical Google Code Jam problem, each case consists of
-- two integers separated by a space, and we're to output their product.

import Butter

main = butter $ do
  [m, n] <- getints
  return $ show $ m * n

While debugging, I found it useful to be able to extract a particular set of cases from an input file. Hence I added a second list of strings to the state: this second list holds the input read so far for a single test case. Suppose we want to generate a new input file that consists of the first, third and sixth cases of another file. Then we want to be able to temporarily modify our solution to print test inputs instead:

import Butter

main = butterCases [1,3,6] $ do
  [m, n] <- getints
  return $ show $ m * n

We imagine there are other applications: perhaps we want to print input-output pairs for each case.

Our code is just like the IO monad except instead of tacitly modifying a world, we’re tacitly modifying two strings of lists.

module Butter (
  butter, butterCases,
  gets, getsn, getem, getemn, getints, getintsn, getintegers, getdbls
) where

import Control.Monad
import Data.List

data Butter a = Butter (([String], [String]) -> (a, ([String], [String])))

instance Functor Butter where
  fmap = liftM

instance Applicative Butter where
  pure k = Butter (\s -> (k, s))
  (<*>) = ap

instance Monad Butter where
  Butter c1 >>= fc2 = Butter (\s0 -> let
    (r, s1)   = c1 s0
    Butter c2 = fc2 r
    in c2 s1)
  return = pure

gets :: Butter String
gets = Butter (\(x:xs, ys) -> (x, (xs, ys++[x])))

getsn :: Int -> Butter [String]
getsn n = replicateM n gets

getem :: Read a => Butter [a]
getem = gets >>= return . map read . words

getemn :: Read a => Int -> Butter [[a]]
getemn n = getsn n >>= return . map (map read . words)

getints :: Butter [Int]
getints = getem

getintegers :: Butter [Integer]
getintegers = getem

getintsn :: Int -> Butter [[Int]]
getintsn = getemn

getdbls :: Butter [Double]
getdbls = getem

butter f = interact $ \s -> let
  Butter fun = f
  (_n:inp) = lines s
  n = read _n
  in unlines $ zipWith (++) (map (\k -> "Case #" ++ show k ++ ": ") [1..n])
    $ unfoldr (\(xs, _) -> Just . fun $ (xs, [])) $ (inp, [])

butterLn f = interact $ \s -> let
  Butter fun = f
  (_n:inp) = lines s
  n = read _n
  in unlines $ zipWith (++) (map (\k -> "Case #" ++ show k ++ ":\n") [1..n])
    $ unfoldr (\(xs, _) -> Just . fun $ (xs, [])) $ (inp, [])

butterCases idxs f = interact $ \s -> let
  Butter fun = f
  (_n:inp) = lines s
  n = read _n
  cases = take n $ unfoldr (\xy -> let
    (_, (xs, ys)) = fun xy in Just (ys, (xs, []))) (inp, [])
  in unlines $ (:) (show $ length idxs) $ concatMap (cases!!) idxs

We name it Butter, because it smooth to use, and like Jam, it’s also a spread.

It turns out we often want to attach some kind of state to a sequence of functions. This is exactly why the State monad was written, and in fact, we could have just defined:

data Butter a = State ([String], [String])

But one should write out a monad in full (even if it is copied from elsewhere!) at least once while learning Haskell.

Amusingly, our code resembles what we might write if we had stuck with the IO monad from the beginning:

iogetints :: IO [Int]
iogetints = do
  s <- getLine
  return $ map read $ words s

main = do
  [m, n] <- iogetints
  putStrLn $ show $ m * n

However, it’s good form to steer clear of IO as much as possible. Especially if it’s as easy as swapping out the IO monad with a State monad. Besides feeling good about ourselves, we can, for example, trivially feed a string to our program instead of reading from standard input. We lose this flexibility if we use the IO monad everywhere.


Ben Lynn blynn@cs.stanford.edu