Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Vault.KVv2.Client.Types
Documentation
type VaultToken = String Source #
data VaultConnection Source #
Constructors
VaultConnection | |
Fields
|
Instances
Show VaultConnection Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> VaultConnection -> ShowS # show :: VaultConnection -> String # showList :: [VaultConnection] -> ShowS # |
newtype SecretVersions Source #
Constructors
SecretVersions [SecretVersion] |
Instances
Eq SecretVersions Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods (==) :: SecretVersions -> SecretVersions -> Bool # (/=) :: SecretVersions -> SecretVersions -> Bool # | |
Show SecretVersions Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> SecretVersions -> ShowS # show :: SecretVersions -> String # showList :: [SecretVersions] -> ShowS # | |
ToJSON SecretVersions Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods toJSON :: SecretVersions -> Value # toEncoding :: SecretVersions -> Encoding # toJSONList :: [SecretVersions] -> Value # toEncodingList :: [SecretVersions] -> Encoding # |
newtype SecretVersion Source #
Constructors
SecretVersion Int |
Instances
Eq SecretVersion Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods (==) :: SecretVersion -> SecretVersion -> Bool # (/=) :: SecretVersion -> SecretVersion -> Bool # | |
Show SecretVersion Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> SecretVersion -> ShowS # show :: SecretVersion -> String # showList :: [SecretVersion] -> ShowS # | |
Generic SecretVersion Source # | |
Defined in Database.Vault.KVv2.Client.Types Associated Types type Rep SecretVersion :: Type -> Type # | |
Hashable SecretVersion Source # | |
Defined in Database.Vault.KVv2.Client.Types | |
type Rep SecretVersion Source # | |
Defined in Database.Vault.KVv2.Client.Types type Rep SecretVersion = D1 (MetaData "SecretVersion" "Database.Vault.KVv2.Client.Types" "gothic-0.1.2-I92vKypLdMf7W1Bkgf3zWb" True) (C1 (MetaCons "SecretVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
newtype SecretMetadata Source #
Constructors
SecretMetadata (HashMap SecretVersion Metadata) |
Instances
Eq SecretMetadata Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods (==) :: SecretMetadata -> SecretMetadata -> Bool # (/=) :: SecretMetadata -> SecretMetadata -> Bool # | |
Show SecretMetadata Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> SecretMetadata -> ShowS # show :: SecretMetadata -> String # showList :: [SecretMetadata] -> ShowS # | |
FromJSON SecretMetadata Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods parseJSON :: Value -> Parser SecretMetadata # parseJSONList :: Value -> Parser [SecretMetadata] # |
Constructors
Metadata | |
Fields
|
Instances
Eq Metadata Source # | |
Show Metadata Source # | |
Generic Metadata Source # | |
ToJSON Metadata Source # | |
Defined in Database.Vault.KVv2.Client.Types | |
FromJSON Metadata Source # | |
type Rep Metadata Source # | |
Defined in Database.Vault.KVv2.Client.Types type Rep Metadata = D1 (MetaData "Metadata" "Database.Vault.KVv2.Client.Types" "gothic-0.1.2-I92vKypLdMf7W1Bkgf3zWb" False) (C1 (MetaCons "Metadata" PrefixI True) (S1 (MetaSel (Just "destroyed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "deletion_time") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "created_time") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) |
newtype SecretData Source #
Constructors
SecretData (HashMap Text Text) |
Instances
Show SecretData Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> SecretData -> ShowS # show :: SecretData -> String # showList :: [SecretData] -> ShowS # | |
Generic SecretData Source # | |
Defined in Database.Vault.KVv2.Client.Types Associated Types type Rep SecretData :: Type -> Type # | |
ToJSON SecretData Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods toJSON :: SecretData -> Value # toEncoding :: SecretData -> Encoding # toJSONList :: [SecretData] -> Value # toEncodingList :: [SecretData] -> Encoding # | |
FromJSON SecretData Source # | |
Defined in Database.Vault.KVv2.Client.Types | |
type Rep SecretData Source # | |
Defined in Database.Vault.KVv2.Client.Types |
data SecretSettings Source #
Constructors
SecretSettings | |
Fields
|
Instances
newtype SecretPath Source #
Constructors
SecretPath | |
Instances
Show SecretPath Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> SecretPath -> ShowS # show :: SecretPath -> String # showList :: [SecretPath] -> ShowS # | |
Generic SecretPath Source # | |
Defined in Database.Vault.KVv2.Client.Types Associated Types type Rep SecretPath :: Type -> Type # | |
ToJSON SecretPath Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods toJSON :: SecretPath -> Value # toEncoding :: SecretPath -> Encoding # toJSONList :: [SecretPath] -> Value # toEncodingList :: [SecretPath] -> Encoding # | |
type Rep SecretPath Source # | |
Defined in Database.Vault.KVv2.Client.Types type Rep SecretPath = D1 (MetaData "SecretPath" "Database.Vault.KVv2.Client.Types" "gothic-0.1.2-I92vKypLdMf7W1Bkgf3zWb" True) (C1 (MetaCons "SecretPath" PrefixI True) (S1 (MetaSel (Just "path") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
data CheckAndSet Source #
Constructors
WriteAllowed | |
CreateOnly | |
CurrentVersion !Int |
Instances
newtype PutSecretOptions Source #
Constructors
PutSecretOptions | |
Fields
|
Instances
Show PutSecretOptions Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods showsPrec :: Int -> PutSecretOptions -> ShowS # show :: PutSecretOptions -> String # showList :: [PutSecretOptions] -> ShowS # | |
ToJSON PutSecretOptions Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods toJSON :: PutSecretOptions -> Value # toEncoding :: PutSecretOptions -> Encoding # toJSONList :: [PutSecretOptions] -> Value # toEncodingList :: [PutSecretOptions] -> Encoding # |
data PutSecretRequestBody Source #
Constructors
PutSecretRequestBody | |
Fields |
Instances
ToJSON PutSecretRequestBody Source # | |
Defined in Database.Vault.KVv2.Client.Types Methods toJSON :: PutSecretRequestBody -> Value # toEncoding :: PutSecretRequestBody -> Encoding # toJSONList :: [PutSecretRequestBody] -> Value # toEncodingList :: [PutSecretRequestBody] -> Encoding # |