Jdh-0.1.0.0: A Json implementation for Haskell, with JavaScript Values and Encoding/Decoding

LicenseMIT
Maintainerbrunoczim@gmail.com
Stabilityexperimental
PortabilityOS-Independent
Safe HaskellSafe
LanguageHaskell2010

Data.Jdh.Json.Generic

Description

This module contains the generic version for Json Values. Example: A JSInt can be an Int but also an Integer. This module also provides the functions for JSON encoding and decoding.

Synopsis

Documentation

data JSValue int real str Source

The data JSValue holds any possible JSON Value. Note that its types can be flexible, a JSInt may be of any Integral type, JSReal of any Fractional type, etc.

Instances

(Integral a, Fractional b, IsString c, Eq a, Eq b, Eq c) => Eq (JSValue a b c) Source

JSValue Implements the Eq class, the method == is implemented comparing the respectives JSValue types. Example: JSBooleans are compared only with JSBooleans, comparing other types will always return False

(Integral a, Fractional b, IsString c, Read a, Read b, Read c) => Read (JSValue a b c) Source

JSValue Implements the Read class, the method readsPrec is implemented with parse.

(Integral a, Fractional b, IsString c, Show a, Show b, Show c) => Show (JSValue a b c) Source

JSValue Implements the Show class, the method show is implemented with prettify.

type JSProperty int real str = (str, JSValue int real str) Source

The JSProperty type is a synonymous for a tuple containing a String-like value and a JSValue. It represents an object Property.

getInt :: JSValue int real str -> int Source

Returns the unboxed Integral value of JSValue

getReal :: JSValue int real str -> real Source

Returns the unboxed Fractional value of JSValue

getBool :: JSValue int real str -> Bool Source

Returns the unboxed Bool value of JSValue

getStr :: JSValue int real str -> str Source

Returns the unboxed IsString value of JSValue

getArray :: JSValue int real str -> [JSValue int real str] Source

Returns the unboxed [JSValue] value of JSValue

getObj :: JSValue int real str -> [(str, JSValue int real str)] Source

Returns the unboxed [(IsString, JSValue)] value of JSValue

isNull :: JSValue a b c -> Bool Source

This function checks if a JSValue is null (constructed with JSNull constructor).

isInt :: JSValue a b c -> Bool Source

This function checks if a JSValue is an integer (constructed with JSInt constructor).

isReal :: JSValue a b c -> Bool Source

This function checks if a JSValue is floating point number (constructed with JSReal constructor).

isBool :: JSValue a b c -> Bool Source

This function checks if a JSValue is boolean (constructed with JSBoolean constructor).

isStr :: JSValue a b c -> Bool Source

This function checks if a JSValue is string (constructed with JSString constructor).

isArray :: JSValue a b c -> Bool Source

This function checks if a JSValue is array (constructed with JSArray constructor).

isObj :: JSValue a b c -> Bool Source

This function checks if a JSValue is object (constructed with JSObject constructor).

fromNull :: (Integral a, Fractional b, IsString c) => JSValue a b c Source

Creates a null JSValue (no arguments).

fromInt :: (Integral a, Fractional b, IsString c) => a -> JSValue a b c Source

Creates a JSValue from an Integral value.

fromReal :: (Integral a, Fractional b, IsString c) => b -> JSValue a b c Source

Creates a JSValue from a Fractional value.

fromBool :: (Integral a, Fractional b, IsString c) => Bool -> JSValue a b c Source

Creates a JSValue from a Bool value.

fromStr :: (Integral a, Fractional b, IsString c) => c -> JSValue a b c Source

Creates a JSValue from a IsString value.

fromArray :: (Integral a, Fractional b, IsString c) => [JSValue a b c] -> JSValue a b c Source

Creates an Array JSValue from a list of JSValue.

fromProps :: (Integral a, Fractional b, IsString c) => [JSProperty a b c] -> JSValue a b c Source

Creates an Object JSValue from a list of properties relation (a (IsString,JSValue) tuple).

(=:) :: (Integral a, Fractional b, IsString c) => c -> JSValue a b c -> JSProperty a b c infixl 5 Source

An operator that creates a JSPropery value. Use it as property =: value.

stringify :: (Integral a, Fractional b, IsString c, Show a, Show b, Show c) => JSValue a b c -> String Source

Encodes a JSValue into a String. Condenses the String; no whitespace will be included.

prettify :: (Integral a, Fractional b, IsString c, Show a, Show b, Show c) => JSValue a b c -> String Source

Encodes a JSValue into a String. Prettifies the output with indentation and linefeeds.

parse :: (Integral a, Fractional b, IsString c, Read a, Read b, Read c) => String -> [(JSValue a b c, String)] Source

Parses an encoded JSON string into JSValues.

getProp :: (Integral a, Fractional b, IsString c, Eq c) => c -> JSValue a b c -> Maybe (JSValue a b c) Source

Returns a given property from a object. Note that this function returns type of Maybe (JSValue a b c); if the property is not found, returns Nothing