RJson-0.3.6: A reflective JSON serializer/parser.

Text.RJson

Synopsis

Documentation

class TranslateField a whereSource

Methods

translateField :: a -> String -> StringSource

This method defines the mapping from Haskell record field names to JSON object field names. The default is to strip any initial underscores. Specialize this method to define a different behavior.

Instances

Typeable a => TranslateField a

Removes initial underscores from a string.

class TranslateField a => ToJson a whereSource

New instances can be added to this class to customize certain aspects of the way in which Haskell types are serialized to JSON.

Methods

toJson :: a -> JsonDataSource

exclude :: a -> String -> BoolSource

Applies to record types only. You can specialize this method to prevent certain fields from being serialized. Given a Haskell field name, it should return True if that field is to be serialized, and False otherwise.

arrayPrepend :: a -> [JsonData]Source

Types that will be converted to JSON arrays can override this method to specify additional elements to be prepended to the array.

arrayAppend :: a -> [JsonData]Source

Types that will be converted to JSON arrays can override this method to specify additional elements to be appended to the array.

objectExtras :: a -> [(String, JsonData)]Source

Types that will be converted to JSON objects can override this method to specify additional fields of the object.

Instances

ToJson Bool 
ToJson Char 
ToJson Double 
ToJson Int 
ToJson Integer 
(Data ToJsonD t, TranslateField t) => ToJson t 
(ToJson a, TranslateField a, Typeable a) => ToJson [a] 
(Integral a, TranslateField a, Typeable a) => ToJson (Ratio a) 
(Typeable a, ToJson a) => ToJson (Maybe a) 
(ToJson a, Typeable a, ToJson b, Typeable b) => ToJson (a, b) 
(ToJson a, TranslateField a, Typeable a, Typeable i, Ix i) => ToJson (Array i a) 
(ToJson a, TranslateField a, Data TranslateFieldD (Map String a)) => ToJson (Map String a) 
(ToJson a, ToJson b, TranslateField a, TranslateField b, Typeable a, Typeable b, Typeable2 Union) => ToJson (Union a b) 
(ToJson a, Typeable a, ToJson b, Typeable b, ToJson c, Typeable c) => ToJson (a, b, c) 
(ToJson a, Typeable a, ToJson b, Typeable b, ToJson c, Typeable c, ToJson d, Typeable d) => ToJson (a, b, c, d) 
(ToJson a, Typeable a, ToJson b, Typeable b, ToJson c, Typeable c, ToJson d, Typeable d, ToJson e, Typeable e) => ToJson (a, b, c, d, e) 
(ToJson a, Typeable a, ToJson b, Typeable b, ToJson c, Typeable c, ToJson d, Typeable d, ToJson e, Typeable e, ToJson f, Typeable f) => ToJson (a, b, c, d, e, f) 
(ToJson a, Typeable a, ToJson b, Typeable b, ToJson c, Typeable c, ToJson d, Typeable d, ToJson e, Typeable e, ToJson f, Typeable f, ToJson g, Typeable g) => ToJson (a, b, c, d, e, f, g) 

data ToJsonD a Source

Instances

ToJson t => Sat (ToJsonD t) 

genericToJson :: (Data ToJsonD a, ToJson a, TranslateField a) => a -> JsonDataSource

This function is used as the the implementation of toJson for the generic instance declaration. It's useful to be able to use the same implentation for other instance declarations which override the default implementations of other methods of the ToJson class.

enumToJson :: (Data ToJsonD a, ToJson a, TranslateField a) => (String -> String) -> a -> JsonDataSource

This function can be used as an implementation of toJson for simple enums. It converts an enum value to a string determined by the name of the constructor, after being fed through the (String -> String) function given as the first argument.

data JsonData Source

A Haskell representation of a JSON data structure.

Instances

class TranslateField a => FromJson a whereSource

Methods

fromJson :: a -> JsonData -> Either String aSource

objectDefaults :: a -> Map String JsonDataSource

To specify default values for the required fields of a JSON object, specialize this method in the instance definition for the relevant datatype.

Instances

FromJson Bool 
FromJson Char 
FromJson Double 
FromJson Int 
FromJson Integer 
(Data FromJsonD t, TranslateField t) => FromJson t 
(FromJson a, TranslateField a, Typeable a) => FromJson [a] 
(Typeable a, Integral a) => FromJson (Ratio a) 
(FromJson a, TranslateField a, Typeable a) => FromJson (Maybe a) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b) => FromJson (a, b) 
(FromJson a, FromJson b, Typeable a, Typeable b, TranslateField a, TranslateField b) => FromJson (Union a b) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b, FromJson c, Typeable c, TranslateField c) => FromJson (a, b, c) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b, FromJson c, Typeable c, TranslateField c, FromJson d, Typeable d, TranslateField d) => FromJson (a, b, c, d) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b, FromJson c, Typeable c, TranslateField c, FromJson d, Typeable d, TranslateField d, FromJson e, Typeable e, TranslateField e) => FromJson (a, b, c, d, e) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b, FromJson c, Typeable c, TranslateField c, FromJson d, Typeable d, TranslateField d, FromJson e, Typeable e, TranslateField e, FromJson f, Typeable f, TranslateField f) => FromJson (a, b, c, d, e, f) 
(FromJson a, Typeable a, TranslateField a, FromJson b, Typeable b, TranslateField b, FromJson c, Typeable c, TranslateField c, FromJson d, Typeable d, TranslateField d, FromJson e, Typeable e, TranslateField e, FromJson f, Typeable f, TranslateField f, FromJson g, Typeable g, TranslateField g) => FromJson (a, b, c, d, e, f, g) 

data FromJsonD a Source

Instances

parseJsonString :: String -> Either String JsonDataSource

Converts a String (interpreted as a true unicode String) to an instance of JsonData.

parseJsonByteString :: ByteString -> Either String JsonDataSource

Converts a ByteString to an instance of JsonData (unicode encoding is detected automatically).

fromJsonString :: FromJson a => a -> String -> Either String aSource

Converts a JSON String (interpreted as a true unicode string) to a value of the type given by the first (dummy) argument.

fromJsonByteString :: FromJson a => a -> ByteString -> Either String aSource

Converts a JSON ByteString (with unicode encoding automatically detected) to a value of the type given by the first (dummy) argument.

toJsonString :: ToJson a => a -> StringSource

Converts a value to an ASCII-only JSON String.

firstCharToUpper :: String -> StringSource

Converts the first character of a string to upper case.

firstCharToLower :: String -> StringSource

Converts the first character of a string to lower case.

data Union a b Source

This type can be used for merging two or more records together into a single JSON object. By default, a structure such as (Union X Y) is serialized as follows. First, X and Y are serialized, and a runtime error is signalled if the result of serialization is not a JSON object in both cases. The key/value pairs of the two JSON objects are then merged to form a single object.

Constructors

Union a b 

Instances

Typeable2 Union 
(Data ctx a[a28u], Data ctx b[a28v], Sat (ctx (Union a[a28u] b[a28v]))) => Data ctx (Union a[a28u] b[a28v]) 
(Show a, Show b) => Show (Union a b) 
(ToJson a, ToJson b, TranslateField a, TranslateField b, Typeable a, Typeable b, Typeable2 Union) => ToJson (Union a b) 
(FromJson a, FromJson b, Typeable a, Typeable b, TranslateField a, TranslateField b) => FromJson (Union a b) 

type Union3 a b c = Union (Union a b) cSource

Nested Unions are left-branching by convention (since this is what you get by using the constructor as an infix operator).

type Union4 a b c d = Union (Union3 a b c) dSource

type Union5 a b c d e = Union (Union4 a b c d) eSource

type Union6 a b c d e f = Union (Union5 a b c d e) fSource

type Union7 a b c d e f g = Union (Union6 a b c d e f) gSource

type Union8 a b c d e f g h = Union (Union7 a b c d e f g) hSource

type Union9 a b c d e f g h i = Union (Union8 a b c d e f g h) iSource

type Union10 a b c d e f g h i j = Union (Union9 a b c d e f g h i) jSource