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

Copyright(c) Duncan Coutts 2015 2017
Safe HaskellNone
LanguageHaskell2010

Text.JSON.Canonical.Types

Description

 
Synopsis

Documentation

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 #

newtype 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.

Constructors

Int54 

Fields

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 #