Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provide an IO-based API. The ks executable provides some keystore management functions that can be used from the shell and Data.KeyStore.KeyStore provides the underlying functional model.
Synopsis
- readSettings :: FilePath -> IO Settings
- data CtxParams = CtxParams {}
- data IC = IC {}
- module Data.KeyStore.Types
- module Data.KeyStore.KS.KS
- keyStoreBytes :: KeyStore -> ByteString
- keyStoreFromBytes :: ByteString -> E KeyStore
- settingsFromBytes :: ByteString -> E Settings
- defaultSettingsFilePath :: FilePath
- settingsFilePath :: String -> FilePath
- defaultKeyStoreFilePath :: FilePath
- defaultCtxParams :: CtxParams
- instanceCtx :: CtxParams -> IO IC
- instanceCtx_ :: CtxParams -> IC
- newKeyStore :: FilePath -> Settings -> IO ()
- store :: IC -> IO FilePath
- listSettings :: IC -> IO ()
- settings :: IC -> IO Settings
- updateSettings :: IC -> FilePath -> IO ()
- listTriggers :: IC -> IO ()
- triggers :: IC -> IO [Trigger]
- addTrigger :: IC -> TriggerID -> Pattern -> FilePath -> IO ()
- addTrigger' :: IC -> TriggerID -> Pattern -> Settings -> IO ()
- rmvTrigger :: IC -> TriggerID -> IO ()
- createRSAKeyPair :: IC -> Name -> Comment -> Identity -> [Safeguard] -> IO ()
- createKey :: IC -> Name -> Comment -> Identity -> Maybe EnvVar -> Maybe ByteString -> IO ()
- adjustKey :: IC -> Name -> (Key -> Key) -> IO ()
- rememberKey :: IC -> Name -> FilePath -> IO ()
- rememberKey_ :: IC -> Name -> ByteString -> IO ()
- secureKey :: IC -> Name -> Safeguard -> IO ()
- loadKey :: IC -> Name -> IO Key
- showIdentity :: IC -> Bool -> Name -> IO ByteString
- showComment :: IC -> Bool -> Name -> IO ByteString
- showDate :: IC -> Bool -> Name -> IO ByteString
- showHash :: IC -> Bool -> Name -> IO ByteString
- showHashComment :: IC -> Bool -> Name -> IO ByteString
- showHashSalt :: IC -> Bool -> Name -> IO ByteString
- showPublic :: IC -> Bool -> Name -> IO ByteString
- showSecret :: IC -> Bool -> Name -> IO ByteString
- keys :: IC -> IO [Key]
- list :: IC -> IO ()
- keyInfo :: IC -> Name -> IO ()
- deleteKeys :: IC -> [Name] -> IO ()
- encrypt :: IC -> Name -> FilePath -> FilePath -> IO ()
- encrypt_ :: IC -> Name -> ByteString -> IO ByteString
- encrypt__ :: IC -> Name -> ByteString -> IO RSASecretData
- decrypt :: IC -> FilePath -> FilePath -> IO ()
- decrypt_ :: IC -> ByteString -> IO ByteString
- decrypt__ :: IC -> Name -> RSASecretData -> IO ByteString
- sign :: IC -> Name -> FilePath -> FilePath -> IO ()
- sign_ :: IC -> Name -> ByteString -> IO ByteString
- verify :: IC -> FilePath -> FilePath -> IO Bool
- verify_ :: IC -> ByteString -> ByteString -> IO Bool
- run :: IC -> KS a -> IO a
- getKeystore :: IC -> IO KeyStore
- getState :: IC -> IO State
- getCtxState :: IC -> IO (Ctx, State)
- putCtxState :: IC -> Ctx -> State -> IO ()
Documentation
readSettings :: FilePath -> IO Settings Source #
Read the JSON-encoded KeyStore settings from the named file.
The parameters used to set up a KeyStore session.
module Data.KeyStore.Types
module Data.KeyStore.KS.KS
keyStoreBytes :: KeyStore -> ByteString Source #
Encode a key store as a JSON ByteString (discarding any cached cleartext copies of secrets it may have)
keyStoreFromBytes :: ByteString -> E KeyStore Source #
settingsFromBytes :: ByteString -> E Settings Source #
defaultSettingsFilePath :: FilePath Source #
The default place for keystore settings (settings).
settingsFilePath :: String -> FilePath Source #
Add the standard file extension to a base name (.json).
defaultKeyStoreFilePath :: FilePath Source #
The default file for a keystore (keystore.json).
defaultCtxParams :: CtxParams Source #
Suitable default CtxParams
.
instanceCtx :: CtxParams -> IO IC Source #
Given CtxParams
describing the location of the keystore, etc., generate
an IC for use in the following keystore access functions that will allow
context to be cached between calls to these access functions.
instanceCtx_ :: CtxParams -> IC Source #
This functional method will generate an IC that will not cache any state between calls.
newKeyStore :: FilePath -> Settings -> IO () Source #
Generate a new keystore located in the given file with the given global settings.
listSettings :: IC -> IO () Source #
List the JSON settings on stdout.
updateSettings :: IC -> FilePath -> IO () Source #
Update the global settings of a keystore from the given JSON settings.
listTriggers :: IC -> IO () Source #
List the triggers set up in the keystore on stdout.
addTrigger :: IC -> TriggerID -> Pattern -> FilePath -> IO () Source #
addTrigger' cariant that erads the setting from a file.
addTrigger' :: IC -> TriggerID -> Pattern -> Settings -> IO () Source #
Set up a named trigger on a keystore that will fire when a key matches the given pattern establishing the settings.
createRSAKeyPair :: IC -> Name -> Comment -> Identity -> [Safeguard] -> IO () Source #
Create an RSA key pair, encoding the private key in the named Safeguards.
createKey :: IC -> Name -> Comment -> Identity -> Maybe EnvVar -> Maybe ByteString -> IO () Source #
Create a symmetric key, possibly auto-loaded from an environment variable.
rememberKey_ :: IC -> Name -> ByteString -> IO () Source #
Load the named key.
secureKey :: IC -> Name -> Safeguard -> IO () Source #
Encrypt and store the key with the named safeguard.
showIdentity :: IC -> Bool -> Name -> IO ByteString Source #
Return the identity of a key.
showComment :: IC -> Bool -> Name -> IO ByteString Source #
Return the comment associated with a key.
showHashComment :: IC -> Bool -> Name -> IO ByteString Source #
Return the hash comment of a key/
showHashSalt :: IC -> Bool -> Name -> IO ByteString Source #
Retuen the hash salt of a key.
showPublic :: IC -> Bool -> Name -> IO ByteString Source #
(For public key pairs only) return the public key.
showSecret :: IC -> Bool -> Name -> IO ByteString Source #
Return the secret text of a key (will be the private key for a public key pair).
encrypt_ :: IC -> Name -> ByteString -> IO ByteString Source #
Encrypt a ByteString
with a named key.
encrypt__ :: IC -> Name -> ByteString -> IO RSASecretData Source #
Encrypt a ByteString
with a named key to produce a RSASecretData
.
decrypt :: IC -> FilePath -> FilePath -> IO () Source #
Decrypt a file with the named key (whose secret text must be accessible).
decrypt_ :: IC -> ByteString -> IO ByteString Source #
Decrypt a ByteString
with the named key
(whose secret text must be accessible).
decrypt__ :: IC -> Name -> RSASecretData -> IO ByteString Source #
Decrypt a ByteString
from a RSASecretData
with the named key
(whose secret text must be accessible).
sign :: IC -> Name -> FilePath -> FilePath -> IO () Source #
Sign a file with the named key (whose secret text must be accessible) to produce a detached signature in the named file.
sign_ :: IC -> Name -> ByteString -> IO ByteString Source #
Sign a ByteString
with the named key (whose secret text must be accessible)
to produce a detached signature.
verify :: IC -> FilePath -> FilePath -> IO Bool Source #
Verify that a signature for a file via the named public key.
verify_ :: IC -> ByteString -> ByteString -> IO Bool Source #
Verify that a signature for a ByteString
via the named public key.