[Start chapter 6 text Bryan O'Sullivan **20080220011535] { move ./examples/ch06/JSONOutput.hs ./examples/ch06/SimpleJSON.hs addfile ./examples/ch06/simplejson.ghci hunk ./en/ch06-library.xml 6 - FIXME + In this chapter, we'll take a look at developing a small, but + complete, Haskell library. + + + A whirlwind tour of the JSON language + + The JSON (JavaScript Object Notation) language is a small, + simple representation for structured data. Its most common use + is to transfer data from a web service to a browser-based + JavaScript application. + + JSON supports four basic types of value: strings, numbers, + booleans, and a special value named null. + + "a string" +12345 +true +null + + The language also allows for the construction of compound + values. Its compound types are the array, an ordered sequence + of values; and the struct, an unordered collection of name/value + pairs. The values in a struct or array can be of any + type. + + [-3.14, true, null, "a string"] +{"numbers": [1,2,3,4,5], "useful": false} + + + + Representing JSON data in Haskell + + To work with JSON data in Haskell, we use an algebraic data + type to represent the range of possible JSON types. In a text + editor, create a file named SimpleJSON.hs, and + insert the following contents. + + &SimpleJSON.hs:JValue; + + Here, we associate each JSON type with a distinct + constructor. Some of these constructors have parameters: if we + want to construct a JSON string, we must provide a + String value as an argument to the + JString constructor. + + To start experimenting with this code, save the file + SimpleJSON.hs in your editor, switch to a &ghci; + window, and load the file into &ghci;. + + &simplejson.ghci:load; + + We can see how to use a constructor to take a normal Haskell + value and turn it into a JSON value. To do the reverse, we use + pattern matching. Here's a function that we can add to + SimpleJSON.hs that will extract a string from a + JSON value for us. If the JSON value actually contains a + string, our function will wrap the string with the + Just constructor, otherwise it will return + Nothing. + + &SimpleJSON.hs:getString; + + If we save the source file again, we can reload it in + &ghci; and try the new definition. + + &simplejson.ghci:reload; + + hunk ./examples/ch06/Prettify.hs 24 -import Data.Monoid -import Debug.Trace +import Data.Monoid (Monoid(..)) hunk ./examples/ch06/SimpleJSON.hs 1 -module JSONOutput +module SimpleJSON hunk ./examples/ch06/SimpleJSON.hs 3 - jvalue + JValue(..) + , jvalue hunk ./examples/ch06/SimpleJSON.hs 7 -import qualified Data.Map as M hunk ./examples/ch06/SimpleJSON.hs 8 +-- import Text.PrettyPrint.HughesPJ (Doc, (<>), (<+>), char, double, fsep, hcat, punctuate, text) hunk ./examples/ch06/SimpleJSON.hs 10 -import JSON (JValue(..), fromJArray, fromJObject) -import qualified Data.ByteString.Lazy.Char8 as C hunk ./examples/ch06/SimpleJSON.hs 11 -import Data.ByteString.Internal (c2w) -import qualified JSONBuilder as B hunk ./examples/ch06/SimpleJSON.hs 12 -import JSON -import Prettify +{-- snippet JValue --} +data JValue = JString String + | JNumber Double + | JBool Bool + | JNull + | JObject [(String, JValue)] + | JArray [JValue] + deriving (Eq, Ord, Show) +{-- /snippet JValue --} hunk ./examples/ch06/SimpleJSON.hs 24 -jvalue (JNumber n) = double (fromRational n) -jvalue (JObject o) = series (encloseC '{' '}') field (fromJObject o) -jvalue (JArray a) = series (encloseC '(' ')') jvalue (fromJArray a) +jvalue (JNumber n) = double n +jvalue (JObject o) = series (encloseC '{' '}') field o +jvalue (JArray a) = series (encloseC '(' ')') jvalue a hunk ./examples/ch06/SimpleJSON.hs 31 +{-- snippet getString --} +getString :: JValue -> Maybe String +getString (JString s) = Just s +getString _ = Nothing +{-- /snippet getString --} + hunk ./examples/ch06/SimpleJSON.hs 49 - where one c = case M.lookup c specials of + where one c = case lookup c specials of hunk ./examples/ch06/SimpleJSON.hs 53 - specials = M.fromList [ - ('\b', "\\b"), ('\n', "\\n"), ('\f', "\\f"), ('\r', "\\r"), - ('\t', "\\t"), ('\\', "\\\\"), ('\"', "\\\""), ('/', "\\/")] + specials = zipWith ch "\b\n\f\r\t\\\"/" "bnrt\\\"/" + ch a b = (a, '\\':[b]) hunk ./examples/ch06/SimpleJSON.hs 62 +-- Not present in Text.PrettyPrint.HughesPJ. + +--enclose :: Doc -> Doc -> Doc -> Doc +--enclose left right x = left <> x <> right + +--encloseC :: Char -> Char -> Doc -> Doc +--encloseC left right x = char left <> x <> char right + hunk ./examples/ch06/simplejson.ghci 1 +--# load +:load SimpleJSON +JString "foo" +JNumber 2.7 +:type JBool True + +--# reload +:reload SimpleJSON +getString (JString "hello") +getString (JNumber 3) }