json-0.9.2: Support for serialising Haskell to and from JSON

Copyright(c) Galois Inc. 2007-2009
LicenseBSD3
MaintainerSigbjorn Finne <sof@galois.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Text.JSON

Contents

Description

 

Synopsis

JSON Types

data JSValue Source #

JSON values

The type to which we encode Haskell values. There's a set of primitives, and a couple of heterogenous collection types.

Objects:

An object structure is represented as a pair of curly brackets surrounding zero or more name/value pairs (or members). A name is a string. A single colon comes after each name, separating the name from the value. A single comma separates a value from a following name.

Arrays:

An array structure is represented as square brackets surrounding zero or more values (or elements). Elements are separated by commas.

Only valid JSON can be constructed this way

Instances

Serialization to and from JSValues

class JSON a where Source #

The class of types serialisable to and from JSON

Minimal complete definition

readJSON, showJSON

Instances

JSON Bool Source # 
JSON Char Source # 
JSON Double Source # 
JSON Float Source # 
JSON Int Source # 
JSON Int8 Source # 
JSON Int16 Source # 
JSON Int32 Source # 
JSON Int64 Source # 
JSON Integer Source # 
JSON Ordering Source # 
JSON Word Source # 
JSON Word8 Source # 
JSON Word16 Source # 
JSON Word32 Source # 
JSON Word64 Source # 
JSON () Source # 
JSON ByteString Source # 
JSON ByteString Source # 
JSON IntSet Source # 
JSON Text Source # 
JSON JSString Source # 
JSON JSValue Source #

To ensure we generate valid JSON, we map Haskell types to JSValue internally, then pretty print that.

JSON a => JSON [a] Source # 
JSON a => JSON (Maybe a) Source # 
JSON a => JSON (IntMap a) Source # 
(Ord a, JSON a) => JSON (Set a) Source # 
JSON a => JSON (JSObject a) Source # 
(JSON a, JSON b) => JSON (Either a b) Source # 
(JSON a, JSON b) => JSON (a, b) Source # 

Methods

readJSON :: JSValue -> Result (a, b) Source #

showJSON :: (a, b) -> JSValue Source #

readJSONs :: JSValue -> Result [(a, b)] Source #

showJSONs :: [(a, b)] -> JSValue Source #

(Ix i, JSON i, JSON e) => JSON (Array i e) Source # 
(Ord a, JSON a, JSON b) => JSON (Map a b) Source # 
(JSON a, JSON b, JSON c) => JSON (a, b, c) Source # 

Methods

readJSON :: JSValue -> Result (a, b, c) Source #

showJSON :: (a, b, c) -> JSValue Source #

readJSONs :: JSValue -> Result [(a, b, c)] Source #

showJSONs :: [(a, b, c)] -> JSValue Source #

(JSON a, JSON b, JSON c, JSON d) => JSON (a, b, c, d) Source # 

Methods

readJSON :: JSValue -> Result (a, b, c, d) Source #

showJSON :: (a, b, c, d) -> JSValue Source #

readJSONs :: JSValue -> Result [(a, b, c, d)] Source #

showJSONs :: [(a, b, c, d)] -> JSValue Source #

Encoding and Decoding

data Result a Source #

A type for parser results

Constructors

Ok a 
Error String 

Instances

Monad Result Source # 

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Alternative Result Source # 

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

MonadPlus Result Source # 

Methods

mzero :: Result a #

mplus :: Result a -> Result a -> Result a #

Eq a => Eq (Result a) Source # 

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

encode :: JSON a => a -> String Source #

Encode a Haskell value into a string, in JSON format.

This is a superset of JSON, as types other than Array and Object are allowed at the top level.

decode :: JSON a => String -> Result a Source #

Decode a String representing a JSON value (either an object, array, bool, number, null)

This is a superset of JSON, as types other than Array and Object are allowed at the top level.

encodeStrict :: JSON a => a -> String Source #

Encode a value as a String in strict JSON format. This follows the spec, and requires all values at the top level to be wrapped in either an Array or Object. JSON types to be an Array or Object.

decodeStrict :: JSON a => String -> Result a Source #

Decode a String representing a strict JSON value. This follows the spec, and requires top level JSON types to be an Array or Object.

Wrapper Types

toJSString :: String -> JSString Source #

Turn a Haskell string into a JSON string.

data JSObject e Source #

As can association lists

toJSObject :: [(String, a)] -> JSObject a Source #

Make JSON object out of an association list.

resultToEither :: Result a -> Either String a Source #

Map Results to Eithers

Serialization to and from Strings.

Reading JSON

readJSNull :: GetJSON JSValue Source #

Read the JSON null type

readJSBool :: GetJSON JSValue Source #

Read the JSON Bool type

readJSString :: GetJSON JSValue Source #

Read the JSON String type

readJSRational :: GetJSON Rational Source #

Read an Integer or Double in JSON format, returning a Rational

readJSArray :: GetJSON JSValue Source #

Read a list in JSON format

readJSObject :: GetJSON JSValue Source #

Read an object in JSON format

readJSValue :: GetJSON JSValue Source #

Read one of several possible JS types

Writing JSON

showJSNull :: ShowS Source #

Write the JSON null type

showJSBool :: Bool -> ShowS Source #

Write the JSON Bool type

showJSArray :: [JSValue] -> ShowS Source #

Show a list in JSON format

showJSRational :: Rational -> ShowS Source #

Show a Rational in JSON format

showJSObject :: JSObject JSValue -> ShowS Source #

Show an association list in JSON format

showJSValue :: JSValue -> ShowS Source #

Show JSON values

Instance helpers

valFromObj :: JSON a => String -> JSObject JSValue -> Result a Source #

Pull a value out of a JSON object.

class JSKey a where Source #

Haskell types that can be used as keys in JSON objects.

Minimal complete definition

toJSKey, fromJSKey

encJSDict :: (JSKey a, JSON b) => [(a, b)] -> JSValue Source #

Encode an association list as JSObject value.

decJSDict :: (JSKey a, JSON b) => String -> JSValue -> Result [(a, b)] Source #

Decode a JSObject value into an association list.