Sunday, November 25, 2007

How to lose six in a row to a cow college

Play with all the fire, intensity, and desire of a house fern.

Monday, September 17, 2007

Dear Coach Saban

Just beat Auburn.

Saturday, August 18, 2007

Word ladder in Haskell

Another followup to my earlier post about searching for word ladders, this time using Haskell!

This blog post is a Haskell program, written using the "literate comment" convention.

First a bit of front matter. This implementation of the word-ladder search will use the State and list monads.


> module Main where
> import Control.Monad.State
> import Data.Char
> import Data.List (find)
> import Data.Set (Set, member, difference)
> import qualified Data.Set as Set
> import System.Environment (getArgs)
> import System.Exit

The idea is simple: read the dictionary, search for the desired ladder, and show it to the user:


> main :: IO ()
> main = do
>   (start, goal, dict) <- getArgs >>= parse
>   fullDictionary <- readDictionary dict
>   print $ search start goal (trim fullDictionary start)

Remember that getArgs is an action that returns the list of command-line arguments. We bind this action to the following:


>   where parse [start,goal,dict] = return (start,goal,dict)
>         parse [start,goal]      = return (start,goal,"/usr/dict/words")
>         parse _ =
>           putStrLn "Usage: ladder start goal [ dictionary ]" >>
>           exitWith (ExitFailure 1)

Haskell's pattern matching shows that the program takes two or three arguments. The first two are the start and goal words. The optional third argument is the path to a dictionary (one word per line) to use.

We condition the dictionary by eliminating words whose lengths differ from the length of the start word and also converting everything to lowercase.


>         trim :: [String] -> String -> [String]
>         trim words start = filter (sameLength start) (lc words)
>
>         sameLength start = (== length start) . length
>
>         lc = map (map toLower)

The search can fail, so result is of type Maybe [String]. Handling both cases is straightforward:


>         print Nothing = putStrLn "No ladder found."
>         print (Just a) = mapM_ putStrLn a

The dictionary's format is simple, so reading it is a matter of extracting the lines from the file:


> readDictionary :: FilePath -> IO [String]
> readDictionary path = liftM lines $ readFile path

Now for the fun bits. Imagine a graph where nodes are words from the dictionary and where edges are between words that are "one hop' from each other, i.e., words that could be on consecutive "rungs" of a ladder.

Beginning with the start word, the program performs a breadth-first search of this graph. We call the set of words reached in the most recent iteration the "fringe." When the fringe contains the goal word, we're done.

The state monad simulates destructive update in imperative programming languages. (Haskell is purely functional.) Without it, we'd have to explicitly thread the state value through the call chain, but with it, we retrieve and update the state value with get and put as below:


> search start goal words =
>   evalState (loop [[start]]) (Set.fromList $ filter (/=start) words)
>   where
>     loop :: [[String]] -> State (Set String) (Maybe [String])
>     loop [] = return Nothing
>     loop paths = do
>       next <- step paths
>       let newFringe = fringe next
>       words <- get
>       put $ words `difference` newFringe
>       if goal `member` newFringe
>         then return $ Just (winner next)
>         else loop next

The list monad is handy for representing nondeterministic computations. In concept at least, the search carries around a list of lists that has all of the partial results computed so far.

For example, if the start word is dog, the state value on the second iteration might be [["dog", "dig"], ["dog", "fog"], ["dog", "bog"]]. This approach might seems to be a memory pig, but it remains surprisingly frugal.

To proceed to the next iteration of the search, for each partial result (one ladder beginning with the start word) we find the as-yet unseen neighbors of its last element (a member of the current fringe) and replace the current partial result with new ones for each of the neighbors. Again, consider the partial results at the second iteration in the previous paragraph.


>     step :: [[String]] -> State (Set String) [[String]]
>     step paths = do
>       words <- get
>       return $ paths >>= augment words
>
>     augment :: Set String -> [String] -> [[String]]
>     augment words path = [ path ++ [n] | n <- ns ]
>       where ns = Set.elems $ neighbors (last path) words
>     
>     neighbors :: String -> Set String -> Set String
>     neighbors word words = Set.filter (oneHop word) words
>       where oneHop [] [] = False
>             oneHop (x:xs) (y:ys) | x /= y = xs == ys
>                                  | otherwise = oneHop xs ys

As described above, the fringe is the set of words at the ends of the partial ladders computed so far:

>     fringe :: [[String]] -> Set String
>     fringe paths = Set.fromList (map last paths)

Once we've seen the goal in the fringe, we return the ladder that ends with the goal word:

>     winner :: [[String]] -> [String]
>     winner paths =
>       case (find ((== goal) . last) paths) of
>         Nothing -> undefined
>         Just a -> a

Saturday, August 04, 2007

Word ladder in Python

In an earlier post, I described an implementation in Common Lisp of a breadth-first search to find word ladders.

This time I practiced the kata using Python. Python's list comprehensions help to make the solution concise, but apparently the lunch isn't free. For example, I could have written one_hop as

    def one_hop(a, b):
      return len([aa for aa, bb in zip(a, b) if aa != bb]) == 1

but that resulted in about a twenty percent slowdown.

The code falls out pretty easily:

#! /usr/bin/env python

"""Usage: %(prog)s start-word goal-word [ dictionary-path ]
"""

import sys

prog = sys.argv[0]

def read_words(path):
  words = []

  try:
    f = open(path, "r")
  except IOError, (errno, error):
    sys.stderr.write("%s: open %s: %s\n" % (prog, path, error))
    sys.exit(1)

  for word in f:
    words.append(word[:-1].lower())

  return words

def unpack_args(args):
  dict = "/usr/dict/words"

  if len(args) < 2 or len(args) > 3:
    sys.stderr.write(__doc__ % globals())
    sys.exit(1)

  start, goal = args[0:2]
  if len(args) == 3:
    dict = args[2]

  return (start, goal, dict)

def one_hop(a, b):
#  return len([aa for aa,bb in zip(a, b) if aa != bb]) == 1
  hops = 0
  for aa, bb in zip(a, b):
    if aa != bb:
      hops += 1

  return hops == 1

def rungs(start, goal, begat):
  path = [goal]
  while path[-1] != start:
    path.append(begat[path[-1]])
  path.reverse()

  return path

def ladder(start, goal, dict):
  if len(start) != len(goal):
    return None

  words = read_words(dict)
  candidates = set([w for w in words if len(w) == len(start)])

  start = start.lower()
  goal  = goal.lower()

  begat = {}

  last = [start]
  while len(last) > 0:
    fringe = []

    for w in last:
      neighbors = [n for n in candidates if one_hop(n, w)]

      for n in neighbors:
        begat[n] = w
        candidates.remove(n)

      if goal in neighbors:
        return rungs(start, goal, begat)
      else:
        fringe.extend(neighbors)

    last = fringe
  else:
    return None

def main(args):
  start, goal, dict = unpack_args(args)

  path = ladder(start, goal, dict)
  if path is None:
    print "%s: no path from '%s' to '%s'" % (prog, start, goal)
  else:
    for w, i in zip(path, range(1, len(path) + 1)):
      print "%3d. %s" % (i, w)

  return 0

if __name__ == "__main__":
    sys.exit(main(sys.argv[1:]))

Friday, June 15, 2007

Word ladder

You form a word ladder by changing exactly one letter in the current "rung" to form the next. For example, the following is a ladder from 'paste' to 'carry':

  1. paste
  2. pasty
  3. party
  4. parry
  5. carry

Given starting and goal words, the Lisp code below performs a breadth-first search in the supplied dictionary. Using BFS has the interesting property of guaranteeing that the path found is the shortest between the two words.

I'm not really pleased with the result: there's not enough abstraction. I guess with Lisp, it's hard to be satisfied unless you write a couple of fly-daddy macros that reduce the meat of the code to about three lines.

(defparameter *default-dictionary*
  #P"/usr/dict/words"
)


(defvar *dictionary* (make-hash-table :test #'equal))

(defun ladder (start goal)
  (if (/= (length start) (length goal))
      (error "'~S' and '~S' have different lengths" start goal)
      (let* ((dict (read-dictionary))
             (candidates (ladder-candidates dict start))
             (seen (make-hash-table :test #'equal))
             (begat (make-hash-table :test #'equal))
             (todo (list start))
)

        (loop while todo do
              (let ((next '()))
                (loop for word in todo do
                      (let ((neighbors (neighbors word candidates seen)))
                        (loop for w in neighbors do
                              (setf (gethash w seen) 1
                                    (gethash w begat) word
)
)

                        (if (find goal neighbors :test #'equal)
                            (return-from ladder (rungs start goal begat))
                            (setf next (nconc next neighbors))
)
)
)

                (setf todo next)
)
)

        (error "No path from '~A' to '~A'" start goal)
)
)
)


(defun read-dictionary (&optional (path *default-dictionary*))
  (let ((cached (gethash path *dictionary*)))
    (if cached
        cached
        (let ((dict '()))
          (with-open-file (s path)
            (loop for word = (read-line s nil)
                  while word do
                  (push word dict)
)
)

          (setf (gethash path *dictionary*) dict)
)
)
)
)


(defun ladder-candidates (dict start)
  (let ((candidates '())
        (len (length start))
)

    (loop for w in dict
          when (and (= len (length w)) (string-not-equal w start)) do
          (push (string-downcase w) candidates)
)

    candidates
)
)


(defun one-hop-p (from to)
  (let ((hops 0))
    (loop for ff across from
          for tt across to
          when (char-not-equal ff tt) do
          (incf hops)
)

    (= hops 1)
)
)


(defun rungs (start goal begat)
  (let ((path (list goal)))
    (loop for word = (first path)
          for parent = (gethash word begat)
          while (string-not-equal word start) do
          (push parent path)
)

    path
)
)


(defun neighbors (word pool &optional (seen (make-hash-table)))
  (loop for w in pool
        when (and (one-hop-p word w)
                  (not (gethash w seen))
)

        collect w
)
)


(defun one-hop-neighbors (word)
  (neighbors word (ladder-candidates (read-dictionary) word))
)

Friday, May 18, 2007

I *seen* it!

I've been meaning to put this baby up forever, and I finally got around to scanning it (albeit two years later as you can see from the date).

This was the game where where Jamie Christiansen won the game with that ugly kick and of course Roman Harper's famous forced fumble, memorialized by Daniel Moore in "Rocky Stop." I'd still like to add a copy next to Tyrone Prothro's amazing catch and put the stub inside the frame.

Before the game, I got to meet my aunt, uncle, and a couple of cousins for some mean Mexican. That was after the Florida game where we humbled the cocky Urban Meyer. I heard the ground was literally rumbling from all the cheering. Wish I coulda been there too!

We had great seats -- at the 40 yard line -- and could see everything. I remember being sick of hearing it from my Tennessee-fan friends (if there can be such a thing). I even told my aunt that I'd rather beat UT than Auburn if we could only have one.

(If you remember, that was how it ended up. My brother-in-law who scored those tickets also had a hookup for Iron Bowl tickets. After Prothro took that horrific injury on a stupid, needless, low-class, NFL-style showoff long pass when the Gators were already starting to load the buses -- Shula, you dog! -- we just didn't have it. They were mine for the taking, and I easily said, "No thanks.")

But now the bad times are behind us: it's morning in Alabama!

Monday, April 16, 2007

Tuesday, March 20, 2007

It's official!

Not long ago, I was on the same flight to DC with Bud Cramer. When we reached the terminal at Reagan, I said to him, "Congressman, give my best to Ron Paul!" An honest man and perhaps the humble American republic's last hope, Dr. Paul is officially a candidate for president!

Notable quotes:

  • "I'm very confident about the message of liberty and the constitution. I'm very confident that the American people are sick and tired of what they're getting. And I'm also very confident that the Republican party has gone in the wrong direction. We used to be the party of small government, but now we're the party of Big Government."
  • "My main thrust would be I would emphasize my oath of office. As a congressman, I emphasize that. As president, I would emphasize that. And that is, to obey the constitution, which strictly limits the power of government. It strictly limits the power of the executive branch. It strictly limits the power of the congress -- and even the courts. That would be my goal: to shrink the size and scope of government, believing very sincerely that the benefits to people are far better off in a free society than in an authoritarian society. When government is involved in central planning, and running the world, running the economy, and running our personal lives, we're not better off: we're worse off."
  • "If we don't get a handle on the entitlements, if we don't get a handle on all this foreign adventurism, this country is going broke. Actually, I think the country is insolvent. It's just the fact that the world still accepts our dollars that we can still get away with this. Yes, we can have full accountability, but the ultimate accountability has to be to make sure that we hold government under control -- that we not allow it to continue to grow or try to do everything conceivable at the central level."
  • "Very simply, governments always like inflation, that is, the creation of money out of thin air to debase the value of your currency. This is the reason that we don't have a gold standard: because big-government conservatives and big-government liberals like to spend money. But they really don't like the taxes, and there's a limit to how much they can borrow... and every time they create new money, they devalue the money we have in our pockets. So it's a tax on us; it's a sinister, immoral tax..."
  • "[Inflation is] so destructive because it's the most regressive of all taxes. Poor people and the middle class eventually get wiped out by rising prices. Now government tells us there's only a 2% inflation rate, but that's not true: the inflation rate for poor people and the middle class might be 6 or 8 or 10 percent. Who benefits the most? It's the wealthy class: the bankers, the domestic industries, the military-industrial complex."
  • "The answer to this is gold and silver, and that's still the law of the land. Under the constitution, only gold and silver can be legal tender, yet it's been a good many years since we've completely forgotten about it. We've had no connection -- our dollar's had no connection to gold since 1971. If you look at the problems we've had since that time, they're definitely related."
  • "I would come home [from Iraq] as soon as possible."
  • "Liberty will provide the answers that we need."

Dr. Paul is for peace and friendships among nations. When he gives his solemn word to uphold and defend the constitution, he'll really do it: he won't merely be reading a script. A politician is actually making an issue of sound money!

Ron Paul is a true American. See the video below for more details.

Sunday, March 11, 2007

Wal-Mart, health care, and irresistable market forces

Bo's post today about Wal-Mart made me think of an excellent definition, thanks to Byrne's Eye View:

capitalism
Economic system under which any legitimate complaint can be rephrased as a decent business plan…

Bo's complaint is about customer service: it can take a long time to get in and out of the place. In a free market, goods are allocated by price and by time. When we think of Tiffany & Co., for example, a price tag with many digits comes to mind, but if a customer walks in weary from hauling around so much cash, they'll graciously relieve him of that burden.

Wal-Mart chooses the opposite corner: low prices but slow service. Target's business model attracts customers with more money to spend, and they do it with features such as cleaner stores and better customer service, which their customers value more highly than the few extra dollars that they trade in return.

Even deeper in the corner of low price and long lines are the popular proposals for "free" health care. (As P.J. O'Rourke quipped, "If you think health care is expensive now, wait till it's free.") The "free" health care in Canada and the UK are characterized by long waiting lists -- which exist for exactly the same reasons as the bread lines in the Soviet Union.

Economist Ludwig von Mises wrote, "Even the most mighty government, operating with the utmost severity, cannot succeed in endeavors that are contrary to what has been called 'economic law.'" The mighty United States government has sort of a pilot program for "free," "single-payer" health care: the VA's frightening maze, and, boy, is it a success!

I'm confident that the calls for "free" health care are well-meaning, but their inevitable result would cruelly force everyone into the same trap -- while politicians insult everyone with unending proclamations of success. (Don't be surprised if members of the congress also give themselves a "special" health care system just as they did with Social Security.)

The lesson is simple: there ain't no such thing as a free lunch.

Saturday, March 10, 2007

"How's that working out for you -- being clever?"

Timeless political commentary

Insincerity. Gratuitous appeals to emotion. Tired clichés. Focus-groupped pablum. Wanton demagoguery.

Refuse to allow your mind to be filled with this trash! Instead, enrich your mind with reasoned, intellectual analysis:

What is the attitude of the democrat when political rights are under discussion? How does he regard the people when a legislator is to be chosen? Ah, then it is claimed that the people have an instinctive wisdom; they are gifted with the finest perception; their will is always right; the general will cannot err; voting cannot be too universal . . .
But when the legislator is finally elected — ah! then indeed does the tone of his speech undergo a radical change. The people are returned to passiveness, inertness, and unconsciousness; the legislator enters into omnipotence. Now it is for him to initiate, to direct, to propel, and to organize. Mankind has only to submit; the hour of despotism has struck.

The passage above comes from The Law by Frédéric Bastiat, available as a two-part audio book from FreeAudio.org.

Remember this one?

Thursday, March 08, 2007

Mr. Dylan can moo! Can you?

Yes, it's as cool as you imagine!

Waterfalls are bad, mmmkay?

Adobe's Photoshop team reports success and joy from abandoning waterfall! For details, read an interview with co-architect Russell Williams in which he talks about the benefits of such practices as nightly builds; running, tested features; and continuous integration.

42 Presidents in 10 Minutes

42 presidents remain

Named so far:
None

Saturday, March 03, 2007

Ron Paul on CNN

In this appearance from February 26, Dr. Ron Paul talks about economics, foreign policy, immigration reform, and upholding the constitution.

Saturday, February 24, 2007

My first monadic program!

Problem 32 from Project Euler reads

The product 7254 is unusual, as the identity, 39 x 186 = 7254, containing multiplicand, multiplier, and product is 1 through 9 pandigital.

Find the sum of all products whose multiplicand/multiplier/product identity can be written as a 1 through 9 pandigital.

Not one of my brighter moments, the first approach I considered was applying goon-force to permute a list of eleven characters ('1' .. '9', 'x', and '=') -- a search space of almost 40 million -- looking for well-formed and valid statements.

Initially, I looked at using Text.Regex. As I was fishing for examples to crib from, I saw a suggestion that people may as well use Parsec, the monadic parser combinator library. So let's knock out the preliminaries:

> module Main where
>
> import Data.List hiding (map)
> import Text.ParserCombinators.Parsec

A parser for the simple expressions reads easily:

> num :: Parser Int
> num = do ns <- many1 digit
>          return $ read ns
>
> expression :: Parser (Int,Int,Int)
> expression = do multiplier <- num
>                 times <- char 'x'
>                 multiplicand <- num
>                 equals <- char '='
>                 product <- num
>                 return (multiplier, multiplicand, product)

Generating permutations is no problem in Haskell:

> permutations :: [a] -> [[a]]
> permutations [x] = [[x]]
> permutations xs =
>   [ y : zs
>   | (y,ys) <- selections xs
>   , zs     <- permutations ys
>   ]
>
> selections []     = []
> selections (x:xs) = (x,xs) : [(y,x:ys) | (y,ys) <- selections xs]

I'd been wanting to solve as a learning example one of the Project Euler problems using monads. As I tried to shoehorn the problem into a monadic solution, I remembered the characterization of the Maybe monad as being useful for computations that can fail, and I saw two possibilities for failure: garbage input (e.g., "x=123456789") and false statements (e.g., "1x2=3456789").

Having a particular permutation, check tests whether it's well-formed and valid:

check :: String -> Maybe Int
check s = do
  result <- parseExpr s
  p <- validProduct result
  return p

parseExpr :: String -> Maybe (Int,Int,Int)
parseExpr s =
  case parse expression "expression" s of
    Left err -> Nothing
    Right tuple@(mr,md,pr) -> return tuple

validProduct (mr, md, pr)
  | mr * md == pr = Just pr
  | otherwise = Nothing

The test goes just as you would describe it to someone else: parse the input to extract the components of the mulitiplication and then check whether the multiplication holds. Simple.

You wonder, 'But what about when the parse fails or when the statement is bogus?' Those checks are still happening, but the Maybe monad and the do-notation syntactic sugar are performing those checks implicitly! "Control" (to borrow an imperative concept) reaches the return p line only if both the parse and validProduct succeed. Otherwise, check bails and returns Nothing.

All that's left to do is feed it input and sum the result. Note: it's very s-l-o-w.

p32 = sum $ elems $ fromList $ catMaybes $ map check (permutations cs)
  where cs = ['1','2','3','4','5','6','7','8','9','x','=']

An obvious improvement is to use nub instead of (elems . fromList). Even better, lists are also monads, so Maybe distractions disappear with only a few very minor changes:

> p32 = sum (nub $ concatMap check (permutations cs))
>   where cs = ['1','2','3','4','5','6','7','8','9','x','=']
>
> main = print p32
>
> check :: (Monad m) => String -> m Int
> check s = do
>   result <- parseExpr s
>   p <- validProduct result
>   return p
>
> parseExpr :: (Monad m) => String -> m (Int,Int,Int)
> parseExpr s =
>     case parse expression "expression" s of
>       Left err -> fail (show err)
>       Right tuple@(mr,md,pr) -> return tuple
>
> validProduct :: (Monad m) => (Int,Int,Int) -> m Int
> validProduct (mr, md, pr)
>   | mr * md == pr = return pr
>   | otherwise = fail "invalid product"

This works because failure in the list monad is the empty list, and concatMap gets rid of all the empties.

Saturday, February 17, 2007

Very touching short animation

I saw this video when my wife was in St. Louis at a baby shower for one of the girls she played volleyball with in college and my kids were at my mother-in-law's. So moving.

Thursday, January 11, 2007

A candidate worth supporting

Ron Paul filed papers to form an exploratory committee!

In an interview, Dr. Tom DiLorenzo said, "No one is proposing anything near constitutional government. I consider the act of voting to be treasonous to the Constitution." Unlike so many of his colleagues, Paul has read but also works diligently to apply the constitution properly.

Peace. Freedom. Property. Vote for Dr. Ron Paul.

Wednesday, January 03, 2007

Bo stole my line!

Bo stole my line! (Not really -- he gave an attribution and everything -- but "Bo follows MLA style" is a pretty lame headline.)

A relative of my wife's -- one of those baby-mama-sista-cousin kind of deals -- knows someone connected to the Bama athletic department and had been saying since around Thanksgiving that Nick Saban was a done deal.

Given Saban's strong denials, it didn't seem likely at all. Bill, I'm glad I was wrong!

Shula was a clown. He's gone, so it's morning in Alabama.