-- |
-- Module      : Crypto.Store.CMS.PEM
-- License     : BSD-style
-- Maintainer  : Olivier Chéron <olivier.cheron@gmail.com>
-- Stability   : experimental
-- Portability : unknown
--
-- PEM serialization and deserialization of CMS 'ContentInfo'.
module Crypto.Store.CMS.PEM
    ( readCMSFile
    , readCMSFileFromMemory
    , berToContentInfo
    , pemToContentInfo
    , writeCMSFile
    , writeCMSFileToMemory
    , contentInfoToDER
    , contentInfoToPEM
    ) where

import qualified Data.ByteString as B
import           Data.Maybe (catMaybes)

import Crypto.Store.CMS.Info
import Crypto.Store.CMS.Util
import Crypto.Store.Error
import Crypto.Store.PEM


-- Reading from PEM format

-- | Read content info elements from a PEM file.
readCMSFile :: FilePath -> IO [ContentInfo]
readCMSFile :: FilePath -> IO [ContentInfo]
readCMSFile FilePath
path = [PEM] -> [ContentInfo]
accumulate ([PEM] -> [ContentInfo]) -> IO [PEM] -> IO [ContentInfo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO [PEM]
readPEMs FilePath
path

-- | Read content info elements from a bytearray in PEM format.
readCMSFileFromMemory :: B.ByteString -> [ContentInfo]
readCMSFileFromMemory :: ByteString -> [ContentInfo]
readCMSFileFromMemory = (FilePath -> [ContentInfo])
-> ([PEM] -> [ContentInfo])
-> Either FilePath [PEM]
-> [ContentInfo]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([ContentInfo] -> FilePath -> [ContentInfo]
forall a b. a -> b -> a
const []) [PEM] -> [ContentInfo]
accumulate (Either FilePath [PEM] -> [ContentInfo])
-> (ByteString -> Either FilePath [PEM])
-> ByteString
-> [ContentInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either FilePath [PEM]
pemParseBS

accumulate :: [PEM] -> [ContentInfo]
accumulate :: [PEM] -> [ContentInfo]
accumulate = [Maybe ContentInfo] -> [ContentInfo]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe ContentInfo] -> [ContentInfo])
-> ([PEM] -> [Maybe ContentInfo]) -> [PEM] -> [ContentInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PEM -> [Maybe ContentInfo] -> [Maybe ContentInfo])
-> [Maybe ContentInfo] -> [PEM] -> [Maybe ContentInfo]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (([Maybe ContentInfo] -> PEM -> [Maybe ContentInfo])
-> PEM -> [Maybe ContentInfo] -> [Maybe ContentInfo]
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Maybe ContentInfo] -> PEM -> [Maybe ContentInfo]
pemToContentInfo) []

-- | Read a content info from a bytearray in BER format.
berToContentInfo :: B.ByteString -> Either StoreError ContentInfo
berToContentInfo :: ByteString -> Either StoreError ContentInfo
berToContentInfo = ByteString -> Either StoreError ContentInfo
forall obj.
ParseASN1Object [ASN1Event] obj =>
ByteString -> Either StoreError obj
decodeASN1Object

-- | Read a content info from a 'PEM' element and add it to the accumulator
-- list.
pemToContentInfo :: [Maybe ContentInfo] -> PEM -> [Maybe ContentInfo]
pemToContentInfo :: [Maybe ContentInfo] -> PEM -> [Maybe ContentInfo]
pemToContentInfo [Maybe ContentInfo]
acc PEM
pem
    | PEM -> FilePath
pemName PEM
pem FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath]
names = ByteString -> [Maybe ContentInfo]
decode (PEM -> ByteString
pemContent PEM
pem)
    | Bool
otherwise                = Maybe ContentInfo
forall a. Maybe a
Nothing Maybe ContentInfo -> [Maybe ContentInfo] -> [Maybe ContentInfo]
forall a. a -> [a] -> [a]
: [Maybe ContentInfo]
acc
  where
    names :: [FilePath]
names = [ FilePath
"CMS", FilePath
"PKCS7" ]
    decode :: ByteString -> [Maybe ContentInfo]
decode ByteString
bs =
        case ByteString -> Either StoreError ContentInfo
berToContentInfo ByteString
bs of
            Left StoreError
_ -> Maybe ContentInfo
forall a. Maybe a
Nothing Maybe ContentInfo -> [Maybe ContentInfo] -> [Maybe ContentInfo]
forall a. a -> [a] -> [a]
: [Maybe ContentInfo]
acc
            Right ContentInfo
info -> ContentInfo -> Maybe ContentInfo
forall a. a -> Maybe a
Just ContentInfo
info Maybe ContentInfo -> [Maybe ContentInfo] -> [Maybe ContentInfo]
forall a. a -> [a] -> [a]
: [Maybe ContentInfo]
acc


-- Writing to PEM format

-- | Write content info elements to a PEM file.
writeCMSFile :: FilePath -> [ContentInfo] -> IO ()
writeCMSFile :: FilePath -> [ContentInfo] -> IO ()
writeCMSFile FilePath
path = FilePath -> ByteString -> IO ()
B.writeFile FilePath
path (ByteString -> IO ())
-> ([ContentInfo] -> ByteString) -> [ContentInfo] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ContentInfo] -> ByteString
writeCMSFileToMemory

-- | Write content info elements to a bytearray in PEM format.
writeCMSFileToMemory :: [ContentInfo] -> B.ByteString
writeCMSFileToMemory :: [ContentInfo] -> ByteString
writeCMSFileToMemory = [PEM] -> ByteString
pemsWriteBS ([PEM] -> ByteString)
-> ([ContentInfo] -> [PEM]) -> [ContentInfo] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ContentInfo -> PEM) -> [ContentInfo] -> [PEM]
forall a b. (a -> b) -> [a] -> [b]
map ContentInfo -> PEM
contentInfoToPEM

-- | Generate a bytearray in DER format for a content info.
contentInfoToDER :: ContentInfo -> B.ByteString
contentInfoToDER :: ContentInfo -> ByteString
contentInfoToDER = ContentInfo -> ByteString
forall obj. ProduceASN1Object ASN1P obj => obj -> ByteString
encodeASN1Object

-- | Generate PEM for a content info.
contentInfoToPEM :: ContentInfo -> PEM
contentInfoToPEM :: ContentInfo -> PEM
contentInfoToPEM ContentInfo
info = PEM :: FilePath -> [(FilePath, ByteString)] -> ByteString -> PEM
PEM { pemName :: FilePath
pemName = FilePath
"CMS", pemHeader :: [(FilePath, ByteString)]
pemHeader = [], pemContent :: ByteString
pemContent = ByteString
bs}
  where bs :: ByteString
bs = ContentInfo -> ByteString
contentInfoToDER ContentInfo
info