cryptostore-0.1.0.0: Serialization of cryptographic data types

LicenseBSD-style
MaintainerOlivier Chéron <olivier.cheron@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Crypto.Store.PKCS12

Contents

Description

Personal Information Exchange Syntax, aka PKCS #12.

Only password integrity mode and password privacy modes are supported.

Synopsis

Documentation

type IntegrityParams = (DigestAlgorithm, PBEParameter) Source #

Parameters used for password integrity mode.

readP12File :: FilePath -> IO (Either StoreError (OptProtected PKCS12)) Source #

Read a PKCS #12 file from disk.

readP12FileFromMemory :: ByteString -> Either StoreError (OptProtected PKCS12) Source #

Read a PKCS #12 file from a bytearray in BER format.

writeP12File :: FilePath -> IntegrityParams -> Password -> PKCS12 -> IO (Either StoreError ()) Source #

Write a PKCS #12 file to disk.

writeP12FileToMemory :: IntegrityParams -> Password -> PKCS12 -> Either StoreError ByteString Source #

Write a PKCS #12 file to a bytearray in DER format.

writeUnprotectedP12File :: FilePath -> PKCS12 -> IO () Source #

Write a PKCS #12 file without integrity protection to disk.

writeUnprotectedP12FileToMemory :: PKCS12 -> ByteString Source #

Write a PKCS #12 file without integrity protection to a bytearray in DER format.

PKCS #12 privacy

data PKCS12 Source #

PKCS #12 privacy wrapper, adding optional encryption to SafeContents. ASN.1 equivalent is AuthenticatedSafe.

The semigroup interface allows to combine multiple pieces encrypted separately but they should all derive from the same password to be readable by unPKCS12 and most other software.

Instances
Eq PKCS12 Source # 
Instance details

Defined in Crypto.Store.PKCS12

Methods

(==) :: PKCS12 -> PKCS12 -> Bool #

(/=) :: PKCS12 -> PKCS12 -> Bool #

Show PKCS12 Source # 
Instance details

Defined in Crypto.Store.PKCS12

Semigroup PKCS12 Source # 
Instance details

Defined in Crypto.Store.PKCS12

unPKCS12 :: PKCS12 -> OptProtected [SafeContents] Source #

Read the contents of a PKCS #12. The same privacy password will be used for all content elements.

This convenience function returns a Protected value as soon as one element at least is encrypted. This does not mean all elements were actually protected in the input. If detailed view is required then function unPKCS12' is also available.

unPKCS12' :: PKCS12 -> [OptProtected SafeContents] Source #

Read the contents of a PKCS #12.

unencrypted :: SafeContents -> PKCS12 Source #

Build a PKCS #12 without encryption. Usage scenario is when private keys are already encrypted with PKCS8ShroudedKeyBag.

encrypted :: EncryptionScheme -> Password -> SafeContents -> Either StoreError PKCS12 Source #

Build a PKCS #12 encrypted with the specified scheme and password.

PKCS #12 contents and bags

newtype SafeContents Source #

Content objects stored in a PKCS #12.

Constructors

SafeContents 

Fields

type SafeBag = Bag SafeInfo Source #

Main bag type in a PKCS #12.

data Bag info Source #

Polymorphic PKCS #12 bag parameterized by the payload data type.

Constructors

Bag 

Fields

Instances
Eq info => Eq (Bag info) Source # 
Instance details

Defined in Crypto.Store.PKCS12

Methods

(==) :: Bag info -> Bag info -> Bool #

(/=) :: Bag info -> Bag info -> Bool #

Show info => Show (Bag info) Source # 
Instance details

Defined in Crypto.Store.PKCS12

Methods

showsPrec :: Int -> Bag info -> ShowS #

show :: Bag info -> String #

showList :: [Bag info] -> ShowS #

data SafeInfo Source #

Main bag payload in PKCS #12 contents.

Constructors

KeyBag (FormattedKey PrivKey)

unencrypted private key

PKCS8ShroudedKeyBag PKCS5

encrypted private key

CertBag (Bag CertInfo)

certificate

CRLBag (Bag CRLInfo)

CRL

SecretBag [ASN1]

arbitrary secret

SafeContentsBag SafeContents

safe contents embeded recursively

Instances
Eq SafeInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

Show SafeInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

newtype CertInfo Source #

Certificate bags. Only X.509 certificates are supported.

Instances
Eq CertInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

Show CertInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

newtype CRLInfo Source #

CRL bags. Only X.509 CRLs are supported.

Constructors

CRLX509 SignedCRL 
Instances
Eq CRLInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

Methods

(==) :: CRLInfo -> CRLInfo -> Bool #

(/=) :: CRLInfo -> CRLInfo -> Bool #

Show CRLInfo Source # 
Instance details

Defined in Crypto.Store.PKCS12

data Attribute Source #

An attribute extending the parent structure with arbitrary data.

Constructors

Attribute 

Fields

Instances
Eq Attribute Source # 
Instance details

Defined in Crypto.Store.CMS.Attribute

Show Attribute Source # 
Instance details

Defined in Crypto.Store.CMS.Attribute

getSafeKeys :: SafeContents -> [OptProtected PrivKey] Source #

Return all private keys contained in the safe contents.

getAllSafeKeys :: [SafeContents] -> OptProtected [PrivKey] Source #

Return all private keys contained in the safe content list. All shrouded private keys must derive from the same password.

This convenience function returns a Protected value as soon as one key at least is encrypted. This does not mean all keys were actually protected in the input. If detailed view is required then function getSafeKeys is available.

getSafeX509Certs :: SafeContents -> [SignedCertificate] Source #

Return all X.509 certificates contained in the safe contents.

getAllSafeX509Certs :: [SafeContents] -> [SignedCertificate] Source #

Return all X.509 certificates contained in the safe content list.

getSafeX509CRLs :: SafeContents -> [SignedCRL] Source #

Return all X.509 CRLs contained in the safe contents.

getAllSafeX509CRLs :: [SafeContents] -> [SignedCRL] Source #

Return all X.509 CRLs contained in the safe content list.

PKCS #12 attributes

findAttribute :: OID -> [Attribute] -> Maybe [ASN1] Source #

Return the values for the first attribute with the specified type.

setAttribute :: OID -> [ASN1] -> [Attribute] -> [Attribute] Source #

Add or replace an attribute in a list of attributes.

filterAttributes :: (OID -> Bool) -> [Attribute] -> [Attribute] Source #

Filter a list of attributes based on a predicate applied to attribute type.

getFriendlyName :: [Attribute] -> Maybe String Source #

Return the value of the friendlyName attribute.

setFriendlyName :: String -> [Attribute] -> [Attribute] Source #

Add or replace the friendlyName attribute in a list of attributes.

getLocalKeyId :: [Attribute] -> Maybe ByteString Source #

Return the value of the localKeyId attribute.

setLocalKeyId :: ByteString -> [Attribute] -> [Attribute] Source #

Add or replace the localKeyId attribute in a list of attributes.

Credentials

fromCredential :: Maybe EncryptionScheme -> EncryptionScheme -> Password -> (CertificateChain, PrivKey) -> Either StoreError PKCS12 Source #

Build a PKCS12 value containing a private key and certificate chain. Distinct encryption is applied for both. Encrypting the certificate chain is optional.

Note: advice is to always generate fresh and independent EncryptionScheme values so that the salt is not reused twice in the encryption process.

toCredential :: PKCS12 -> OptProtected (Maybe (CertificateChain, PrivKey)) Source #

Extract the private key and certificate chain from a PKCS12 value. A credential is returned when the structure contains exactly one private key and at least one X.509 certificate.

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

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