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

Copyright(c) Lennart Augustsson, 2008-2009
LicenseBSD3
MaintainerSigbjorn Finne <sof@galois.com>
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.JSON.Generic

Description

JSON serializer and deserializer using Data.Generics. The functions here handle algebraic data types and primitive types. It uses the same representation as Text.JSON for Prelude types.

Synopsis

Documentation

module Text.JSON

class Typeable * a => Data a

The Data class comprehends a fundamental primitive gfoldl for folding over constructor applications, say terms. This primitive can be instantiated in several ways to map over the immediate subterms of a term; see the gmap combinators later in this class. Indeed, a generic programmer does not necessarily need to use the ingenious gfoldl primitive but rather the intuitive gmap combinators. The gfoldl primitive is completed by means to query top-level constructors, to turn constructor representations into proper terms, and to list all possible datatype constructors. This completion allows us to serve generic programming scenarios like read, show, equality, term generation.

The combinators gmapT, gmapQ, gmapM, etc are all provided with default definitions in terms of gfoldl, leaving open the opportunity to provide datatype-specific definitions. (The inclusion of the gmap combinators as members of class Data allows the programmer or the compiler to derive specialised, and maybe more efficient code per datatype. Note: gfoldl is more higher-order than the gmap combinators. This is subject to ongoing benchmarking experiments. It might turn out that the gmap combinators will be moved out of the class Data.)

Conceptually, the definition of the gmap combinators in terms of the primitive gfoldl requires the identification of the gfoldl function arguments. Technically, we also need to identify the type constructor c for the construction of the result type from the folded term type.

In the definition of gmapQx combinators, we use phantom type constructors for the c in the type of gfoldl because the result type of a query does not involve the (polymorphic) type of the term argument. In the definition of gmapQl we simply use the plain constant type constructor because gfoldl is left-associative anyway and so it is readily suited to fold a left-associative binary operation over the immediate subterms. In the definition of gmapQr, extra effort is needed. We use a higher-order accumulation trick to mediate between left-associative constructor application vs. right-associative binary operation (e.g., (:)). When the query is meant to compute a value of type r, then the result type withing generic folding is r -> r. So the result of folding is a function to which we finally pass the right unit.

With the -XDeriveDataTypeable option, GHC can generate instances of the Data class automatically. For example, given the declaration

data T a b = C1 a b | C2 deriving (Typeable, Data)

GHC will generate an instance that is equivalent to

instance (Data a, Data b) => Data (T a b) where
    gfoldl k z (C1 a b) = z C1 `k` a `k` b
    gfoldl k z C2       = z C2

    gunfold k z c = case constrIndex c of
                        1 -> k (k (z C1))
                        2 -> z C2

    toConstr (C1 _ _) = con_C1
    toConstr C2       = con_C2

    dataTypeOf _ = ty_T

con_C1 = mkConstr ty_T "C1" [] Prefix
con_C2 = mkConstr ty_T "C2" [] Prefix
ty_T   = mkDataType "Module.T" [con_C1, con_C2]

This is suitable for datatypes that are exported transparently.

Minimal complete definition

gunfold, toConstr, dataTypeOf

Instances

Data Bool 
Data Char 
Data Double 
Data Float 
Data Int 
Data Int8 
Data Int16 
Data Int32 
Data Int64 
Data Integer 
Data Ordering 
Data Word 
Data Word8 
Data Word16 
Data Word32 
Data Word64 
Data () 
Data Handle 
Data SpecConstrAnnotation 
Data DataType 
Data Version 
Data ThreadId 
Data TypeRep 
Data TyCon 
Data ByteString 
Data ByteString 
Data IntSet 
Data Text 
Data Text

This instance preserves data abstraction at the cost of inefficiency. We omit reflection services for the sake of data abstraction.

This instance was created by copying the updated behavior of Data.Set.Set and Data.Map.Map. If you feel a mistake has been made, please feel free to submit improvements.

The original discussion is archived here: could we get a Data instance for Data.Text.Text?

The followup discussion that changed the behavior of Set and Map is archived here: Proposal: Allow gunfold for Data.Map, ...

Data a => Data [a] 
(Data a, Integral a) => Data (Ratio a) 
Typeable * a => Data (StablePtr a) 
Typeable * a => Data (IO a) 
(Data a, Typeable * a) => Data (Ptr a) 
(Data a, Typeable * a) => Data (ForeignPtr a) 
Typeable * a => Data (STM a) 
Typeable * a => Data (TVar a) 
Typeable * a => Data (MVar a) 
Typeable * a => Data (IORef a) 
Data a => Data (Maybe a) 
Data a => Data (IntMap a) 
(Data a, Ord a) => Data (Set a) 
(Data a, Data b) => Data (a -> b) 
(Data a, Data b) => Data (Either a b) 
(Data a, Data b) => Data (a, b) 
(Typeable * s, Typeable * a) => Data (ST s a) 
(Typeable * a, Data a, Data b, Ix a) => Data (Array a b) 
Data t => Data (Proxy * t) 
(Data k, Data a, Ord k) => Data (Map k a) 
(Data a, Data b, Data c) => Data (a, b, c) 
(Coercible * a b, Data a, Data b) => Data (Coercion * a b) 
((~) * a b, Data a) => Data ((:~:) * a b) 
(Data a, Data b, Data c, Data d) => Data (a, b, c, d) 
(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) 
(Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) 
(Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) 

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Instances

Typeable * Bool 
Typeable * Char 
Typeable * Double 
Typeable * Float 
Typeable * Int 
Typeable * Int8 
Typeable * Int16 
Typeable * Int32 
Typeable * Int64 
Typeable * Integer 
Typeable * Ordering 
Typeable * RealWorld 
Typeable * Word 
Typeable * Word8 
Typeable * Word16 
Typeable * Word32 
Typeable * Word64 
Typeable * () 
Typeable * Handle 
Typeable * Handle__ 
Typeable * SpecConstrAnnotation 
Typeable * DataType 
Typeable * Version 
Typeable * ThreadId 
Typeable * TypeRep 
Typeable * TyCon 
Typeable * ByteString 
Typeable * ByteString 
Typeable * IntSet 
Typeable * Text 
Typeable * Text 
Typeable * JSString 
Typeable * JSValue 
(Typeable (k1 -> k) s, Typeable k1 a) => Typeable k (s a)

Kind-polymorphic Typeable instance for type application

Typeable ((* -> *) -> Constraint) Alternative 
Typeable ((* -> *) -> Constraint) Applicative 
Typeable (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) 
Typeable (* -> * -> * -> * -> * -> * -> *) (,,,,,) 
Typeable (* -> * -> * -> * -> * -> *) (,,,,) 
Typeable (* -> * -> * -> * -> *) (,,,) 
Typeable (* -> * -> * -> *) (,,) 
Typeable (* -> * -> * -> *) STArray 
Typeable (* -> * -> *) (->) 
Typeable (* -> * -> *) Either 
Typeable (* -> * -> *) (,) 
Typeable (* -> * -> *) ST 
Typeable (* -> * -> *) Array 
Typeable (* -> * -> *) STRef 
Typeable (* -> * -> *) Map 
Typeable (* -> *) [] 
Typeable (* -> *) Ratio 
Typeable (* -> *) StablePtr 
Typeable (* -> *) IO 
Typeable (* -> *) Ptr 
Typeable (* -> *) FunPtr 
Typeable (* -> *) ForeignPtr 
Typeable (* -> *) STM 
Typeable (* -> *) TVar 
Typeable (* -> *) MVar 
Typeable (* -> *) IORef 
Typeable (* -> *) Maybe 
Typeable (* -> *) IntMap 
Typeable (* -> *) Set 
Typeable (* -> *) JSObject 
Typeable (* -> Constraint) Monoid 
Typeable (k -> *) (Proxy k) 
Typeable (k -> k -> *) (Coercion k) 
Typeable (k -> k -> *) ((:~:) k) 

toJSON :: Data a => a -> JSValue Source

Convert anything to a JSON value.

fromJSON :: Data a => JSValue -> Result a Source

Convert a JSON value to anything (fails if the types do not match).

encodeJSON :: Data a => a -> String Source

Encode a value as a string.

decodeJSON :: Data a => String -> a Source

Decode a string as a value.