json5hs-0.1.2.2: Serialising to and from JSON5

Safe HaskellSafe
LanguageHaskell98

Text.JSON5

Contents

Description

Serialising Haskell values to and from JSON5 values.

Synopsis

JSON5 Types

data JSValue Source #

Instances
Eq JSValue Source # 
Instance details

Defined in Text.JSON5.Types

Methods

(==) :: JSValue -> JSValue -> Bool #

(/=) :: JSValue -> JSValue -> Bool #

Ord JSValue Source # 
Instance details

Defined in Text.JSON5.Types

Read JSValue Source # 
Instance details

Defined in Text.JSON5.Types

Show JSValue Source # 
Instance details

Defined in Text.JSON5.Types

IsString JSValue Source # 
Instance details

Defined in Text.JSON5.Types

Methods

fromString :: String -> JSValue #

JSON5 JSValue Source #

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

Instance details

Defined in Text.JSON5

Serialization to and from JSValues

class JSON5 a where Source #

The class of types serialisable to and from JSON5

Minimal complete definition

readJSON, showJSON

Instances
JSON5 Bool Source # 
Instance details

Defined in Text.JSON5

JSON5 Char Source # 
Instance details

Defined in Text.JSON5

JSON5 Double Source # 
Instance details

Defined in Text.JSON5

JSON5 Float Source # 
Instance details

Defined in Text.JSON5

JSON5 Int Source # 
Instance details

Defined in Text.JSON5

JSON5 Int8 Source # 
Instance details

Defined in Text.JSON5

JSON5 Int16 Source # 
Instance details

Defined in Text.JSON5

JSON5 Int32 Source # 
Instance details

Defined in Text.JSON5

JSON5 Int64 Source # 
Instance details

Defined in Text.JSON5

JSON5 Integer Source # 
Instance details

Defined in Text.JSON5

JSON5 Ordering Source # 
Instance details

Defined in Text.JSON5

JSON5 Word Source # 
Instance details

Defined in Text.JSON5

JSON5 Word8 Source # 
Instance details

Defined in Text.JSON5

JSON5 Word16 Source # 
Instance details

Defined in Text.JSON5

JSON5 Word32 Source # 
Instance details

Defined in Text.JSON5

JSON5 Word64 Source # 
Instance details

Defined in Text.JSON5

JSON5 () Source # 
Instance details

Defined in Text.JSON5

JSON5 ByteString Source # 
Instance details

Defined in Text.JSON5

JSON5 ByteString Source # 
Instance details

Defined in Text.JSON5

JSON5 IntSet Source # 
Instance details

Defined in Text.JSON5

JSON5 Text Source # 
Instance details

Defined in Text.JSON5

JSON5 JSString Source # 
Instance details

Defined in Text.JSON5

JSON5 JSValue Source #

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

Instance details

Defined in Text.JSON5

JSON5 a => JSON5 [a] Source # 
Instance details

Defined in Text.JSON5

JSON5 a => JSON5 (Maybe a) Source # 
Instance details

Defined in Text.JSON5

JSON5 a => JSON5 (IntMap a) Source # 
Instance details

Defined in Text.JSON5

(Ord a, JSON5 a) => JSON5 (Set a) Source # 
Instance details

Defined in Text.JSON5

JSON5 a => JSON5 (JSObject a) Source # 
Instance details

Defined in Text.JSON5

(JSON5 a, JSON5 b) => JSON5 (Either a b) Source # 
Instance details

Defined in Text.JSON5

(JSON5 a, JSON5 b) => JSON5 (a, b) Source # 
Instance details

Defined in Text.JSON5

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, JSON5 i, JSON5 e) => JSON5 (Array i e) Source # 
Instance details

Defined in Text.JSON5

(Ord a, JSON5 a, JSON5 b) => JSON5 (Map a b) Source # 
Instance details

Defined in Text.JSON5

(JSON5 a, JSON5 b, JSON5 c) => JSON5 (a, b, c) Source # 
Instance details

Defined in Text.JSON5

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 #

(JSON5 a, JSON5 b, JSON5 c, JSON5 d) => JSON5 (a, b, c, d) Source # 
Instance details

Defined in Text.JSON5

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 # 
Instance details

Defined in Text.JSON5

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 # 
Instance details

Defined in Text.JSON5

Methods

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

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

Applicative Result Source # 
Instance details

Defined in Text.JSON5

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 # 
Instance details

Defined in Text.JSON5

Methods

empty :: Result a #

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

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

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

MonadPlus Result Source # 
Instance details

Defined in Text.JSON5

Methods

mzero :: Result a #

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

Eq a => Eq (Result a) Source # 
Instance details

Defined in Text.JSON5

Methods

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

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

Show a => Show (Result a) Source # 
Instance details

Defined in Text.JSON5

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

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

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

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

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

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

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

encodeStrict :: JSON5 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. JSON5 types to be an Array or Object.

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

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

Wrapper Types

data JSObject a Source #

Instances
Eq a => Eq (JSObject a) Source # 
Instance details

Defined in Text.JSON5.Types

Methods

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

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

Ord a => Ord (JSObject a) Source # 
Instance details

Defined in Text.JSON5.Types

Methods

compare :: JSObject a -> JSObject a -> Ordering #

(<) :: JSObject a -> JSObject a -> Bool #

(<=) :: JSObject a -> JSObject a -> Bool #

(>) :: JSObject a -> JSObject a -> Bool #

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

max :: JSObject a -> JSObject a -> JSObject a #

min :: JSObject a -> JSObject a -> JSObject a #

Read a => Read (JSObject a) Source # 
Instance details

Defined in Text.JSON5.Types

Show a => Show (JSObject a) Source # 
Instance details

Defined in Text.JSON5.Types

Methods

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

show :: JSObject a -> String #

showList :: [JSObject a] -> ShowS #

JSON5 a => JSON5 (JSObject a) Source # 
Instance details

Defined in Text.JSON5

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

Map Results to Eithers

Serialization to and from Strings.

Reading JSON5

readJSNull :: GetJSON JSValue Source #

Read the JSON5 null type

readJSBool :: GetJSON JSValue Source #

Read the JSON5 Bool type

readJSString :: Char -> GetJSON JSValue Source #

Strings

Read the JSON5 String type

readJSRational :: GetJSON Rational Source #

Numbers

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

readJSArray :: GetJSON JSValue Source #

Objects & Arrays

Read a list in JSON5 format

readJSObject :: GetJSON JSValue Source #

Read an object in JSON5 format

readJSValue :: GetJSON JSValue Source #

Read one of several possible JS types

Writing JSON5

showJSNull :: ShowS Source #

Write the JSON5 null type

showJSBool :: Bool -> ShowS Source #

Write the JSON5 Bool type

showJSArray :: [JSValue] -> ShowS Source #

Show a list in JSON format

showJSRational :: Rational -> ShowS Source #

Show a Rational in JSON5 format

showJSInfNaN :: Float -> ShowS Source #

Show a Infinity or NaN in JSON5 format

showJSObject :: JSObject JSValue -> ShowS Source #

Show an association list in JSON format

showJSValue :: JSValue -> ShowS Source #

Show JSON5 values

Instance helpers

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

Pull a value out of a JSON5 object.

class JSKey a where Source #

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

Instances
JSKey Int Source # 
Instance details

Defined in Text.JSON5

JSKey String Source # 
Instance details

Defined in Text.JSON5

JSKey JSString Source # 
Instance details

Defined in Text.JSON5

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

Encode an association list as JSValue value.

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

Decode a JSValue value into an association list.