module Main where import Test.QuickCheck import Testing.QuickGenerator 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 = "\f\n\r\t" cyrillic = ['а'..'я'] ++ ['А'..'Я'] alphaNum_ = digit ++ alpha_ jspace = return " " jspaces0 = (control ++ replicate 20 space) ??* (0,2) jspaces1 = jspace .++ jspaces0 jcomma = jspaces0 .++ return "," jvalue = jspaces1 .++ jvalue' jvalue' = oneof [jtrue, jfalse, jnull , jobject, jarray, jstring, jnumber] {- value := string | number | object |array | true |false | null -} jobject = jlbrace .++ jpair ?* (0,6) .++ jrbrace jpair = jstring .++ jcolon .++ jvalue jcolon = jspaces0 .++ return ":" jlbrace = return "{" jrbrace = jspaces0 .++ return "}" {- object := {} | { members } members := pair | pair , members pair := string : value -} jarray = return "[" .++ jarray' .++ jspaces0 .++ return "]" jarray' = repeatWithInter jvalue jcomma (0,6) {- array := [] | [ elements ] elements := value | value , elements -} jnumber = oneof [jint, jint .++ jfrac, jint .++ jexp, jint .++ jfrac .++ jexp] jint = "-" ??* (0,1) .++ (jdigit .| (jdigit1_9 .++ jdigits)) jfrac = jdot .++ jdigits jexp = je .++ jdigits jdot = return "." jdigit = el digit jdigits = digit ??* (1,3) 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 .++ jchar ?* (0,6) .++ jquot jchar = elements escControl .| el cyrillic .| ju .| el punctations .| el alphaNum_ .| jspace .| el alpha_ ju = return "0u" .++ digit ??* (4,4 ) 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" main = sample jvalue