canonical-json-0.6.0.0: Canonical JSON for signing and hashing JSON values

Copyright(c) Duncan Coutts 2017
Safe HaskellNone
LanguageHaskell2010

Text.JSON.Canonical

Contents

Description

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

Types

data JSValue Source #

Instances
Eq JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

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

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

Ord JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Read JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Show JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Types

NFData JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

rnf :: JSValue -> () #

Monad m => FromJSON m JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => ToJSON m JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: JSValue -> m JSValue Source #

data Int54 Source #

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
Bounded Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Enum Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Eq Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

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

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

Integral Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Data Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int54 -> c Int54 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int54 #

toConstr :: Int54 -> Constr #

dataTypeOf :: Int54 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int54) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int54) #

gmapT :: (forall b. Data b => b -> b) -> Int54 -> Int54 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int54 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int54 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

Num Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Ord Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

compare :: Int54 -> Int54 -> Ordering #

(<) :: Int54 -> Int54 -> Bool #

(<=) :: Int54 -> Int54 -> Bool #

(>) :: Int54 -> Int54 -> Bool #

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

max :: Int54 -> Int54 -> Int54 #

min :: Int54 -> Int54 -> Int54 #

Read Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Real Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

toRational :: Int54 -> Rational #

Show Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

showsPrec :: Int -> Int54 -> ShowS #

show :: Int54 -> String #

showList :: [Int54] -> ShowS #

Ix Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

PrintfArg Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Storable Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

sizeOf :: Int54 -> Int #

alignment :: Int54 -> Int #

peekElemOff :: Ptr Int54 -> Int -> IO Int54 #

pokeElemOff :: Ptr Int54 -> Int -> Int54 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int54 #

pokeByteOff :: Ptr b -> Int -> Int54 -> IO () #

peek :: Ptr Int54 -> IO Int54 #

poke :: Ptr Int54 -> Int54 -> IO () #

Bits Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

FiniteBits Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Types

ReportSchemaErrors m => FromJSON m Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

fromJSON :: JSValue -> m Int54 Source #

Monad m => ToJSON m Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: Int54 -> m JSValue Source #

data JSString Source #

Canonical JSON strings are in fact just bytes.

Instances
Eq JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Ord JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Read JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Show JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

IsString JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Semigroup JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Monoid JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

PrintfArg JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

NFData JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Types

Methods

rnf :: JSString -> () #

Monad m => FromObjectKey m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => ToObjectKey m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

ReportSchemaErrors m => FromJSON m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => ToJSON m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: JSString -> m JSValue 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 #

Methods

toJSON :: a -> m JSValue Source #

Instances
Monad m => ToJSON m Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: Int54 -> m JSValue Source #

Monad m => ToJSON m String Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: String -> m JSValue Source #

Monad m => ToJSON m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: JSString -> m JSValue Source #

Monad m => ToJSON m JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: JSValue -> m JSValue Source #

(Monad m, ToJSON m a) => ToJSON m [a] Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: [a] -> m JSValue Source #

(Monad m, ToObjectKey m k, ToJSON m a) => ToJSON m (Map k a) Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

toJSON :: Map k a -> m JSValue Source #

class FromJSON m a where Source #

Methods

fromJSON :: JSValue -> m a Source #

Instances
ReportSchemaErrors m => FromJSON m Int54 Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

fromJSON :: JSValue -> m Int54 Source #

ReportSchemaErrors m => FromJSON m String Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

fromJSON :: JSValue -> m String Source #

ReportSchemaErrors m => FromJSON m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => FromJSON m JSValue Source # 
Instance details

Defined in Text.JSON.Canonical.Class

(ReportSchemaErrors m, FromJSON m a) => FromJSON m [a] Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

fromJSON :: JSValue -> m [a] Source #

(ReportSchemaErrors m, Ord k, FromObjectKey m k, FromJSON m a) => FromJSON m (Map k a) Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Methods

fromJSON :: JSValue -> m (Map k a) Source #

class ToObjectKey m a where Source #

Used in the ToJSON instance for Map

Methods

toObjectKey :: a -> m JSString Source #

Instances
Monad m => ToObjectKey m String Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => ToObjectKey m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

class FromObjectKey m a where Source #

Used in the FromJSON instance for Map

Methods

fromObjectKey :: JSString -> m (Maybe a) Source #

Instances
Monad m => FromObjectKey m String Source # 
Instance details

Defined in Text.JSON.Canonical.Class

Monad m => FromObjectKey m JSString Source # 
Instance details

Defined in Text.JSON.Canonical.Class

class (Applicative m, Monad m) => ReportSchemaErrors m where Source #

Monads in which we can report schema errors

Methods

expected :: Expected -> Maybe Got -> m a Source #

Utility

fromJSField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> JSString -> m a Source #

Extract a field from a JSON object

mkObject :: forall m. Monad m => [(JSString, m JSValue)] -> m JSValue Source #