Copyright | (c) Duncan Coutts 2017 |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
An implementation of Canonical JSON.
http://wiki.laptop.org/go/Canonical_JSON
The "canonical JSON" format is designed to provide repeatable hashes of JSON-encoded data. It is designed for applications that need to hash, sign or authenitcate JSON data structures.
The format is an extended subset of the normal JSON format.
Canonical JSON is parsable with any full JSON parser, and it allows whitespace for pretty-printed human readable presentation, but it can be put into a canonical form which then has a stable serialised representation and thus a stable hash.
The basic concept is that a file in the canonical JSON format can be read
using parseCanonicalJSON
. Note that this input file does not itself need
to be in canonical form, it just needs to be in the canonical JSON format.
Then the renderCanonicalJSON
function is used to render into the canonical
form. This is then the form that can be hashed or signed etc.
The prettyCanonicalJSON
is for convenience to render in a human readable
style, since the canoncal form eliminates unnecessary white space which
makes the output hard to read. This style is again suitable to read using
parseCanonicalJSON
. So this is suitable to use for producing output that
has to be later hashed or otherwise checked.
Known bugs/limitations:
- Decoding/encoding Unicode code-points beyond
U+00ff
is currently broken
Synopsis
- data JSValue
- data Int54
- data JSString
- parseCanonicalJSON :: ByteString -> Either String JSValue
- renderCanonicalJSON :: JSValue -> ByteString
- prettyCanonicalJSON :: JSValue -> String
- class ToJSON m a where
- class FromJSON m a where
- class ToObjectKey m a where
- toObjectKey :: a -> m JSString
- class FromObjectKey m a where
- fromObjectKey :: JSString -> m (Maybe a)
- class (Applicative m, Monad m) => ReportSchemaErrors m where
- type Expected = String
- type Got = String
- expectedButGotValue :: ReportSchemaErrors m => Expected -> JSValue -> m a
- toJSString :: String -> JSString
- fromJSString :: JSString -> String
- fromJSObject :: ReportSchemaErrors m => JSValue -> m [(JSString, JSValue)]
- fromJSField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> JSString -> m a
- fromJSOptField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> JSString -> m (Maybe a)
- mkObject :: forall m. Monad m => [(JSString, m JSValue)] -> m JSValue
Types
JSNull | |
JSBool !Bool | |
JSNum !Int54 | |
JSString !JSString | |
JSArray [JSValue] | |
JSObject [(JSString, JSValue)] |
54-bit integer values
JavaScript can only safely represent numbers between -(2^53 - 1)
and
2^53 - 1
.
TODO: Although we introduce the type here, we don't actually do any bounds
checking and just inherit all type class instance from Int64. We should
probably define fromInteger
to do bounds checking, give different instances
for type classes such as Bounded
and FiniteBits
, etc.
Instances
Canonical JSON strings are in fact just bytes.
Instances
Eq JSString Source # | |
Ord JSString Source # | |
Defined in Text.JSON.Canonical.Types | |
Read JSString Source # | |
Show JSString Source # | |
IsString JSString Source # | |
Defined in Text.JSON.Canonical.Types fromString :: String -> JSString # | |
Semigroup JSString Source # | |
Monoid JSString Source # | |
PrintfArg JSString Source # | |
Defined in Text.JSON.Canonical.Types formatArg :: JSString -> FieldFormatter # parseFormat :: JSString -> ModifierParser # | |
NFData JSString Source # | |
Defined in Text.JSON.Canonical.Types | |
Monad m => FromObjectKey m JSString Source # | |
Defined in Text.JSON.Canonical.Class | |
Monad m => ToObjectKey m JSString Source # | |
Defined in Text.JSON.Canonical.Class toObjectKey :: JSString -> m JSString Source # | |
ReportSchemaErrors m => FromJSON m JSString Source # | |
Monad m => ToJSON m JSString Source # | |
Parsing and printing
parseCanonicalJSON :: ByteString -> Either String JSValue Source #
Parse a canonical JSON format string as a JSON value. The input string does not have to be in canonical form, just in the "canonical JSON" format.
Use renderCanonicalJSON
to convert into canonical form.
renderCanonicalJSON :: JSValue -> ByteString Source #
Render a JSON value in canonical form. This rendered form is canonical and so allows repeatable hashes.
For pretty printing, see prettyCanonicalJSON.
NB: Canonical JSON's string escaping rules deviate from RFC 7159 JSON which requires
"All Unicode characters may be placed within the quotation
marks, except for the characters that must be escaped: quotation
mark, reverse solidus, and the control characters (U+0000
through U+001F
)."
Whereas the current specification of Canonical JSON explicitly requires to violate this by only escaping the quotation mark and the reverse solidus. This, however, contradicts Canonical JSON's statement that "Canonical JSON is parsable with any full JSON parser"
Consequently, Canonical JSON is not a proper subset of RFC 7159.
prettyCanonicalJSON :: JSValue -> String Source #
Render a JSON value in a reasonable human-readable form. This rendered
form is not the canonical form used for repeatable hashes, use
renderCanonicalJSON
for that.
Type classes
class ToJSON m a where Source #
Instances
Monad m => ToJSON m Int54 Source # | |
Monad m => ToJSON m String Source # | |
Monad m => ToJSON m JSString Source # | |
Monad m => ToJSON m JSValue Source # | |
(Monad m, ToJSON m a) => ToJSON m [a] Source # | |
Defined in Text.JSON.Canonical.Class | |
(Monad m, ToObjectKey m k, ToJSON m a) => ToJSON m (Map k a) Source # | |
class FromJSON m a where Source #
Instances
ReportSchemaErrors m => FromJSON m Int54 Source # | |
ReportSchemaErrors m => FromJSON m String Source # | |
ReportSchemaErrors m => FromJSON m JSString Source # | |
Monad m => FromJSON m JSValue Source # | |
(ReportSchemaErrors m, FromJSON m a) => FromJSON m [a] Source # | |
Defined in Text.JSON.Canonical.Class | |
(ReportSchemaErrors m, Ord k, FromObjectKey m k, FromJSON m a) => FromJSON m (Map k a) Source # | |
class ToObjectKey m a where Source #
toObjectKey :: a -> m JSString Source #
Instances
Monad m => ToObjectKey m String Source # | |
Defined in Text.JSON.Canonical.Class toObjectKey :: String -> m JSString Source # | |
Monad m => ToObjectKey m JSString Source # | |
Defined in Text.JSON.Canonical.Class toObjectKey :: JSString -> m JSString Source # |
class FromObjectKey m a where Source #
fromObjectKey :: JSString -> m (Maybe a) Source #
Instances
Monad m => FromObjectKey m String Source # | |
Defined in Text.JSON.Canonical.Class | |
Monad m => FromObjectKey m JSString Source # | |
Defined in Text.JSON.Canonical.Class |
class (Applicative m, Monad m) => ReportSchemaErrors m where Source #
Monads in which we can report schema errors
expectedButGotValue :: ReportSchemaErrors m => Expected -> JSValue -> m a Source #
Utility
toJSString :: String -> JSString Source #
fromJSString :: JSString -> String Source #
fromJSObject :: ReportSchemaErrors m => JSValue -> m [(JSString, JSValue)] Source #
fromJSField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> JSString -> m a Source #
Extract a field from a JSON object
fromJSOptField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> JSString -> m (Maybe a) Source #