-- | -- Generator random test data for QuickCheck. -- -- Example: -- -- The generator JSON. -- -- The JSON specifcation is available at . -- -- > alpha_ = ['a'..'z'] ++ ['A'..'Z'] ++ ['_'] -- > digit = ['0'..'9'] -- > digit1_9 = ['1'..'9'] -- > hexdigit = digit ++ ['a'..'f'] -- > punctations = "!#%&'()*,-.:;?@[]_{}" -- > escControl = ["\\\"", "\\\\", "\\/", "\\\b", "\\\f", "\\\n", "\\\r", "\\\t"] -- > space = ' ' -- > control = "\b\f\n\r\t" -- > cyrillic = ['а'..'я'] ++ ['А'..'Я'] -- > alphaNum_ = digit ++ alpha_ -- > -- > jcomma = jspaces0 !++ return "," -- > jspace = return " " -- > jspaces0 = genRepeatElements 0 2 $ control ++ (replicate 20 space) -- > jspaces1 = jspace !++ jspaces0 -- > -- > jvalue = jspaces1 !++ jvalue' -- > jvalue' = oneof [jtrue, jfalse, jnull , jobject, jarray, jstring, jnumber] -- > -- value = string | number | object |array -- > -- | true |false | null -- > -- > jobject = gbi06 jlbrace jcomma jrbrace jpair -- > jpair = jstring !++ jcolon !++ jvalue -- > jcolon = jspaces0 !++ return ":" -- > jlbrace = return "{" -- > jrbrace = jspaces0 !++ return "}" -- > -- object = {} | { members } -- > -- members = pair | pair , members -- > -- pair = string : value -- > -- > jarray = gbi06 jlbracket jcomma jrbracket jvalue -- > jlbracket = return "[" -- > jrbracket = jspaces0 !++ return "]" -- > -- array = [] | [ elements ] -- > -- elements = value | value , elements -- > -- > jnumber = oneof [jint, jint !++ jfrac, jint !++ jexp, jint !++ jfrac !++ jexp] -- > jint = g01 jminus !++ (jdigit !| (jdigit1_9 !++ jdigits)) -- > jfrac = jdot !++ jdigits -- > jexp = je !++ jdigits -- > jdot = return "." -- > jminus = return "-" -- > jdigit = el digit -- > jdigits = genRepeatElements 1 3 digit -- > jdigit1_9 = el digit1_9 -- > je = elements ["e", "e+", "e-", "E", "E+", "E-"] -- > -- number = int | int frac | int exp | int frac exp -- > -- int = digit | digit1-9 digits | - digit | - digit1-9 digits -- > -- frac = . digits -- > -- exp = e digits -- > -- digits = digit | digit digits -- > -- e = e | e+ | e- | E | E+ |E- -- > -- > jstring = jquot !++ g06 jchar !++ jquot -- > jchar = elements escControl !| el cyrillic !| ju !| el punctations -- > !| el alphaNum_ !| jspace !| el alpha_ -- > ju = return "\\u" !++ genRepeatElements 4 4 digit -- > jquot = return "\"" -- > -- string = "" | "chars" -- > -- chars = char | char chars -- > -- char = any-Unicode-character-except- " -or- \ -or- -- > -- control-character \" \\ \/ \b \f \n \r \t -- > -- | \u four-hex-digits number -- > -- > jtrue = return "true" -- > jfalse = return "false" -- > jnull = return "null" -- > module Testing.QuickGenerator ( -- * Base genRepeat ,genRepeatElements ,genRepeatIntercalate -- * Combinators ,(!++) ,(!|) -- * Helpers ,g06 ,g16 ,g01 ,gbi06 ,gbi16 ,el ) where import Test.QuickCheck import Control.Monad (replicateM, liftM2) -- Base -------------------------------------------------------------- -- | Repeat g from min to max times. genRepeat :: Int -> Int -> Gen [a] -> Gen [a] genRepeat min max g = do n <- choose (min, max) concat `fmap` replicateM n g -- | Repeat of xs from min to max times. genRepeatElements :: Int -> Int -> [a] -> Gen [a] genRepeatElements min max xs = do n <- choose (min, max) replicateM n (elements xs) -- | Repeat g with inset i from min to max times. genRepeatIntercalate :: Int -> Int -> Gen [a] -> Gen [a] -> Gen [a] genRepeatIntercalate min max i g = do n <- choose (min, max) case n of 0 -> return [] 1 -> g _ -> (concat `fmap` replicateM (n - 1) (g !++ i)) !++ g -- Combinators ------------------------------------------------------- -- | Or (!|) :: Gen a -> Gen a -> Gen a x !| y = do v <- choose (False, True) :: Gen Bool if v then x else y -- | Concat (!++) :: Gen [a] -> Gen [a] -> Gen [a] (!++) = liftM2 (++) -- Helpers ---------------------------------------------------------- -- | -- > g06 = genRepeat 0 6 g06 :: Gen [a] -> Gen [a] g06 = genRepeat 0 6 -- | -- > g16 = genRepeat 1 6 g16 :: Gen [a] -> Gen [a] g16 = genRepeat 1 6 -- | -- > g01 = genRepeat 0 1 g01 :: Gen [a] -> Gen [a] g01 = genRepeat 0 1 -- | Repeat g with inset i from 1 to 6 times -- | and insert result between l and r. gbi06 :: Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] gbi06 l i r g = l !++ (genRepeatIntercalate 0 6 i g) !++ r -- | Repeat g with inset i from 1 to 6 times -- | and insert result between l and r. gbi16 :: Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] gbi16 l i r g = l !++ (genRepeatIntercalate 1 6 i g) !++ r -- | Castom QuickChceck.elements el :: [a] -> Gen [a] el xs = (\x -> [x]) `fmap` elements xs