| License | BSD-style | 
|---|---|
| Maintainer | Olivier Chéron <olivier.cheron@gmail.com> | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Crypto.Store.PKCS8
Description
Private-Key Information Syntax, aka PKCS #8.
Presents an API similar to Data.X509.Memory and Data.X509.File but allows to write private keys and provides support for password-based encryption.
Functions to read a private key return an object wrapped in the
 OptProtected data type.
Functions related to public keys, certificates and CRLs are available from Crypto.Store.X509.
Synopsis
- readKeyFile :: FilePath -> IO [OptProtected PrivKey]
- readKeyFileFromMemory :: ByteString -> [OptProtected PrivKey]
- pemToKey :: [Maybe (OptProtected PrivKey)] -> PEM -> [Maybe (OptProtected PrivKey)]
- writeKeyFile :: PrivateKeyFormat -> FilePath -> [PrivKey] -> IO ()
- writeKeyFileToMemory :: PrivateKeyFormat -> [PrivKey] -> ByteString
- keyToPEM :: PrivateKeyFormat -> PrivKey -> PEM
- writeEncryptedKeyFile :: FilePath -> EncryptionScheme -> Password -> PrivKey -> IO (Either StoreError ())
- writeEncryptedKeyFileToMemory :: EncryptionScheme -> Password -> PrivKey -> Either StoreError ByteString
- encryptKeyToPEM :: EncryptionScheme -> Password -> PrivKey -> Either StoreError PEM
- data PrivateKeyFormat
- data FormattedKey a = FormattedKey PrivateKeyFormat a
- type Password = ByteString
- data OptProtected a- = Unprotected a
- | Protected (Password -> Either StoreError a)
 
- recover :: Password -> OptProtected a -> Either StoreError a
- recoverA :: Applicative f => f Password -> OptProtected a -> f (Either StoreError a)
- readPEMs :: FilePath -> IO [PEM]
- writePEMs :: FilePath -> [PEM] -> IO ()
Documentation
readKeyFile :: FilePath -> IO [OptProtected PrivKey] Source #
Read private keys from a PEM file.
readKeyFileFromMemory :: ByteString -> [OptProtected PrivKey] Source #
Read private keys from a bytearray in PEM format.
pemToKey :: [Maybe (OptProtected PrivKey)] -> PEM -> [Maybe (OptProtected PrivKey)] Source #
Read a private key from a PEM element and add it to the accumulator list.
writeKeyFile :: PrivateKeyFormat -> FilePath -> [PrivKey] -> IO () Source #
Write unencrypted private keys to a PEM file.
writeKeyFileToMemory :: PrivateKeyFormat -> [PrivKey] -> ByteString Source #
Write unencrypted private keys to a bytearray in PEM format.
keyToPEM :: PrivateKeyFormat -> PrivKey -> PEM Source #
Generate an unencrypted PEM for a private key.
writeEncryptedKeyFile :: FilePath -> EncryptionScheme -> Password -> PrivKey -> IO (Either StoreError ()) Source #
Write a PKCS #8 encrypted private key to a PEM file.
If multiple keys need to be stored in the same file, use functions
 encryptKeyToPEM and writePEMs.
Fresh EncryptionScheme parameters should be generated for each key to
 encrypt.
writeEncryptedKeyFileToMemory :: EncryptionScheme -> Password -> PrivKey -> Either StoreError ByteString Source #
Write a PKCS #8 encrypted private key to a bytearray in PEM format.
If multiple keys need to be stored in the same bytearray, use functions
 encryptKeyToPEM and pemWriteBS or pemWriteLBS.
Fresh EncryptionScheme parameters should be generated for each key to
 encrypt.
encryptKeyToPEM :: EncryptionScheme -> Password -> PrivKey -> Either StoreError PEM Source #
Generate a PKCS #8 encrypted PEM for a private key.
Fresh EncryptionScheme parameters should be generated for each key to
 encrypt.
Serialization formats
data PrivateKeyFormat Source #
Private-key serialization format.
Encryption in traditional format is not supported currently.
Constructors
| TraditionalFormat | SSLeay compatible | 
| PKCS8Format | PKCS #8 | 
Instances
| Eq PrivateKeyFormat Source # | |
| Defined in Crypto.Store.PKCS8 Methods (==) :: PrivateKeyFormat -> PrivateKeyFormat -> Bool # (/=) :: PrivateKeyFormat -> PrivateKeyFormat -> Bool # | |
| Show PrivateKeyFormat Source # | |
| Defined in Crypto.Store.PKCS8 Methods showsPrec :: Int -> PrivateKeyFormat -> ShowS # show :: PrivateKeyFormat -> String # showList :: [PrivateKeyFormat] -> ShowS # | |
data FormattedKey a Source #
A key associated with format.  Allows to implement ASN1Object instances.
Constructors
| FormattedKey PrivateKeyFormat a | 
Instances
| Functor FormattedKey Source # | |
| Defined in Crypto.Store.PKCS8 Methods fmap :: (a -> b) -> FormattedKey a -> FormattedKey b # (<$) :: a -> FormattedKey b -> FormattedKey a # | |
| Eq a => Eq (FormattedKey a) Source # | |
| Defined in Crypto.Store.PKCS8 Methods (==) :: FormattedKey a -> FormattedKey a -> Bool # (/=) :: FormattedKey a -> FormattedKey a -> Bool # | |
| Show a => Show (FormattedKey a) Source # | |
| Defined in Crypto.Store.PKCS8 Methods showsPrec :: Int -> FormattedKey a -> ShowS # show :: FormattedKey a -> String # showList :: [FormattedKey a] -> ShowS # | |
| ASN1Object (FormattedKey KeyPair) Source # | |
| Defined in Crypto.Store.PKCS8 | |
| ASN1Object (FormattedKey PrivateKey) Source # | |
| Defined in Crypto.Store.PKCS8 Methods toASN1 :: FormattedKey PrivateKey -> ASN1S # fromASN1 :: [ASN1] -> Either String (FormattedKey PrivateKey, [ASN1]) # | |
| ASN1Object (FormattedKey PrivKeyEC) Source # | |
| Defined in Crypto.Store.PKCS8 | |
| ASN1Object (FormattedKey PrivKey) Source # | |
| Defined in Crypto.Store.PKCS8 | |
Password-based protection
type Password = ByteString Source #
A password stored as a sequence of UTF-8 bytes.
Some key-derivation functions add restrictions to what characters are supported.
data OptProtected a Source #
Data type for objects that are possibly protected with a password.
Constructors
| Unprotected a | Value is unprotected | 
| Protected (Password -> Either StoreError a) | Value is protected with a password | 
Instances
| Functor OptProtected Source # | |
| Defined in Crypto.Store.PKCS8 Methods fmap :: (a -> b) -> OptProtected a -> OptProtected b # (<$) :: a -> OptProtected b -> OptProtected a # | |
recover :: Password -> OptProtected a -> Either StoreError a Source #
Try to recover an OptProtected content using the specified password.
recoverA :: Applicative f => f Password -> OptProtected a -> f (Either StoreError a) Source #
Try to recover an OptProtected content in an applicative context.  The
 applicative password is used if necessary.
import qualified Data.ByteString as B
import           Crypto.Store.PKCS8
[encryptedKey] <- readKeyFile "privkey.pem"
let askForPassword = putStr "Please enter password: " >> B.getLine
result <- recoverA askForPassword encryptedKey
case result of
    Left err  -> putStrLn $ "Unable to recover key: " ++ show err
    Right key -> print key