quick-generator-0.1.2: Generator random test data for QuickCheck

Testing.QuickGenerator

Contents

Description

Generator random test data for QuickCheck.

Example:

The generator JSON.

The JSON specifcation is available at http://www.json.org/ .

 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 = gi06 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    = gi06 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"
 

Synopsis

Base

genRepeat :: Int -> Int -> Gen [a] -> Gen [a]Source

genRepeat min max g repeat g from min to max times.

genRepeatElements :: Int -> Int -> [a] -> Gen [a]Source

genRepeatElements min max xs repeat of xs from min to max times.

genRepeatIntercalate :: Int -> Int -> Gen [a] -> Gen [a] -> Gen [a]Source

genRepeatIntercalate min max i g repeat g with inset i from min to max times.

Combinators

(!++) :: Gen [a] -> Gen [a] -> Gen [a]Source

Concat

(!|) :: Gen a -> Gen a -> Gen aSource

Or

Helpers

g06 :: Gen [a] -> Gen [a]Source

 g06 = genRepeat 0 6

g16 :: Gen [a] -> Gen [a]Source

 g16 = genRepeat 1 6

g01 :: Gen [a] -> Gen [a]Source

 g01 = genRepeat 0 1

gi06 :: Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] -> Gen [a]Source

gi06 l i r g repeat g with inset i from 0 to 6 times and insert result between l and r.

gi16 :: Gen [a] -> Gen [a] -> Gen [a] -> Gen [a] -> Gen [a]Source

gi16 l i r g repeat g with inset i from 1 to 6 times and insert result between l and r.

el :: [a] -> Gen [a]Source

Castom elements