hackage-security-0.5.3.0: Hackage security library

Safe HaskellNone
LanguageHaskell2010

Hackage.Security.JSON

Contents

Description

Hackage-specific wrappers around the Util.JSON module

Synopsis

Deserialization errors

data DeserializationError Source #

Constructors

DeserializationErrorMalformed String

Malformed JSON has syntax errors in the JSON itself (i.e., we cannot even parse it to a JSValue)

DeserializationErrorSchema String

Invalid JSON has valid syntax but invalid structure

The string gives a hint about what we expected instead

DeserializationErrorUnknownKey KeyId

The JSON file contains a key ID of an unknown key

DeserializationErrorValidation String

Some verification step failed

DeserializationErrorFileType String String

Wrong file type

Records actual and expected types.

MonadKeys

addKeys :: MonadKeys m => KeyEnv -> m a -> m a Source #

withKeys :: MonadKeys m => KeyEnv -> m a -> m a Source #

Reader monads

data ReadJSON_Keys_Layout a Source #

Instances

Monad ReadJSON_Keys_Layout Source # 
Functor ReadJSON_Keys_Layout Source # 
Applicative ReadJSON_Keys_Layout Source # 
ReportSchemaErrors ReadJSON_Keys_Layout Source # 
MonadKeys ReadJSON_Keys_Layout Source # 
MonadReader RepoLayout ReadJSON_Keys_Layout Source # 
MonadError DeserializationError ReadJSON_Keys_Layout Source # 

data ReadJSON_Keys_NoLayout a Source #

Instances

Monad ReadJSON_Keys_NoLayout Source # 
Functor ReadJSON_Keys_NoLayout Source # 
Applicative ReadJSON_Keys_NoLayout Source # 
ReportSchemaErrors ReadJSON_Keys_NoLayout Source # 
MonadKeys ReadJSON_Keys_NoLayout Source # 
MonadError DeserializationError ReadJSON_Keys_NoLayout Source # 

Utility

Writing

data WriteJSON a Source #

Instances

Utility

renderJSON :: ToJSON WriteJSON a => RepoLayout -> a -> ByteString Source #

Render to canonical JSON format

renderJSON_NoLayout :: ToJSON Identity a => a -> ByteString Source #

Variation on renderJSON for files that don't require the repo layout

Re-exports

Type classes

class ToJSON m a where Source #

Minimal complete definition

toJSON

Methods

toJSON :: a -> m JSValue Source #

Instances

Monad m => ToJSON m URI Source # 

Methods

toJSON :: URI -> m JSValue Source #

Monad m => ToJSON m UTCTime Source # 

Methods

toJSON :: UTCTime -> m JSValue Source #

Monad m => ToJSON m Int54 Source # 

Methods

toJSON :: Int54 -> m JSValue Source #

Monad m => ToJSON m String Source # 

Methods

toJSON :: String -> m JSValue Source #

Monad m => ToJSON m JSValue Source # 

Methods

toJSON :: JSValue -> m JSValue Source #

Monad m => ToJSON m KeyEnv Source # 

Methods

toJSON :: KeyEnv -> m JSValue Source #

Monad m => ToJSON m PreSignature Source # 
Monad m => ToJSON m Signatures Source # 
Monad m => ToJSON m FileExpires Source # 
Monad m => ToJSON m FileVersion Source # 
Monad m => ToJSON m Mirrors Source # 

Methods

toJSON :: Mirrors -> m JSValue Source #

Monad m => ToJSON m Mirror Source # 

Methods

toJSON :: Mirror -> m JSValue Source #

Monad m => ToJSON m Hash Source # 

Methods

toJSON :: Hash -> m JSValue Source #

Monad m => ToJSON m FileLength Source # 
Monad m => ToJSON m KeyThreshold Source # 
Monad m => ToJSON m FileInfo Source # 

Methods

toJSON :: FileInfo -> m JSValue Source #

Monad m => ToJSON m FileMap Source # 

Methods

toJSON :: FileMap -> m JSValue Source #

MonadReader RepoLayout m => ToJSON m Timestamp Source # 
Monad m => ToJSON m Targets Source # 

Methods

toJSON :: Targets -> m JSValue Source #

Monad m => ToJSON m Delegations Source # 
Monad m => ToJSON m DelegationSpec Source # 
MonadReader RepoLayout m => ToJSON m Snapshot Source # 

Methods

toJSON :: Snapshot -> m JSValue Source #

Monad m => ToJSON m Root Source # 

Methods

toJSON :: Root -> m JSValue Source #

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

Methods

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

Monad m => ToJSON m (KeyType typ) Source # 

Methods

toJSON :: KeyType typ -> m JSValue Source #

Monad m => ToJSON m (Some KeyType) Source # 
Monad m => ToJSON m (Some PublicKey) Source # 
Monad m => ToJSON m (Some Key) Source # 

Methods

toJSON :: Some Key -> m JSValue Source #

Monad m => ToJSON m (PublicKey typ) Source # 

Methods

toJSON :: PublicKey typ -> m JSValue Source #

Monad m => ToJSON m (Key typ) Source # 

Methods

toJSON :: Key typ -> m JSValue Source #

(Monad m, ToJSON m a) => ToJSON m (UninterpretedSignatures a) Source # 
(Monad m, ToJSON m a) => ToJSON m (Signed a) Source # 

Methods

toJSON :: Signed a -> m JSValue Source #

Monad m => ToJSON m (RoleSpec a) Source # 

Methods

toJSON :: RoleSpec a -> m JSValue Source #

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

Methods

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

class FromJSON m a where Source #

Minimal complete definition

fromJSON

Methods

fromJSON :: JSValue -> m a Source #

Instances

ReportSchemaErrors m => FromJSON m URI Source # 

Methods

fromJSON :: JSValue -> m URI Source #

ReportSchemaErrors m => FromJSON m UTCTime Source # 
ReportSchemaErrors m => FromJSON m Int54 Source # 

Methods

fromJSON :: JSValue -> m Int54 Source #

ReportSchemaErrors m => FromJSON m String Source # 

Methods

fromJSON :: JSValue -> m String Source #

Monad m => FromJSON m JSValue Source # 
ReportSchemaErrors m => FromJSON m KeyEnv Source # 

Methods

fromJSON :: JSValue -> m KeyEnv Source #

ReportSchemaErrors m => FromJSON m PreSignature Source # 
MonadKeys m => FromJSON m Signatures Source # 
ReportSchemaErrors m => FromJSON m Header Source # 

Methods

fromJSON :: JSValue -> m Header Source #

ReportSchemaErrors m => FromJSON m FileExpires Source # 
ReportSchemaErrors m => FromJSON m FileVersion Source # 
(MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Mirrors Source # 
ReportSchemaErrors m => FromJSON m Mirror Source # 

Methods

fromJSON :: JSValue -> m Mirror Source #

ReportSchemaErrors m => FromJSON m Hash Source # 

Methods

fromJSON :: JSValue -> m Hash Source #

ReportSchemaErrors m => FromJSON m FileLength Source # 
ReportSchemaErrors m => FromJSON m KeyThreshold Source # 
ReportSchemaErrors m => FromJSON m FileInfo Source # 
ReportSchemaErrors m => FromJSON m FileMap Source # 
(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Timestamp Source # 
MonadKeys m => FromJSON m Targets Source # 
MonadKeys m => FromJSON m Delegations Source # 
MonadKeys m => FromJSON m DelegationSpec Source # 
(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Snapshot Source # 
MonadKeys m => FromJSON m RootRoles Source # 
(ReportSchemaErrors m, FromJSON m a) => FromJSON m [a] Source # 

Methods

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

ReportSchemaErrors m => FromJSON m (Some KeyType) Source # 

Methods

fromJSON :: JSValue -> m (Some KeyType) Source #

ReportSchemaErrors m => FromJSON m (Some PublicKey) Source # 
ReportSchemaErrors m => FromJSON m (Some Key) Source # 

Methods

fromJSON :: JSValue -> m (Some Key) Source #

(ReportSchemaErrors m, FromJSON m a) => FromJSON m (UninterpretedSignatures a) Source # 
MonadKeys m => FromJSON m (Signed Mirrors) Source # 
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) Source # 
MonadKeys m => FromJSON m (Signed Targets) Source # 
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) Source # 
MonadKeys m => FromJSON m (RoleSpec a) Source # 

Methods

fromJSON :: JSValue -> m (RoleSpec a) Source #

MonadKeys m => FromJSON m (Signed Root) Source #

We give an instance for Signed Root rather than Root because the key environment from the root data is necessary to resolve the explicit sharing in the signatures.

Methods

fromJSON :: JSValue -> m (Signed Root) Source #

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

Methods

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

class ToObjectKey m a where Source #

Used in the ToJSON instance for Map

Minimal complete definition

toObjectKey

Methods

toObjectKey :: a -> m String Source #

class FromObjectKey m a where Source #

Used in the FromJSON instance for Map

Minimal complete definition

fromObjectKey

Methods

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

Utility

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

Extract a field from a JSON object

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

Re-exports

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 # 
Enum Int54 Source # 
Eq Int54 Source # 

Methods

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

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

Integral Int54 Source # 
Data Int54 Source # 

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 # 
Ord Int54 Source # 

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 # 
Real Int54 Source # 

Methods

toRational :: Int54 -> Rational #

Show Int54 Source # 

Methods

showsPrec :: Int -> Int54 -> ShowS #

show :: Int54 -> String #

showList :: [Int54] -> ShowS #

Ix Int54 Source # 
PrintfArg Int54 Source # 
Storable Int54 Source # 

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 # 
FiniteBits Int54 Source # 
ReportSchemaErrors m => FromJSON m Int54 Source # 

Methods

fromJSON :: JSValue -> m Int54 Source #

Monad m => ToJSON m Int54 Source # 

Methods

toJSON :: Int54 -> m JSValue Source #