Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hackage-specific wrappers around the Util.JSON module
- data DeserializationError
- validate :: MonadError DeserializationError m => String -> Bool -> m ()
- verifyType :: (ReportSchemaErrors m, MonadError DeserializationError m) => JSValue -> String -> m ()
- class (ReportSchemaErrors m, MonadError DeserializationError m) => MonadKeys m where
- addKeys :: MonadKeys m => KeyEnv -> m a -> m a
- withKeys :: MonadKeys m => KeyEnv -> m a -> m a
- lookupKey :: MonadKeys m => KeyId -> m (Some PublicKey)
- readKeyAsId :: MonadKeys m => JSValue -> m (Some PublicKey)
- data ReadJSON_Keys_Layout a
- data ReadJSON_Keys_NoLayout a
- data ReadJSON_NoKeys_NoLayout a
- runReadJSON_Keys_Layout :: KeyEnv -> RepoLayout -> ReadJSON_Keys_Layout a -> Either DeserializationError a
- runReadJSON_Keys_NoLayout :: KeyEnv -> ReadJSON_Keys_NoLayout a -> Either DeserializationError a
- runReadJSON_NoKeys_NoLayout :: ReadJSON_NoKeys_NoLayout a -> Either DeserializationError a
- parseJSON_Keys_Layout :: FromJSON ReadJSON_Keys_Layout a => KeyEnv -> RepoLayout -> ByteString -> Either DeserializationError a
- parseJSON_Keys_NoLayout :: FromJSON ReadJSON_Keys_NoLayout a => KeyEnv -> ByteString -> Either DeserializationError a
- parseJSON_NoKeys_NoLayout :: FromJSON ReadJSON_NoKeys_NoLayout a => ByteString -> Either DeserializationError a
- readJSON_Keys_Layout :: (FsRoot root, FromJSON ReadJSON_Keys_Layout a) => KeyEnv -> RepoLayout -> Path root -> IO (Either DeserializationError a)
- readJSON_Keys_NoLayout :: (FsRoot root, FromJSON ReadJSON_Keys_NoLayout a) => KeyEnv -> Path root -> IO (Either DeserializationError a)
- readJSON_NoKeys_NoLayout :: (FsRoot root, FromJSON ReadJSON_NoKeys_NoLayout a) => Path root -> IO (Either DeserializationError a)
- data WriteJSON a
- runWriteJSON :: RepoLayout -> WriteJSON a -> a
- renderJSON :: ToJSON WriteJSON a => RepoLayout -> a -> ByteString
- renderJSON_NoLayout :: ToJSON Identity a => a -> ByteString
- writeJSON :: ToJSON WriteJSON a => RepoLayout -> Path Absolute -> a -> IO ()
- writeJSON_NoLayout :: ToJSON Identity a => Path Absolute -> a -> IO ()
- writeKeyAsId :: Some PublicKey -> JSValue
- class ToJSON m a where
- class FromJSON m a where
- class ToObjectKey m a where
- class FromObjectKey m a where
- class (Applicative m, Monad m) => ReportSchemaErrors m where
- type Expected = String
- type Got = String
- expected' :: ReportSchemaErrors m => Expected -> JSValue -> m a
- fromJSObject :: ReportSchemaErrors m => JSValue -> m [(String, JSValue)]
- fromJSField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> String -> m a
- fromJSOptField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> String -> m (Maybe a)
- mkObject :: forall m. Monad m => [(String, m JSValue)] -> m JSValue
- data JSValue
- data Int54
Deserialization errors
data DeserializationError Source #
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. |
validate :: MonadError DeserializationError m => String -> Bool -> m () Source #
verifyType :: (ReportSchemaErrors m, MonadError DeserializationError m) => JSValue -> String -> m () Source #
MonadKeys
class (ReportSchemaErrors m, MonadError DeserializationError m) => MonadKeys m where Source #
MonadReader-like monad, specialized to key environments
Reader monads
data ReadJSON_Keys_Layout a Source #
data ReadJSON_Keys_NoLayout a Source #
data ReadJSON_NoKeys_NoLayout a Source #
runReadJSON_Keys_Layout :: KeyEnv -> RepoLayout -> ReadJSON_Keys_Layout a -> Either DeserializationError a Source #
runReadJSON_Keys_NoLayout :: KeyEnv -> ReadJSON_Keys_NoLayout a -> Either DeserializationError a Source #
Utility
parseJSON_Keys_Layout :: FromJSON ReadJSON_Keys_Layout a => KeyEnv -> RepoLayout -> ByteString -> Either DeserializationError a Source #
parseJSON_Keys_NoLayout :: FromJSON ReadJSON_Keys_NoLayout a => KeyEnv -> ByteString -> Either DeserializationError a Source #
parseJSON_NoKeys_NoLayout :: FromJSON ReadJSON_NoKeys_NoLayout a => ByteString -> Either DeserializationError a Source #
readJSON_Keys_Layout :: (FsRoot root, FromJSON ReadJSON_Keys_Layout a) => KeyEnv -> RepoLayout -> Path root -> IO (Either DeserializationError a) Source #
readJSON_Keys_NoLayout :: (FsRoot root, FromJSON ReadJSON_Keys_NoLayout a) => KeyEnv -> Path root -> IO (Either DeserializationError a) Source #
readJSON_NoKeys_NoLayout :: (FsRoot root, FromJSON ReadJSON_NoKeys_NoLayout a) => Path root -> IO (Either DeserializationError a) Source #
Writing
runWriteJSON :: RepoLayout -> WriteJSON a -> a Source #
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 #
class FromJSON m a where Source #
class ToObjectKey m a where Source #
toObjectKey :: a -> m String Source #
Monad m => ToObjectKey m String Source # | |
Monad m => ToObjectKey m KeyId Source # | |
Monad m => ToObjectKey m HashFn Source # | |
Monad m => ToObjectKey m TargetPath Source # | |
Monad m => ToObjectKey m (Path root) Source # | |
class FromObjectKey m a where Source #
fromObjectKey :: String -> m (Maybe a) Source #
Monad m => FromObjectKey m String Source # | |
Monad m => FromObjectKey m KeyId Source # | |
ReportSchemaErrors m => FromObjectKey m HashFn Source # | |
ReportSchemaErrors m => FromObjectKey m TargetPath Source # | |
Monad m => FromObjectKey m (Path root) Source # | |
class (Applicative m, Monad m) => ReportSchemaErrors m where Source #
Monads in which we can report schema errors
Utility
fromJSObject :: ReportSchemaErrors m => JSValue -> m [(String, JSValue)] Source #
fromJSField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> String -> m a Source #
Extract a field from a JSON object
fromJSOptField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> String -> m (Maybe a) Source #
Re-exports
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.
Bounded Int54 Source # | |
Enum Int54 Source # | |
Eq Int54 Source # | |
Integral Int54 Source # | |
Data Int54 Source # | |
Num Int54 Source # | |
Ord Int54 Source # | |
Read Int54 Source # | |
Real Int54 Source # | |
Show Int54 Source # | |
Ix Int54 Source # | |
PrintfArg Int54 Source # | |
Storable Int54 Source # | |
Bits Int54 Source # | |
FiniteBits Int54 Source # | |
ReportSchemaErrors m => FromJSON m Int54 Source # | |
Monad m => ToJSON m Int54 Source # | |