Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Network.AWS.CloudFront.SignedCookies.Crypto
Synopsis
- readPrivateKeyPemFile :: PemFilePath -> IO PrivateKey
- sign :: PrivateKey -> ByteString -> IO ByteString
- data PrivateKey
- data ByteString
Reading the private key
readPrivateKeyPemFile Source #
Arguments
:: PemFilePath | The filesystem path of the |
-> IO PrivateKey |
Read an RSA private key from a .pem
file you downloaded from AWS.
Generating signatures
Arguments
:: PrivateKey | The RSA private key that you read from the |
-> ByteString | The JSON representation of the |
-> IO ByteString |
Construct the signature that will go into the
CloudFront-Signature
cookie.
Types
data PrivateKey #
Represent a RSA private key.
Only the pub, d fields are mandatory to fill.
p, q, dP, dQ, qinv are by-product during RSA generation, but are useful to record here to speed up massively the decrypt and sign operation.
implementations can leave optional fields to 0.
Instances
Data PrivateKey | |
Defined in Crypto.PubKey.RSA.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateKey -> c PrivateKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateKey # toConstr :: PrivateKey -> Constr # dataTypeOf :: PrivateKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrivateKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey) # gmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r # gmapQ :: (forall d. Data d => d -> u) -> PrivateKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey # | |
Read PrivateKey | |
Defined in Crypto.PubKey.RSA.Types Methods readsPrec :: Int -> ReadS PrivateKey # readList :: ReadS [PrivateKey] # readPrec :: ReadPrec PrivateKey # readListPrec :: ReadPrec [PrivateKey] # | |
Show PrivateKey | |
Defined in Crypto.PubKey.RSA.Types Methods showsPrec :: Int -> PrivateKey -> ShowS # show :: PrivateKey -> String # showList :: [PrivateKey] -> ShowS # | |
NFData PrivateKey | |
Defined in Crypto.PubKey.RSA.Types Methods rnf :: PrivateKey -> () # | |
Eq PrivateKey | |
Defined in Crypto.PubKey.RSA.Types |
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.