module Main where import Test.QuickCheck import Control.Monad import Testing.QuickGenerator -------------------------------------------------------------------------------- viewGen p = verboseCheck $ forAll p (\x -> x == x) -------------------------------------------------------------------------------- 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_ --quot = "\"" 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"