Friday, July 31, 2009

Mrs. B's tasty cooking

I was enjoying a wonderful homemade lunch today and tweeted, “Sam's chicken pot pie == delicious.”

Over on Facebook, someone commented

if (sam's oatmeal cream pies = delicious)
    goto "mmm mmmm yummy!"
else
    try another one
end
Her oatmeal cream pies are great, but her taco salad will make you forget your troubles.

Geeky, yes—“the geekiest thing ANYONE has ever done” was someone else's rejoinder—but I responded with

mapM_ putStrLn $
samsOatmealCreamPies >>=
(>> return "mmm mmmm yummy!") . guard . delicious
Assimilation may be complete.

Monday, July 27, 2009

Simple FitNesse example with CSlim

Tinkering with the FitNesse acceptance testing system, I cloned the CSlim repo, but its README was short on detail about getting the thing to talk to FitNesse.

Attempting to build (on Ubuntu karmic) out of the box failed:

$ make
compiling ListExecutor.c
compiling SlimConnectionHandler.c
compiling SlimList.c
compiling SlimListDeserializer.c
compiling SlimListSerializer.c
compiling SlimUtil.c
compiling StatementExecutor.c
compiling SymbolTable.c
compiling SocketServer.c
compiling TcpComLink.c
Building archive lib/libCSlim.a
ar: lib/libCSlim.a: No such file or directory
make: *** [lib/libCSlim.a] Error 1
The workaround is straightforward: mkdir lib followed by make.

So now what?

$ ./CSlim_server --help
getaddrinfo: Servname not supported for ai_socktype
Following the recommendation in the SLiM docs, I created a page called CslimTest (by editing FrontPage to contain a new line with CslimTest) that contained merely
!define TEST_SYSTEM {slim}
After I clicked the Test button, the page cleared, paused for a few seconds, and then gave a red box with "Testing was interupted and results are incomplete." Clicking Output Captured, I saw a stacktrace that ended with java.lang.ClassNotFoundException: fitnesse.slim.SlimService.

Maybe I could crib from the docs for another server. The FitNesse download page points to servers for various languages, and from there I arrived at a Getting Started page for fitSharp, a C# server for FitNesse, which had the following config:

!define TEST_SYSTEM {slim}
!path c:\myfolder\mytest.dll
!define COMMAND_PATTERN {%m -r fitSharp.Slim.Service.Runner,c:\program files\fitsharp\fitsharp.dll %p}
!define TEST_RUNNER {c:\program files\fitsharp\Runner.exe}
So next I try
!define TEST_SYSTEM {slim}
!define TEST_RUNNER {/home/gbacon/src/cslim/CSlim_server}
I got a similar failure, but this time the class that failed to load was .home.gbacon.src.cslim.CSlim_server.

Even though the fitSharp used !path for test assemblies, Drew suggested pointing it to CSlim_server as in

!define TEST_SYSTEM {slim}
!path /home/gbacon/src/cslim/CSlim_server
But the test still died with ClassNotFoundException.

I monkeyed more with COMMAND_PATTERN, and finally got a quick error using

!define TEST_SYSTEM {slim}
!path /home/gbacon/src/cslim/CSlim_server
!define COMMAND_PATTERN {%m %p}
Instead of Output Captured, I see Tests Executed OK. I notice in src/Main/DecisionTableExample.c there's a Division fixture that seems to match the example in the two-minute example, so I copy-and-paste to get
!define TEST_SYSTEM {slim}
!path /home/gbacon/src/cslim/CSlim_server
!define COMMAND_PATTERN {%m %p}

|eg.Division|
|setNumerator|setDenominator|Quotient?|
|10          |2             |5        |
|12.6        |3             |4.2      |
|100         |4             |33       |
Red box still, and the tests aren't running. Not much help in the output log, but FitNesse complained: "Cannot run program "fitnesse.slim.SlimService".

Remove %m from COMMAND_PATTERN. Progress! Nothing's running, but I see a bunch of exceptions and text with yellow backgrounds, such as "eg.Division Could not find class eg.Division." Maybe it doesn't like the leading eg.

!define TEST_SYSTEM {slim}
!path /home/gbacon/src/cslim/CSlim_server
!define COMMAND_PATTERN {%p}

|Division|
|setNumerator|setDenominator|Quotient?|
|10          |2             |5        |
|12.6        |3             |4.2      |
|100         |4             |33       |
Now Division goes green, but it doesn't like the input methods ("Method setSetNumerator[1] not found in Division." for example). The method names in the fixture are setNumerator, setDenominator, and Quotient, so mangling must be happening somewhere.

That's what I get for trying to think ahead of it:

!define TEST_SYSTEM {slim}
!define COMMAND_PATTERN {%p}
!path /home/gbacon/src/cslim/CSlim_server

|Division|
|numerator|denominator|Quotient?|
|10       |2          |5        |
|12.6     |3          |4.2      |
|100      |4          |33       |
Now the first two rows pass, and the third fails as expected.

Wednesday, July 22, 2009

Hosed at the gas pump — by your debit card

Watch out for this gotcha when using a debit card at the gas pump where funds in your checking account can be "reserved" for days after making gasoline purchases.

My wife and I load Wal-Mart gift cards with our gas budget, which we then use to buy gas at Sam's. This gives us the best of both worlds: the wisdom of the envelope system with the convenience of plastic.

Sunday, July 19, 2009

First thing Monday morning!

Pennsylvania state employees' most recent paychecks were some 30% short, and legislators are waving the threat of goose eggs on the next round. Flat-broke California has already been paying in IOUs, but banks are starting to balk at their worthless paper. Many other states were slow to make good on refunds due taxpayers.

Now turn the tables. We all know people who've been there, and some have been so unfortunate as to experience it personally. The taxman demands payment, and pleas of hardship or budget problems—the same appeals California and Pennsylvania are making now—find no mercy.

“If you don't pay up, we'll garnish your wages.” Revenue agents may even threaten property seizure or jail time.

Government jobs are widely considered to be the among the safest. Civil servants tend to make less money, but the perception of increased security is part of the compensation. GEICO, the Government Employees Insurance Company, was founded with a business model limiting policies to government employees on the bet that they're less likely to be risk takers.

These tough times where even governments can't make payroll help us all appreciate the importance of having an emergency fund as cushion against these sort of blows. How well could you absorb the hits that folks in California and Pennsylvania have taken? Personal-finance advisor Dave Ramsey recommends setting aside 3 to 6 months of expenses at Baby Step 3. But where's the extra money to sock away supposed to come from?

Which brings me to my tip. How big were your income-tax refunds last year, state and federal? Big refunds are not money from heaven: you just paid too much in taxes. Using refunds as a savings program is a rotten plan because the government doesn't pay you interest on your generous loan to them. Now states are earning slow-pay credit ratings, so don't leave your state or the feds owing you money you may need.

First thing Monday morning go to your accounting or human resources department and ask for a new W-4 form to adjust your federal withholding and the appropriate form for your state withholding. The tables on these forms are conservative and will cause you to overpay. TurboTax, for example, has a withholding calculator that gets you close to zero, not much owed either way. Use your most recent paystub and last year's returns to fill in the blanks and get your new withholdings. Easy-peasy.

The point is more money in each paycheck. By increasing the allowances you claim on these forms, less money will be deducted every payday as prepayment on next year's tax bill. So instead of sending that money to the IRS and then waiting—and hoping—for them to send it back next April, keep your hard-earned money. Think of it as getting your refund early. Use it to bulk up your emergency fund, increase 401k or IRA contributions, invest in your professional development, or whatever purpose you see fit.

If you have questions or concerns, be sure to consult with your tax professional.

Saturday, July 18, 2009

“The statists are in control.”

I'd like to be as sure as Peter Morici is in this CNBC clip about the fate of cap-and-trade and the Bride of HillaryCare.

In support of his bullish view, he uses an odd metaphor of an aircraft landing on the deck of a carrier and then, “The politics are very important here. I think cap-and-trade's going down. I think healthcare's going down. And when investors see that, and when the public sees that, and when entrepreneurs see that, they'll say, ‘Hey, America's back! The statists are out!’”

Peter Schiff responds: “I hope these things are defeated. If they're not defeated, it's just gonna take a bad situation and make it worse. But the statists aren't out. They're here; they're in control.”

I'm pleased that this pejorative has been making a comeback in recent months, but it's at least eight years too late.

If you're picking up despair, it's an after-effect of Valkyrie's cinematography, which my wife and I watched last night. Portraits everywhere of Der Führer. Endless arrays of Nazi black, white, and red on stark display. The rule of man. The horror of people being tyrannized by this evil criminal gang and, even worse, so many enthusiastically taking part in its atrocities. It's a frightening historical demonstration of the ratchet effect's potential.

Here in America, the cutting-edge, heady mathematical techniques of addition and subtraction show the situation has also gone out of control, albeit along a different axis. The feds will never pay off their debts—not in real terms, that is. They cannot possibly make good on their promises of Medicare and Social Security: certainly not with Bush's addition to the former, and with the latter, everyone up to around my age cohort is being forced to pay fully fifteen percent of annual income into a system from which realistic hope of receiving benefit is zero. The same goes for paper money and the rest of the welfare state. Already, people are arguing over who should be forced to the back of the line, and the state-run rationing system for healthcare hasn't yet been instituted!

In the long run, the bad guys can't win because they're fighting economic law, but between now and then can be dreadful. The decent remnant of Germans, whom it's easy to forget when jingoistically lumping them all together as “dirty Nazi krauts,” ultimately depended on calamity to knock them off the bad course they were on.

Not a great place to invest one's hopes. Ideas have power.

Thursday, July 16, 2009

Monadic takeWhile

Say we have a list of actions:
printx :: (Show a) => a -> IO a
printx x = do
    print x
    return x

as :: [IO Int]
as = map printx [1..5]
We can then use sequence to execute the actions and collect the results:
*Main> sequence as
1
2
3
4
5
[1,2,3,4,5]
Note that the single-number lines are from print, and the last line is the list of values returned from the actions. A slightly less trivial action clarifies the distinction:
*Main> mapM (\x -> printx x >>= return . (*2)) [1..3]
1
2
3
[2,4,6]
Applying η-reduction yields (return . (*2) =<<) . printx—interesting but slightly ugly. Also note that mapM is defined in terms of sequence:
mapM f as = sequence (map f as)
Now say we want to stop executing these actions after a certain point:
*Main> takeWhile (< 3) $ sequence as

<interactive>:1:26:
    Couldn't match expected type `[a]' against inferred type `IO Int'
      Expected type: [[a]]
      Inferred type: [IO Int]
    In the first argument of `sequence', namely `as'
    In the second argument of `($)', namely `sequence as'
Unlike sequence, takeWhile is pure, so we have to lift it inside the monad:
*Main> liftM (takeWhile (< 3)) (sequence as)
1
2
3
4
5
[1,2]
The result is deceptive: although it is a subset, all the actions ran. Not a big deal in the case of printing to the standard output, but potentially disastrous if the canonical launchTheMissiles were lurking.

But isn't Haskell supposed to be lazy? To see why they all run, look at the definition of sequence:

sequence xs = foldr (liftM2 (:)) (return []) xs

liftM2 :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c
liftM2 f m1 m2 = do
    x1 <- m1
    x2 <- m2
    return (f x1 x2)
We have no opportunity to prevent m2 because it runs unconditionally. We could redefine liftM2 as in the following:
sequenceWhile p xs = foldr (liftM2' (:)) (return []) xs
  where liftM2' f m1 m2 = do
          x1 <- m1
          guard $ p x1
          x2 <- m2
          return $ f x1 x2
But note the type:
*Main> :t sequenceWhile 
sequenceWhile :: (MonadPlus m) => (t -> Bool) -> [m t] -> m [t]
IO is not an instance of MonadPlus (a constraint due to guard), so we must be more deliberate:
sequenceWhile :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
sequenceWhile p xs = foldr (liftM2' (:) []) (return []) xs
  where liftM2' f z m1 m2 = do
            x1 <- m1
            if p x1 then do x2 <- m2
                            return $ f x1 x2
                    else return z
Now we don't launch the missiles:
*Main> sequenceWhile (< 3) as
1
2
3
[1,2]
The definition also maintains laziness:
*Main> sequenceWhile (< 3) $ map printx [1..]
1
2
3
[1,2]
Monadic span would also work:
spanM :: (Monad m) => (a -> Bool) -> [m a] -> m ([a], [m a])
spanM _ [] = return ([], [])
spanM p (a:as) = do
  x <- a
  if p x then do (xs,as') <- spanM p as
                 return (x:xs, as')
         else return ([x], as)
Apply it as in the following example. Unlike span, spanM includes the failing value as the last element of the result list:
*Main> (xs,as') <- spanM (< 3) as
1
2
3
*Main> xs
[1,2,3]
*Main> sequence as'
4
5
[4,5]

Tuesday, July 14, 2009

If the code monkey thing doesn't work out

This morning I sat in for Toni on WBHP's The Morning Show with Toni & Gary.

I haven't yet gotten the all-clear from Dr. Byrd, so Sam, the kids, and I all left at 7 this morning for the radio station. The instructions sent me to the back of the building where there was a ten-foot fence with razor wire at the top. I called Nate the producer, and he met us at the door. Sam and the kids headed off for a hearty breakfast at Cracker Barrel.

I learned later that the razor wire and security door were there because a woman was working nights there, and a stalker would hang out around back, peeking in the windows and engaging and other unwelcome behavior. What's with people?

So Nate and I traversed the twisty passages (all alike!) until we came to the broadcast booth. He hooked up my earphones and mentioned that Gary was still at the TV station. I opened up my Ducks Unlimited portfolio and glanced over my notes while I listened to prerecorded banter between the two regular hosts where Gary was talking about getting in trouble as a youngster for setting a fire in the woods.

Today wasn't my first time in a broadcast booth. Back in 2002 when I ran for state senate, WVNN's Fred Thompson and Peter Thiele (no, a different one) invited me to be on their morning show where I botched my opportunity by failing to stay on message.

Five or ten minutes later, Gary strolled in, and we exchanged pleasantries. He offered to fetch me a cup of coffee, and when he returned, we laughed about my own pyromania-gone-bad story. A neighborhood kid and I were lighting pine straw on fire in a hole and then snuffing it out&emdash;with more pine straw. As you might imagine, we soon lost control of the fire and had to run to a nearby road crew for help. While they dug a control ditch, I ran home and told Mom between breaths to call the fire department. Somehow I managed not to get in trouble for that: maybe an unusual bout of willful ignorance.

Finally on air, Gary introduced me and broke the ice by asking, as people commonly do, whether I'm related to Kevin Bacon. I told him I've learned to answer to Kevin because my last name is evidently easy to remember, but the first must be a little trickier.

The remainder of the show was gone in an Augenblick. We talked about family, work, and topics such as the state's slow-pay record on tax refunds, California versus Texas, whether I'd consider running for office again, and Dave Ramsey's Financial Peace University. For the last one, I wondered aloud about requiring sending FPU kits to all members of the congress.

Toni likes to ask trivia questions, so I brought a few with me. I wanted to ask about outlaw William H. Bonney Jr. (a.k.a. Billy the Kid) because it was the anniversary of his capture, but Gary covered it in a prerecorded segment. The questions (and answers) I did ask:

Which American patriot emphatically declared, "Is life so dear, or peace so sweet, as to be purchased at the price of chains and slavery? Forbid it, Almighty God!" Patrick Henry

A 2006 study published in Cancer Research showed that capsaicin, the chemical that makes buffalo wings, for example, hot is effective in fighting what form of cancer? Prostate

On this day in 1798, a bill was enacted in Congress that criminalized "false, scandalous, and malicious writing" against elected officials. What was the name of this act? Sedition Act

In an essay called "Gold and Economic Freedom," a well-known economist wrote, "In the absence of the gold standard, there is no way to protect savings from confiscation through inflation." Who was this economist? Alan Greenspan

One caller correctly answered the question about Patrick Henry. I was pleased when another caller guessed Murray Rothbard instead of the world's most famous counterfeiter. My friend Jenny texted me promptly about the Sedition Act because she'd recently seen the John Adams series.

I managed to work in a couple of plugs too. In another text, Jenny (a huge Alabama fan) asked, "Can I get a Roll Tide?" Last night, I told Carey I'd mention Haskell somehow, but the best I was able to do was a parting shot. Gary gave me a puzzled look and said, "I hope we shouldn't have bleeped whatever it is you just said."

I was sorry to see nine o'clock roll around. Gary mentioned the possibility of having me sit in for him while he's out next month, and I told him to just say when.

Saturday, July 11, 2009

Just for you, Madeline

My five-year-old daughter is learning to read. I made flash cards for us to practice phonics and recognition, and I wrote this simple app to give her a way to practice on her own too. Thanks to the Wiktionary folks for the pronunciations.

Along with the buttons, you can advance by pressing Enter or Right-Arrow and hear the word with S or space bar.

The code is available on GitHub.

Thursday, July 09, 2009

Gyrigrams

One way to hide spoilers or off-color comments in plain sight is ROT13. The popular Usenet newsreader trn even has a builtin command to unmask text protected in this fashion.

To understand ROT13, imagine an analog clock face. Instead of the numbers one to twelve, this face has the letters A to Z. To get the secret code for any letter, find the letter on the clock face and advance 13 spots. For example, A becomes N, and X becomes K.

Implementing ROT13 is straightforward with the tr command in Unix:

tr A-Za-z N-ZA-Mn-za-m
The word anagram comes from a Greek word for shuffling letters. What about gyrigrams, pairs of words equivalent up to ROT13? (The Greek word γυρίζω means turn or return, so it indicates rotation and also the cipher's symmetry.)

This post is a literate Haskell program that will find interesting gyrigrams in a dictionary file. Copy-and-paste it into a file named gyrigram.lhs to get a runnable program.

Some front matter:

> module Main where
> import Data.Char (toLower)
> import Data.List (sort)
> import qualified Data.Map as M
> import qualified Data.Set as S
> import System.Environment (getArgs, getProgName)
> import System.Exit (ExitCode(ExitFailure), exitWith)
> import System.IO (hPutStrLn, stderr)
To run the program, either provide the path to your dictionary file as the sole command-line argument, or omit it to use /usr/share/dict/words:
> usage :: IO a
> usage = do
>   me <- getProgName
>   hPutStrLn stderr $ "Usage: " ++ me ++ " [ dictionary ]"
>   exitWith (ExitFailure 1)
The implementation of rot13 below performs a table lookup for all characters in the input. Characters outside the set [A-Za-z] pass through unchanged.
> rot13 :: String -> String
> rot13 = map $ \c -> maybe c id (M.lookup c table)
>   where table = M.fromList $ zip (uc ++ lc) (uc' ++ lc')
>         (uc,  lc)  = (['A'..'Z'], ['a'..'z'])
>         (uc', lc') = (rot uc,     rot lc)
>         rot xs = [drop,take] >>= \f -> f 13 xs
To find all gyrigrams, we stuff the input list, normalizing to lowercase, in a Set for quick lookups. Then for each word in the input, probe for its rot13 counterpart and add hits to the result. Removing matches from the dictionary prevents duplicated values. Note also that we ignore single-letter words.
> gyrigrams :: [String] -> [(String,String)]
> gyrigrams xs = go dict xs
>   where go _ [] = []
>         go d (w:ws)
>           | d `has` w' = (w,w') : go d' ws
>           | otherwise  =          go d  ws
>           where has = flip $ S.member . lc
>                 w' = rot13 w
>                 d' = foldr (S.delete . lc) d [w,w']
>         dict = S.fromList $ map lc $ filter ((>1) . length) xs
>         lc = map toLower
The main program reads the input and prints a sorted list of pairs:
> main :: IO ()
> main =
>   getPath >>= readFile >>= mapM_ (putStrLn . show') .
>                              sort . gyrigrams . lines
>   where show' (a,b) = a ++ " => " ++ b
Argument processing:
> getPath :: IO FilePath
> getPath = getArgs >>= go
>   where go [path] = return path
>         go []     = return "/usr/share/dict/words"
>         go _      = usage
One pair is especially interesting because they're both gyrigrams and synonyms: irk and vex.

Wednesday, July 08, 2009

Tuesday, July 07, 2009

Sixty days!

Although we're in the miserable high-heat, high-humidity dog days of summer, college football season is less than sixty days away, with pleasant football weather following soon behind!

Considering we're replacing a quarterback and a Outland Trophy-winning left tackle, we're looking at a favorable schedule for a rebuilding year. The one tough road game all year is the opener in Atlanta against the Virginia Tech. We have rivals UT and LSU at home. Yes, this year's Iron Bowl is at Jordan-Hare, but we play better there anyway. The game at Oxford will be one to look out for if the Rebels live up to the love they've been getting already, but that will become clearer with time. If we play Florida, it'll be in Atlanta.

Notice my careful choice of adjective in the preceding paragraph: ours is favorable, but for the other guy's team it's always a cupcake schedule. Now before you partisans of the Pac-10, ACC, Big T'Eleven, and other girls field hockey leagues get going, you know how even a favorable SEC schedule compares with your Sadie Hawkins dances.

Important questions remain. Will the Tide have anything resembling a pass rush this year? All through the regular season last year, we managed to get by with a shaky secondary, but Florida and Utah did their homework and fully exploited that weakness. McElroy was understudy to John Parker Flock of Seagulls but never managed to upstage him. Was this for team stability or because Mac didn't have it? Will a herd of flat-out hosses in the backfield be enough to offset the disadvantage of a green O-line?

Will the Southeastern Conference be home to the national champs for the fourth year in a row?

Monday, July 06, 2009

A programmable semicolon explained

Don Stewart, for example, uses the folksy characterization of monads as providing us with programmable semicolons. How does this mystifying concept work?

Say we want to compute all Pythagorean triples such that a, b, and c are at most 25. We might use the following predicate to test candidate triples:

p a b c = a*a + b*b == c*c
Then the definition of triples is
triples = do
 a <- [1..25]
 b <- [a..25]
 c <- [b..25]
 guard (p a b c)
 return (a,b,c)

*Main> triples
[(3,4,5),(5,12,13),(6,8,10),(7,24,25),(8,15,17),(9,12,15),(12,16,20),(15,20,25)]
Although triples uses imperative-looking do-notation, it's not in the IO monad but the list monad:
*Main> :type triples
triples :: [(Integer, Integer, Integer)]
How does triples separate the wheat from the chaff with no conditionals? What's the guard thingy? This post is supposed to be about programmable semicolons, but the above example doesn't have any! Let's peek under the hood to answer these questions.

Semicolons are optional thanks to the layout rule, but we could have been explicit:

triples = do {
 a <- [1..25];
 b <- [a..25];
 c <- [b..25];
 guard (p a b c);
 return (a,b,c)
}
Peeling back a few more layers of the onion, we first “desugar” triples by mechanically applying—so easy even a machine can do it!—the definition of do-notation:
triples =
 [1..25]         >>= \a ->
 [a..25]         >>= \b ->
 [b..25]         >>= \c ->
 guard (p a b c) >>
 return (a,b,c)
In the spots where the semicolons are (whether implicit or explicit), notice that we also get applications of the bind operator, concatMap in the list monad, and hence a programmable semicolon! Equational reasoning allows us to substitute “equals for equals” to produce an equivalent definition:
triples =
 concatMap (\a ->
   concatMap (\b ->
     concatMap (\c ->
       guard (p a b c) >> return (a,b,c))
       [b..25])
     [a..25])
   [1..25]
Somehow guard must be doing the work of
if p a b c then [(a,b,c)] else []
In the list monad, return is
return x = [x]
That is, it wraps its argument in a singleton list as with [(a,b,c)] above.

Now consider the definition of guard:

guard           :: (MonadPlus m) => Bool -> m ()
guard True      =  return ()
guard False     =  mzero
In the context of the list monad, it is equivalent to
guard cond = if cond then [()] else []
Substituting the definitions of guard and >>:
triples =
 concatMap (\a ->
   concatMap (\b ->
     concatMap (\c ->
       concatMap (\_ -> [(a,b,c)])
         (if p a b c then [()] else []))
       [b..25])
     [a..25])
   [1..25]
Now we see how guard blocks invalid triples: by nullifying the innermost concatMap. For each valid triple, guard provides a ticket that allows it to pass. The nested applications of concatMap throw away the empty lists and result in a flat list of Pythagorean triples.

Thursday, July 02, 2009