Intro to QuickCheck and Hpc

And you thought my Haskell honeymoon was over.

So the other day, I finally got around to using the legendary QuickCheck testing library for a semi-serious project of mine. And I must say that I am very impressed with QuickCheck — it caught two subtle (but serious) errors in my core functions — in day one! I’m going to explain some basic concepts to help you get started with QuickCheck immediately; afterwards I’ll throw in a brief discussion about the Haskell Program Coverage (“Hpc”) tool, too, since it goes well with QuickCheck.

QuickCheck

The point of QuickCheck is to generate tons of random, junk values (the nastier-looking, the better) to feed into your functions. Well, they’re not really junk values, from a type system perspective, but the point is to generate lots of edge-case values that we forget to consider when writing the code. QuickCheck supports testing of pure functions as well as monadic ones (ST monad), but I’ll just focus on the pure functions because that’s what I have experience with.

So the next question is, how does QuickCheck generate random values? Well, if your function uses any of the basic types like Int, [Integer], Double, Word64, etc., QuickCheck knows how to generate the random values already. But if you use a custom type, or a unique combination of ordinary types (e.g., (Maybe Int, Maybe Int)), you have to instruct QuickCheck how to generate it. You do this by writing an instance for QuickCheck’s Arbitrary typeclass.

So let’s say my custom type is (Maybe Int, Maybe Int), and that it has a special requirement: if it is (Just a, Just b), then b must be greater than a. No problem.

newtype MPair = MPair (Maybe Int, Maybe Int)
    deriving (Show)

instance Arbitrary MPair where
    arbitrary = do
        -- First, generate a random Int.
        a <- arbitrary :: Gen Int
        -- Now generate another random Int, but such that it is greater than *a*.
        b <- suchThat (arbitrary :: Gen Int) (>a)
        -- Now choose between either (Just a), or Nothing.
        a' <- elements [Just a, Nothing]
        -- Repeat the same coin flip for *b*.
        b' <- elements [Just b, Nothing]
        -- Return the random result.
        return $ MPair (a', b')

There is a method to the madness! There are other useful combinators besides suchThat and elements, of course.

So now you’ve told QuickCheck how to generate the random values to stress-test your functions. The next step is to define the stress-tests. In the QuickCheck world, such testing functions are used to test very specific properties of your functions that must hold true no matter what you throw at it. By convention, these functions are named “prop_[function name]”.

So here’s an example, prop_isTouching, which, appropriately enough, tests the isTouching function..

prop_isTouching :: MPair -> MPair -> Bool
prop_isTouching x y =
    isTouching x' y' == isTouching y' x'
    where
    x' = fromMPair x
    y' = fromMPair y

isTouching :: (Ord a) => (Maybe a, Maybe a) -> (Maybe a, Maybe a) -> Bool
isTouching p@(pStart, pEnd) q@(qStart, qEnd)
    -- if no pair has both of its values defined, then just return False;
    -- technically this notion is incorrect, but the greater codebase behind this
    -- interprets it this way, so it's OK
    | not (isBoth p) || not (isBoth q) = False
    -- if one or both pairs are empty, then return False
    | isBlank p || isBlank q = False
    | isLeft q = inP qStart'
    | isRight q = inP qEnd'
    | isLeft p = inQ pStart'
    | isRight p = inQ pEnd'
    | otherwise = inP qStart'
        || inP qEnd'
        || inQ pStart'
        || inQ pEnd'
    where
    pStart' = fromJust pStart
    pEnd' = fromJust pEnd
    qStart' = fromJust qStart
    qEnd' = fromJust qEnd
    inP = isInside (pStart', pEnd')
    inQ = isInside (qStart', qEnd')

isLeft
    , isRight
    , isBoth
    , isBlank :: (Maybe a, Maybe a) -> Bool
isLeft (a, b) = isJust a && isNothing b
isRight (a, b) = isNothing a && isJust b
isBoth (a, b) = isJust a && isJust b
isBlank (a, b) = isNothing a && isNothing b

fromMPair :: MPair -> (Maybe Int, Maybe Int)
fromMPair (MPair a) = a

isInside :: (Ord a) => (a, a) -> a -> Bool
isInside (a, b) c = a <= c && c <= b

You might be wondering, “Hey, I thought you were going to test a function that takes (Maybe Int, Maybe Int), not (Maybe a, Maybe a)!” Well, believe me, it pays off a lot to write higher-order functions like this that work on multiple types. The fact that we can test it using Maybe Ints (a very simple type) is just one benefit. Notice how I’ve made sure to restrict isTouching‘s arguments to the Ord typeclass, since we expect the right hand value in the pair to be greater than the one on the left (if it exists). The fancy Arbitrary instance up above was not in vain.

Anyway, the isTouching function merely checks to see if one given pair “falls in” or “touches” the other pair of values. It’s a pretty mundane function, but such functions often form the backbone of the rest of your code, so it’s really important to get these 100% right. The various helper functions like isLeft, isRight, fromMPair, etc. may seem annoying, as if they get in the way of the example to test isTouching itself. But think about it: all of these auxiliary functions will, by virtue of their necessity, be tested by calling prop_isTouching! And if prop_isTouching keeps failing (and your custom type or function is too complex for a 10-minute debugging session), you can always add more prop_ functions to test these auxiliary functions in isolation. Haskell embraces small, cute functions, and so should you!

The prop_isTouching function itself is straightforward enough: it tests the “commutative” property of isTouching — that the order of the arguments does not matter.

So far so good. Now we just need to run prop_isTouching hundreds (or thousands) of times to see if it holds. QuickCheck defines some basic test running functions, for use in the IO monad. The simplest one is aptly named quickCheck. So, we can run the function above like so:

import Test.QuickCheck

import [Your testing module, where prop_isTouching resides]

main :: IO ()
main = quickCheck prop_isTouching

This will run prop_isTouching 100 times with the default testing settings. But default settings are usually not desirable (for me, I only caught errors when I “upped” the number of runs to 1000, among other things). Oh, and quickCheck will not tell you the name of the function it is testing. So here is a more useful version:

{-# LANGUAGE RecordWildCards #-}
import System.Exit
import Test.QuickCheck

import [Your testing module, where prop_isTouching resides]

-- Rigorous test arguments.
rigorous :: Args
rigorous = Args
    { replay = Nothing
    , maxSuccess = 1000 -- tests to run
    , maxDiscard = 1000 -- the number of tests that are thrown out and ignored b/c of "==>" conditions, before "giving up" and failing due to too many discarded tests
    , maxSize = 1000 -- if a prop_ function uses a list ([]) type, maxSize is the max length of the randomly generated list
    , chatty = True
    }

-- Quick test arguments.
quick :: Args
quick = Args
    { replay = Nothing
    , maxSuccess = 100
    , maxDiscard = 100
    , maxSize = 100
    , chatty = True
    }

runTests :: [String] -> IO ()
runTests as = case as of
    [] -> runTests' quick
    a -> case head a of
        "1" -> runTests' quick
        "2" -> runTests' rigorous
        _ -> runTests' quick
    where
    runTests' :: Args -> IO ()
    runTests' testArgs = do
        -- if all of your prop_ functions are of the same type, you can put
        -- them in a list and use mapM_ instead
        f prop_isTouching "prop_isTouching"
        f prop_someOtherFunc1 "someOtherFunc1"
        f prop_someOtherFunc2 "someOtherFunc2"
        f prop_someOtherFunc3 "someOtherFunc3"
        f prop_someOtherFunc4 "someOtherFunc4"
        where
        f prop str = do
            putStrLn str
            quitOnFail =<< quickCheckWithResult testArgs prop
        quitOnFail r = case r of
            -- pattern match with just two dots with RecordWildCards because I'm lazy
            Success{..} -> return ()
            _ -> exitFailure

main :: IO ()
main = getArgs >>= runTests

If you compile the above as “test”, then running “./test 2” will use the “rigorous” test settings. The key difference is that instead of quickCheck, we use quickCheckWithResult. With it, we can provide our choice of test settings (the Args type), and also get some feedback on what the test results were. For simplicity’s sake, we only check if the test was a complete success; if it’s anything else, we abort immediately.

Here’s a quick note about the term “shrink” that you might encounter: if QuickCheck spots a failure, it will first try to shrink the size of the random input repeatedly while maintaining the “failure” result (and QuickCheck will tell you about how many shrinks were performed). This is to help you work with reasonably small values (esp. useful if you have list arguments with hundreds of items each, like in prop_foo above).)

The careful reader would have wondered what the “==>” was about in the comments. Well, the “==>” function is called the “implication” function, and is used to throw out invalid values before running the prop_ function. It’s another way to customize the random value, sort of like how we defined a custom Arbitrary instance up above for the MPair type synonym. For example,

prop_foo :: [Int] -> [Int] -> Prop
prop_foo xs ys =
    not (null xs) ==> -- xs must not be null
    (length ys > 3) ==> -- ys must have at least 4 elements
    foo xs ys == foo ys xs

and it only gets to the “foo xs ys == bar xs ys” part if the two statements above are true. The only difference is that we have to end up with a Prop type instead of Bool, as was the case in prop_isTouching. No other part of your testing code needs to change. The advantage in using (==>) is its ease of use — you can trivially write any rare edge-case condition that you know does not conform to the spec, without bothering to write an Arbitrary instance. However, the disadvantage is that QuickCheck will waste time generating invalid inputs before it gets to the test the function in question. Because of this, you should first try to create an instance of Arbitrary before going with (==>).

Here is a version without using (==>) just for illustrative purposes:

import Data.List
import Test.QuickCheck

main = verboseCheck prop_foo

newtype Xs = Xs [Int]
    deriving (Show)
newtype Ys = Ys [Int]
    deriving (Show)

prop_foo :: Xs -> Ys -> Bool
prop_foo (Xs xs) (Ys ys) =
    foo xs ys == foo ys xs

foo :: [Int] -> [Int] -> [Int]
foo xs ys = sort $ xs ++ ys

instance Arbitrary Xs where
    arbitrary = do
    -- xs must not be null
    xs <- suchThat (arbitrary :: Gen [Int]) (not . null)
    return $ Xs xs

instance Arbitrary Ys where
    arbitrary = do
    -- ys must have at least 4 elements
    ys <- suchThat (arbitrary :: Gen [Int]) ((>3) . length)
    return $ Ys ys

That’s it! You now know enough to get started with QuickCheck today. No excuses! Make it a New Year’s resolution for 2012, if you have to!

QuickCheck has taught me to be skeptical of the “if it compiles, it is OK” Haskell attitude — it has really opened my eyes. I now want QuickCheck as a bare minimum testing setup for all of my Haskell code. No tests = poor design (Medieval II: Total War, I’m looking at you…).

QuickCheck can even be used to test C code with the Foreign Function Interface (FFI), so I’m forever tempted to go back to my other C projects and test them with QuickCheck as well (can you imagine the millions of bugs that lie hidden in C code everywhere — that could be exposed with just a little bit of Haskell knowledge and QuickCheck by the everyday developer? Suddenly, I am overcome with optimism… yet I fear that it is really pessimism underneath… hmm.)

Hpc

I said I would mention Hpc at the beginning. So, what does it do?

Simply put, Hpc tells you which codepaths were used (or not used) after running a binary executable. This is a perfect match for the binary you used for running QuickCheck tests, because during the course of its run QuickCheck will have fed tens of thousands of random values into your functions and have visited most, if not all, parts of your code. Thankfully, Hpc is included with GHC, so you already have it! Just compile your binary with the -fhpc flag. Here is the process:

  1. Compile your program with -fhpc. (ghc -fhpc –make foo.hs)
  2. Run your program. (./foo)
  3. Your program should have generated a *.tix metadata file, as well as a .hpc folder with *.mix files for hpc to analyze.
  4. Run hpc report foo for a quick plaintext report on your codepaths.
  5. Run hpc markup foo to generate prettified HTML files for a more comprehensive overview.
  6. Rinse and repeat. Remove the old *.tix files if you don’t want combined results.

One big caveat: make sure to delete any existing object files (*.o, *.hi) that you had earlier which were produced without the -fhpc flag! Otherwise, those portions of code will not generate hpc metadata! Alternatively, instead of deleting every *.o or *.hi file you have down your project’s folder tree, you could also pass the -fforce-recompile flag to ghc (this is the new name for the deprecated -no-recomp flag, which was used (sans explanation!) in Real World Haskell, Chapter 11).

Go forth, fellow Haskell newbies — embrace testing and code coverage analysis today!

Science and Religion (Creationism, etc.)

From what I understand, science seeks measurable truth. By “measurable” I mean something that is verifiable. Logical proofs are verifiable (as are mathematical proofs), and so are things we can touch, see, etc. Anything beyond measure is of no interest to scientists.

There will always be a point where things become “unmeasurable” and “unknown.” It’s sort of like how you run out of answers to a 7-year old’s rigorous adherence to the Socratic method: if you keep asking why something is the way it is, you will eventually run out of answers. You will eventually run up against that boundary of measurable truth.

So this is the reason why I don’t understand why some people think that science can’t coexist with religion. Religion steps in exactly at the point where you cross into the unmeasurable truths. Religion answers questions like, “What happened before the Big Bang?” or “Why did the Big Bang occur?” where science cannot (at least currently). Science and religion, as far as I can see, are our eyes in the realms of measurable and unmeasurable truths, respectively. Interestingly, the study of philosophy sits right on the border, between what is measurable and not measurable, but what is still “true” in some sense of the word.

The problem with Creationism is that it tries (to comedic effect) to claim a huge chunk of science (evolution) as “unmeasurable.” It says that the human eye is so complicated yet so perfectly tuned that it must have had an intelligent creator behind its design. It says that the reason behind the existence of complex, inter-dependent organs is “unmeasurable” — unexplainable — by any scientific means. Of course, they have to blatantly ignore the mountains of evidence in support for the theory of evolution in doing so, as well as the beautiful consistency of it all.

I think the Creationists fear that the teaching of evolution will somehow destroy one’s belief in their Judeo-Christian God. But once you see that the realms of science and religion are *completely* separate, you quickly realize that such fear is unfounded. Rather, the Creationists should be concerned about the teaching of philosophy, as it asks questions that touch on religious teachings more directly.

Alas, unfortunately for the Christians, their Holy Book is embarrasingly wrong (this is the Word of God we are talking about!) on a lot of things because, like Creationism, it makes lots of utterly false statements that fall into what is measurable, into the domain of science. The story of Noah’s Ark is probably the best example. The “Earth is less than 10,000 years old” inference drawn from gathering the ages and lives of those described in the Bible is another one (it’s just plain wrong if you accept that fossils are real; and I’m not talking dinosaur bones — google “stromatolites” for some really ancient fossils). The whole thing about miracles is also problematic, because what was a miracle 2,000 years ago is not a miracle today. And for some reason all the miracles that happen today are limited to those that can be scientifically explained (but this is getting a bit off topic…).

Hmm, I guess teaching scientific knowledge in general will point to a lot of holes in the Bible, or any other Holy Book that dares to come under genuine scientific inquiry. Maybe the Bible should be rewritten. It could be that Noah’s Ark and the other accounts (some guy lived for 500+ years, IIRC) were just falsely written by some crazy guys in 100 BCE. You could just re-write the Bible and get all the good parts, like “love your enemies.” But this will never happen.

Indeed, the problem with pretty much all the world’s religions are that they have a “creation” story about how the Universe began, and end up with wonderfully confusing and comic descriptions that clash against modern scientific knowledge. I guess this is one reason why there has been an increasing rise in Atheism recently — the traditional religions have too many flaws!

Me, I just follow 1 simple code: “do good stuff, and don’t do bad stuff.” Simple, direct, and always correct. Plus, seeing the world this way, the vast majority of people I meet are also adherents of my code, at least from judging how they treat me. I don’t care enough about atheism or agnosticism to identify myself with one or the other.

EDIT: Grammar fix and clarify the title.
EDIT January 3, 2012: Minor wording tweak.

Simple Password Generation with Haskell

So, I’ve been using a custom password generator for a while. It’s great because it has some useful settings like “only generate alphanumeric passwords” or “only generate letters” to deal with stupid, legacy-code websites that refuse to modernize their password handling code. I use this generator to create 50-character passwords, because hey, if it’s randomly generated, then you might as well generate really long passwords! I recently upgraded the pseudorandom number generator (PRNG) to use a cryptographically secure PRNG (CPRNG), just for fun.

Anyway, here is the program:

-- LICENSE: PUBLIC DOMAIN
module Main where

import Control.Monad.State
import Crypto.Random.AESCtr
import Data.Binary (decode)
import qualified Data.ByteString.Lazy as B
import Data.List (nub)
import IO
import System (getArgs)
import System.IO (hSetEcho)

keysChar, keysNum, keysPunc, keysCharNum, keysAll, keysHex :: String
keysChar = ['a'..'z'] ++ ['A'..'Z']
keysHex = ['a'..'f']
keysNum = ['0'..'9']
keysPunc = "`~!@#$%^&*()-_=+[{]}\\|;:'\",<.>/? "
keysCharNum = keysChar ++ keysNum
keysAll = keysChar ++ keysNum ++ keysPunc

giveKey ::  String -> Char -> Int -> Char
giveKey keysCustom c n = extractChar $ case c of
    'i'  -> (keysNum ++ keysHex)
    'j'  -> keysNum
    'k'  -> keysChar
    'l'  -> keysCharNum
    ';'  -> keysPunc
    'h'  -> (keysCharNum ++ keysCustom)
    '\n' -> ['\n']
    _    -> keysAll
    where
    extractChar xs = xs!!mod n (length xs)

showRandomKey :: String -> StateT AESRNG IO ()
showRandomKey keysCustom = handleKey =<< liftIO getChar
    where
    handleKey key = case key of
        '\n' -> liftIO (putChar '\n') >> showRandomKey keysCustom
        'q' -> (liftIO $ putStrLn "\nBye!") >> return ()
        _ -> mapM_ f [0..(49)::Int] >> (liftIO $ putStrLn []) >> showRandomKey keysCustom
        where
        f _ = liftIO
            . putChar
            . giveKey keysCustom key
            . (\n -> mod n (length (keysAll ++ keysCustom) - 1))
            =<< aesRandomInt

aesRandomInt :: StateT AESRNG IO Int
aesRandomInt = do
    aesState <- get
    let (bs, aesState') = genRandomBytes aesState 16
    put aesState'
    return (decode $ B.fromChunks [bs])

main :: IO ()
main = do
    hSetBuffering stdin NoBuffering -- disable buffering from STDIN
    hSetBuffering stdout NoBuffering -- disable buffering from STDOUT
    hSetEcho stdin False -- disable terminal echo
    as <- getArgs
    let as' = filter (\c -> elem c keysAll) . nub $ unwords as
    mapM_ putStrLn
        [ []
        , "poke: 'q'     quit"
        , "      'j'     number"
        , "      'k'     letter"
        , "      'l'     alphanumeric"
        , "      ';'     punctuation"
        , "      'h'     alphanumeric" ++ (if null as' then [] else " + " ++ as')
        , "      'i'     hexadecimal"
        , "      'ENTER' newline"
        , "      else    any"
        , []
        ]
    aesState <- makeSystem -- gather entropy from the system to use as the initial seed
    _ <- runStateT (showRandomKey as') aesState -- enter loop
    return ()

Yes, the CPRNG used is the Advanced Encryption Standard (AES) algorithm in counter mode. It sure beats using the default System.Random module in terms of… coolness (for the purposes of this application, the use of a CPRNG over a regular PRNG really gives no benefit). Anyway, here is a sample run:

$ poke \!@#$%
poke: 'q'     quit
      'j'     number
      'k'     letter
      'l'     alphanumeric
      ';'     punctuation
      'h'     alphanumeric + !@#$%
      'i'     hexadecimal
      'ENTER' newline
      else    any

%g@c@geisBaqK81ihYkEC5NyUrWXU2ndCKr3wHkklpjvCWF9I0
zaJ,!z{db.|~vR7,MvOnPU-5v7N;cCy'],bl/d;^s[hI}RM?j>
KfdJKVygPSOufgllMAZlEaLWHSHpDrHIcgmryETcEsx5uUWlQb
49388c0958e9c51f2f4dc06a8097eb8169f715b4fcfb3ca555

I named it “poke” because I couldn’t think of any other short, UNIX-y name.

The program takes a string as input and treats it as a special class of characters to consider when generating a password with the ‘h’ key. This way, you can fit into the requirements of legacy website code that say something like, “You may use alphanumeric characters and also ‘!’ ‘@’ ‘#’ ‘$’ and ‘%’ symbols”.

The output above is from pressing ‘h’, then SPACE, then ‘l’ and finally ‘i’. You could easily extend it to take more fine-tuned options, such as a shorter password length instead of the default 50. (Hint: use this post.)

The interesting side effect of using 50-character long, randomly generated passwords is that I myself do not know these passwords! The only thing I remember is the single password used for my GnuPG private key, used to decrypt the master password file.

In case you are curious, my complete setup regarding passwords is as follows: I store all of my passwords in plaintext in a “master” file, then encrypt it with GnuPG. I use a git repo to track this encrypted file, so that I can sanely remove/delete old passwords without worrying about how to get it back if I need it. Once in a while, I use a simple shell command, gpg2 -d mypasswords.gpg | less, to view the passwords for entry into some website (hooray for copy and paste!). If I need to update/add/delete passwords, I just decrypt the master file, then edit it, and re-encrypt it and commit the change into git (btw, I decrypt it into a RAM partition to avoid leaving any traces of the plaintext file).

The GnuPG private key used to encrypt the master file is itself encrypted with CAST5 (again using GnuPG) and tracked in git. The CAST5 encryption (with the “-c” flag) is a way to encrypt a file with symmetric encryption — i.e., you supply the same password for encryption and decryption, and plus you don’t need a GnuPG key to do it! (You wouldn’t want to encrypt it using another GnuPG key, because then you’d need to encrypt the key for that GnuPG key as well — recursion!) I constantly sync the git repo holding these important, encrypted files across all of my personal machines, thumb drives, etc., for reliability and convenience.

I could learn to use KeyPass or some other software to manage my passwords, but, I’m too lazy. I’m also too paranoid to trust anyone other than myself to handle my passwords. I also take care not to store anything *too* valuable into the passwords file, or anything I type into any file anywhere, just to play it safe.

EDIT: Hey, this is my 100th post! Congratulations to me!