quickCheck 入門

Haskell の quickCheck の簡単な例を作った。

データ型 Obj は、Nil 、数、シンボル、コンスセルの何れかであり、コンスセルはデータ型 Obj 二つからなる。

module ConsCell where
import Test.QuickCheck
import Control.Monad

data Obj = Nil | N Int | Sym String | Cons Obj Obj deriving (Eq)

instance Show Obj where
    show Nil = "()"
    show (N x) = show x
    show (Cons x y) = showCons (Cons x y)
    show (Sym n) = n

consp Nil = False
consp (N _) = False
consp (Cons _ _) = True
consp (Sym _) = False

atom Nil = True
atom (N _) = True
atom (Cons _ _) = False
atom (Sym _) = True

car (Cons x _) = x
car x | not (consp x) = error "x is not cons"

cdr (Cons _ y) = y
cdr x | not (consp x) = error "x is not cons"

-- HyperSpec "22.1.3.5 Printing Lists And Conses"
showCons x = step1 x ""
    where
      step1 x res = step2 x (res ++ "(")
      step2 x res = step3 x (res ++ show (car x))
      step3 x res = if consp (cdr x)
                    then
                        step2 (cdr x) (res ++ " ")
                    else
                        step4 x res
      step4 x res = if cdr x /= Nil
                    then
                        step5 x (res ++ " . " ++ show (cdr x))
                    else
                        step5 x res
      step5 x res = res ++ ")"

show メソッドの定義は HyperSpec に習ったもので、実例は以下の通り。

*ConsCell> N 12
12
*ConsCell> Sym "defun"
defun
*ConsCell> Sym "x"
x
*ConsCell> Nil
()
*ConsCell> Cons (Sym "x") Nil
(x)
*ConsCell> Cons (N 4) (N 3)
(4 . 3)
*ConsCell> Cons (Cons (N 4) (N 3)) Nil
((4 . 3))
*ConsCell> Cons (Sym "x") (Cons (Sym "y") Nil)
(x y)

以下の genobj 関数は Gen Obj 型で、Nil か数かシンボルかコンスセルを再帰的に生成する。

genobj = oneof [ return Nil,
                 liftM N arbitrary,
                 liftM2 Cons genobj genobj,
                 liftM Sym (listOf1 (elements ['a'..'z'])) ]

instance Arbitrary Obj where
    arbitrary = genobj

これを用いると、以下のようにランダムな Obj 型のデータが生成できる。

*ConsCell> sample' arbitrary :: IO [Obj]
[((() () () ()) . f),(),(),novema,(),cwrc,(() . 93),((() . -109)),(()),vobzvhffdhopc,-4096]
*ConsCell> sample' arbitrary :: IO [Obj]
[0,(),(),8,(druo),(-51 () . -36),(),(),-745,((() xqdbgkzk kg) vwebwkcovgwacxytx),vkdchrt]
*ConsCell> sample' arbitrary :: IO [Obj]
[(()),-2,(),(),vqos,(),(s),-112,coabv,((133) . 206),(-3747 . -1992)]
*ConsCell> sample' arbitrary :: IO [Obj]
[i,(),bw,xkvs,bxyep,27,(),-102,-327,rhvhyyoe,()]
*ConsCell> sample' arbitrary :: IO [Obj]
[o,0,h,(),(nh),-38,(),zyhhalfnes,uhpulthbmiqikag,tyveydbrccsxsnp,toxypfsrxomyhqqnjged]
*ConsCell> 

英文

PAIP (Paradigms of Artifical Intelligence Programming) 2章の英文生成。

module English where
import Test.QuickCheck
import Control.Monad

verb = elements ["hit", "took", "saw", "liked"]
noun = elements ["man", "ball", "woman", "table"]
article = elements ["the", "a"]

名詞、動詞、冠詞を生成する関数を、それぞれ Gen [Char] 型 の noun, verb, article とし、 QuickCheck の elements 関数で定義する。elements 関数はリストを引数とする。名詞を QuickCheck の sample 関数で生成させると以下のようになる。

*English> sample noun
"ball"
"table"
"man"
"man"
"woman"
"table"
"woman"
"man"
"table"
"table"
"ball"

次に冠詞と名詞から名詞句を生成する関数 nounPhrase を考える。型は noun や article と同じく、Gen [Char] 型となる。Gen a はモナドなので、nounPhase の中で値を使うためには do 記法が必要になる。

nounPhrase = do
  a <- article
  n <- noun
  return (a ++ " " ++ n)

あるいは、より簡潔に liftM2 を用いても定義できる。

nounPhrase = liftM2 (\a n -> a ++ " " ++ n) article noun

文字列をスペースで結合するには unwords が用意されているので、これを用いる。同様に動詞句を定義し、名詞句と動詞句から文を定義すると、最終的に以下のようになる。

module English where
import Test.QuickCheck
import Control.Monad

verb = elements ["hit", "took", "saw", "liked"] :: Gen String
noun = elements ["man", "ball", "woman", "table"] :: Gen String
article = elements ["the", "a"] :: Gen String

nounPhrase :: Gen String
-- nounPhrase = liftM2 (\a n -> unwords [a, n]) article noun
nounPhrase = do
  a <- article
  n <- noun
  return $ unwords [a, n]

verbPhrase :: Gen String
verbPhrase = do
  v <- verb
  np <- nounPhrase
  return $ unwords [v, np]

sentence :: Gen String
sentence = do
  np <- nounPhrase
  vp <- verbPhrase
  return $ unwords [np, vp]

これでセンテンスを生成させると以下のようになる。

*English> sample sentence
"a man saw a woman"
"a table liked a table"
"a woman saw the woman"
"the table liked a man"
"a ball saw the table"
"a table saw the woman"
"the ball liked the table"
"a man liked the ball"
"a table liked the woman"
"a woman saw the ball"
"the table liked a table"