hackage-security-0.6.2.3: Hackage security library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hackage.Security.JSON

Description

Hackage-specific wrappers around the Util.JSON module

Synopsis

Deserialization errors

data DeserializationError #

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.

Instances

Instances details
Exception DeserializationError # 
Instance details

Defined in Hackage.Security.JSON

Methods

toException :: DeserializationError -> SomeException

fromException :: SomeException -> Maybe DeserializationError

displayException :: DeserializationError -> String

Show DeserializationError # 
Instance details

Defined in Hackage.Security.JSON

Methods

showsPrec :: Int -> DeserializationError -> ShowS

show :: DeserializationError -> String

showList :: [DeserializationError] -> ShowS

Pretty DeserializationError # 
Instance details

Defined in Hackage.Security.JSON

Methods

pretty :: DeserializationError -> String #

MonadError DeserializationError ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

validate :: MonadError DeserializationError m => String -> Bool -> m () #

verifyType :: (ReportSchemaErrors m, MonadError DeserializationError m) => JSValue -> String -> m () #

MonadKeys

class (ReportSchemaErrors m, MonadError DeserializationError m) => MonadKeys m where #

MonadReader-like monad, specialized to key environments

Methods

localKeys :: (KeyEnv -> KeyEnv) -> m a -> m a #

askKeys :: m KeyEnv #

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

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

Reader monads

data ReadJSON_Keys_Layout a #

Instances

Instances details
Applicative ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

MonadKeys ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

Methods

expected :: Expected -> Maybe Got -> ReadJSON_Keys_Layout a #

MonadError DeserializationError ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

MonadReader RepoLayout ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

data ReadJSON_Keys_NoLayout a #

Instances

Instances details
Applicative ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

MonadKeys ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Methods

expected :: Expected -> Maybe Got -> ReadJSON_Keys_NoLayout a #

MonadError DeserializationError ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

data ReadJSON_NoKeys_NoLayout a #

Instances

Instances details
Applicative ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Utility

Writing

data WriteJSON a #

Instances

Instances details
Applicative WriteJSON # 
Instance details

Defined in Hackage.Security.JSON

Methods

pure :: a -> WriteJSON a

(<*>) :: WriteJSON (a -> b) -> WriteJSON a -> WriteJSON b

liftA2 :: (a -> b -> c) -> WriteJSON a -> WriteJSON b -> WriteJSON c

(*>) :: WriteJSON a -> WriteJSON b -> WriteJSON b

(<*) :: WriteJSON a -> WriteJSON b -> WriteJSON a

Functor WriteJSON # 
Instance details

Defined in Hackage.Security.JSON

Methods

fmap :: (a -> b) -> WriteJSON a -> WriteJSON b

(<$) :: a -> WriteJSON b -> WriteJSON a

Monad WriteJSON # 
Instance details

Defined in Hackage.Security.JSON

Methods

(>>=) :: WriteJSON a -> (a -> WriteJSON b) -> WriteJSON b

(>>) :: WriteJSON a -> WriteJSON b -> WriteJSON b

return :: a -> WriteJSON a

MonadReader RepoLayout WriteJSON # 
Instance details

Defined in Hackage.Security.JSON

Utility

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

Render to canonical JSON format

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

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

writeJSON_NoLayout :: ToJSON Identity a => Path Absolute -> a -> IO () #

Re-exports

Type classes

class ToJSON m a where #

Methods

toJSON :: a -> m JSValue #

Instances

Instances details
Monad m => ToJSON m KeyEnv # 
Instance details

Defined in Hackage.Security.Key.Env

Methods

toJSON :: KeyEnv -> m JSValue #

Monad m => ToJSON m FileLength # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: FileLength -> m JSValue #

Monad m => ToJSON m Hash # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: Hash -> m JSValue #

Monad m => ToJSON m KeyThreshold # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: KeyThreshold -> m JSValue #

Monad m => ToJSON m FileInfo # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

toJSON :: FileInfo -> m JSValue #

Monad m => ToJSON m FileMap # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

toJSON :: FileMap -> m JSValue #

Monad m => ToJSON m FileExpires # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

toJSON :: FileExpires -> m JSValue #

Monad m => ToJSON m FileVersion # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

toJSON :: FileVersion -> m JSValue #

Monad m => ToJSON m Mirror # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

toJSON :: Mirror -> m JSValue #

Monad m => ToJSON m Mirrors # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

toJSON :: Mirrors -> m JSValue #

Monad m => ToJSON m Root # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: Root -> m JSValue #

Monad m => ToJSON m RootRoles # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: RootRoles -> m JSValue #

Monad m => ToJSON m PreSignature # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

toJSON :: PreSignature -> m JSValue #

Monad m => ToJSON m Signatures # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

toJSON :: Signatures -> m JSValue #

MonadReader RepoLayout m => ToJSON m Snapshot # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

Methods

toJSON :: Snapshot -> m JSValue #

Monad m => ToJSON m DelegationSpec # 
Instance details

Defined in Hackage.Security.TUF.Targets

Monad m => ToJSON m Delegations # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

toJSON :: Delegations -> m JSValue #

Monad m => ToJSON m Targets # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

toJSON :: Targets -> m JSValue #

MonadReader RepoLayout m => ToJSON m Timestamp # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

Methods

toJSON :: Timestamp -> m JSValue #

Monad m => ToJSON m Int54 # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Int54 -> m JSValue #

Monad m => ToJSON m JSValue # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: JSValue -> m JSValue #

Monad m => ToJSON m URI # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: URI -> m JSValue #

Monad m => ToJSON m UTCTime # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: UTCTime -> m JSValue #

Monad m => ToJSON m String # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: String -> m JSValue #

Monad m => ToJSON m (Key typ) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Key typ -> m JSValue #

Monad m => ToJSON m (KeyType typ) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: KeyType typ -> m JSValue #

Monad m => ToJSON m (PublicKey typ) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: PublicKey typ -> m JSValue #

Monad m => ToJSON m (RoleSpec a) # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: RoleSpec a -> m JSValue #

(Monad m, ToJSON m a) => ToJSON m (Signed a) # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

toJSON :: Signed a -> m JSValue #

(Monad m, ToJSON m a) => ToJSON m (UninterpretedSignatures a) # 
Instance details

Defined in Hackage.Security.TUF.Signed

Monad m => ToJSON m (Some Key) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Some Key -> m JSValue #

Monad m => ToJSON m (Some KeyType) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Some KeyType -> m JSValue #

Monad m => ToJSON m (Some PublicKey) # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Some PublicKey -> m JSValue #

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

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: [a] -> m JSValue #

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

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Map k a -> m JSValue #

class FromJSON m a where #

Methods

fromJSON :: JSValue -> m a #

Instances

Instances details
ReportSchemaErrors m => FromJSON m KeyEnv # 
Instance details

Defined in Hackage.Security.Key.Env

Methods

fromJSON :: JSValue -> m KeyEnv #

ReportSchemaErrors m => FromJSON m FileLength # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

fromJSON :: JSValue -> m FileLength #

ReportSchemaErrors m => FromJSON m Hash # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

fromJSON :: JSValue -> m Hash #

ReportSchemaErrors m => FromJSON m KeyThreshold # 
Instance details

Defined in Hackage.Security.TUF.Common

ReportSchemaErrors m => FromJSON m FileInfo # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

fromJSON :: JSValue -> m FileInfo #

ReportSchemaErrors m => FromJSON m FileMap # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

fromJSON :: JSValue -> m FileMap #

ReportSchemaErrors m => FromJSON m FileExpires # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

fromJSON :: JSValue -> m FileExpires #

ReportSchemaErrors m => FromJSON m FileVersion # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

fromJSON :: JSValue -> m FileVersion #

ReportSchemaErrors m => FromJSON m Header # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

fromJSON :: JSValue -> m Header #

ReportSchemaErrors m => FromJSON m Mirror # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

fromJSON :: JSValue -> m Mirror #

(MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Mirrors # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

fromJSON :: JSValue -> m Mirrors #

MonadKeys m => FromJSON m RootRoles # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m RootRoles #

ReportSchemaErrors m => FromJSON m PreSignature # 
Instance details

Defined in Hackage.Security.TUF.Signed

MonadKeys m => FromJSON m Signatures # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

fromJSON :: JSValue -> m Signatures #

(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Snapshot # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

Methods

fromJSON :: JSValue -> m Snapshot #

MonadKeys m => FromJSON m DelegationSpec # 
Instance details

Defined in Hackage.Security.TUF.Targets

MonadKeys m => FromJSON m Delegations # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

fromJSON :: JSValue -> m Delegations #

MonadKeys m => FromJSON m Targets # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

fromJSON :: JSValue -> m Targets #

(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Timestamp # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

Methods

fromJSON :: JSValue -> m Timestamp #

ReportSchemaErrors m => FromJSON m Int54 # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m Int54 #

Monad m => FromJSON m JSValue # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m JSValue #

ReportSchemaErrors m => FromJSON m URI # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m URI #

ReportSchemaErrors m => FromJSON m UTCTime # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m UTCTime #

ReportSchemaErrors m => FromJSON m String # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m String #

MonadKeys m => FromJSON m (RoleSpec a) # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

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

MonadKeys m => FromJSON m (Signed Mirrors) # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

fromJSON :: JSValue -> m (Signed Mirrors) #

MonadKeys m => FromJSON m (Signed Root) #

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.

Instance details

Defined in Hackage.Security.TUF.Root

Methods

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

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

Methods

fromJSON :: JSValue -> m (Signed Snapshot) #

MonadKeys m => FromJSON m (Signed Targets) # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

fromJSON :: JSValue -> m (Signed Targets) #

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

Methods

fromJSON :: JSValue -> m (Signed Timestamp) #

(ReportSchemaErrors m, FromJSON m a) => FromJSON m (UninterpretedSignatures a) # 
Instance details

Defined in Hackage.Security.TUF.Signed

ReportSchemaErrors m => FromJSON m (Some Key) # 
Instance details

Defined in Hackage.Security.Key

Methods

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

ReportSchemaErrors m => FromJSON m (Some KeyType) # 
Instance details

Defined in Hackage.Security.Key

Methods

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

ReportSchemaErrors m => FromJSON m (Some PublicKey) # 
Instance details

Defined in Hackage.Security.Key

Methods

fromJSON :: JSValue -> m (Some PublicKey) #

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

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m [a] #

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

Defined in Hackage.Security.Util.JSON

Methods

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

class ToObjectKey m a where #

Used in the ToJSON instance for Map

Methods

toObjectKey :: a -> m String #

Instances

Instances details
Monad m => ToObjectKey m KeyId # 
Instance details

Defined in Hackage.Security.Key

Methods

toObjectKey :: KeyId -> m String #

Monad m => ToObjectKey m HashFn # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

toObjectKey :: HashFn -> m String #

Monad m => ToObjectKey m TargetPath # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

toObjectKey :: TargetPath -> m String #

Monad m => ToObjectKey m String # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toObjectKey :: String -> m String #

Monad m => ToObjectKey m (Path root) # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toObjectKey :: Path root -> m String #

class FromObjectKey m a where #

Used in the FromJSON instance for Map

Methods

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

Instances

Instances details
Monad m => FromObjectKey m KeyId # 
Instance details

Defined in Hackage.Security.Key

Methods

fromObjectKey :: String -> m (Maybe KeyId) #

ReportSchemaErrors m => FromObjectKey m HashFn # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

fromObjectKey :: String -> m (Maybe HashFn) #

ReportSchemaErrors m => FromObjectKey m TargetPath # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

fromObjectKey :: String -> m (Maybe TargetPath) #

Monad m => FromObjectKey m String # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

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

Monad m => FromObjectKey m (Path root) # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromObjectKey :: String -> m (Maybe (Path root)) #

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

Monads in which we can report schema errors

Methods

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

Instances

Instances details
ReportSchemaErrors ReadJSON_Keys_Layout # 
Instance details

Defined in Hackage.Security.JSON

Methods

expected :: Expected -> Maybe Got -> ReadJSON_Keys_Layout a #

ReportSchemaErrors ReadJSON_Keys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

Methods

expected :: Expected -> Maybe Got -> ReadJSON_Keys_NoLayout a #

ReportSchemaErrors ReadJSON_NoKeys_NoLayout # 
Instance details

Defined in Hackage.Security.JSON

type Expected = String #

type Got = String #

Utility

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

Extract a field from a JSON object

fromJSOptField :: (ReportSchemaErrors m, FromJSON m a) => JSValue -> String -> m (Maybe a) #

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

Re-exports

data JSValue #

Constructors

JSNull 
JSBool !Bool 
JSNum !Int54 
JSString String 
JSArray [JSValue] 
JSObject [(String, JSValue)] 

Instances

Instances details
Read JSValue # 
Instance details

Defined in Text.JSON.Canonical

Methods

readsPrec :: Int -> ReadS JSValue

readList :: ReadS [JSValue]

readPrec :: ReadPrec JSValue

readListPrec :: ReadPrec [JSValue]

Show JSValue # 
Instance details

Defined in Text.JSON.Canonical

Methods

showsPrec :: Int -> JSValue -> ShowS

show :: JSValue -> String

showList :: [JSValue] -> ShowS

Eq JSValue # 
Instance details

Defined in Text.JSON.Canonical

Methods

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

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

Ord JSValue # 
Instance details

Defined in Text.JSON.Canonical

Methods

compare :: JSValue -> JSValue -> Ordering

(<) :: JSValue -> JSValue -> Bool

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

(>) :: JSValue -> JSValue -> Bool

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

max :: JSValue -> JSValue -> JSValue

min :: JSValue -> JSValue -> JSValue

Monad m => FromJSON m JSValue # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m JSValue #

Monad m => ToJSON m JSValue # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: JSValue -> m JSValue #

data Int54 #

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

Instances details
Data Int54 # 
Instance details

Defined in Text.JSON.Canonical

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 :: forall r r'. (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

Storable Int54 # 
Instance details

Defined in Text.JSON.Canonical

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 # 
Instance details

Defined in Text.JSON.Canonical

Methods

(.&.) :: Int54 -> Int54 -> Int54

(.|.) :: Int54 -> Int54 -> Int54

xor :: Int54 -> Int54 -> Int54

complement :: Int54 -> Int54

shift :: Int54 -> Int -> Int54

rotate :: Int54 -> Int -> Int54

zeroBits :: Int54

bit :: Int -> Int54

setBit :: Int54 -> Int -> Int54

clearBit :: Int54 -> Int -> Int54

complementBit :: Int54 -> Int -> Int54

testBit :: Int54 -> Int -> Bool

bitSizeMaybe :: Int54 -> Maybe Int

bitSize :: Int54 -> Int

isSigned :: Int54 -> Bool

shiftL :: Int54 -> Int -> Int54

unsafeShiftL :: Int54 -> Int -> Int54

shiftR :: Int54 -> Int -> Int54

unsafeShiftR :: Int54 -> Int -> Int54

rotateL :: Int54 -> Int -> Int54

rotateR :: Int54 -> Int -> Int54

popCount :: Int54 -> Int

FiniteBits Int54 # 
Instance details

Defined in Text.JSON.Canonical

Bounded Int54 # 
Instance details

Defined in Text.JSON.Canonical

Enum Int54 # 
Instance details

Defined in Text.JSON.Canonical

Ix Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

range :: (Int54, Int54) -> [Int54]

index :: (Int54, Int54) -> Int54 -> Int

unsafeIndex :: (Int54, Int54) -> Int54 -> Int

inRange :: (Int54, Int54) -> Int54 -> Bool

rangeSize :: (Int54, Int54) -> Int

unsafeRangeSize :: (Int54, Int54) -> Int

Num Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

(+) :: Int54 -> Int54 -> Int54

(-) :: Int54 -> Int54 -> Int54

(*) :: Int54 -> Int54 -> Int54

negate :: Int54 -> Int54

abs :: Int54 -> Int54

signum :: Int54 -> Int54

fromInteger :: Integer -> Int54

Read Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

readsPrec :: Int -> ReadS Int54

readList :: ReadS [Int54]

readPrec :: ReadPrec Int54

readListPrec :: ReadPrec [Int54]

Integral Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

quot :: Int54 -> Int54 -> Int54

rem :: Int54 -> Int54 -> Int54

div :: Int54 -> Int54 -> Int54

mod :: Int54 -> Int54 -> Int54

quotRem :: Int54 -> Int54 -> (Int54, Int54)

divMod :: Int54 -> Int54 -> (Int54, Int54)

toInteger :: Int54 -> Integer

Real Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

toRational :: Int54 -> Rational

Show Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

showsPrec :: Int -> Int54 -> ShowS

show :: Int54 -> String

showList :: [Int54] -> ShowS

PrintfArg Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

formatArg :: Int54 -> FieldFormatter

parseFormat :: Int54 -> ModifierParser

Eq Int54 # 
Instance details

Defined in Text.JSON.Canonical

Methods

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

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

Ord Int54 # 
Instance details

Defined in Text.JSON.Canonical

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

ReportSchemaErrors m => FromJSON m Int54 # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m Int54 #

Monad m => ToJSON m Int54 # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Int54 -> m JSValue #