summaryrefslogtreecommitdiff
path: root/src/Network/ACME/Encoding.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/ACME/Encoding.hs')
-rw-r--r--src/Network/ACME/Encoding.hs24
1 files changed, 5 insertions, 19 deletions
diff --git a/src/Network/ACME/Encoding.hs b/src/Network/ACME/Encoding.hs
index dc2c963..315ff49 100644
--- a/src/Network/ACME/Encoding.hs
+++ b/src/Network/ACME/Encoding.hs
@@ -3,8 +3,6 @@
3{-# LANGUAGE ScopedTypeVariables #-} 3{-# LANGUAGE ScopedTypeVariables #-}
4 4
5module Network.ACME.Encoding ( 5module Network.ACME.Encoding (
6 Keys(..),
7 readKeys,
8 thumbprint, 6 thumbprint,
9 JWK(..), 7 JWK(..),
10 toStrict, 8 toStrict,
@@ -12,7 +10,7 @@ module Network.ACME.Encoding (
12 challenge, 10 challenge,
13 registration, 11 registration,
14 authz, 12 authz,
15 signPayload, 13 signPayload',
16 ) where 14 ) where
17 15
18import Crypto.Number.Serialize (i2osp) 16import Crypto.Number.Serialize (i2osp)
@@ -27,29 +25,17 @@ import Data.Digest.Pure.SHA (bytestringDigest, sha256)
27import Data.Maybe 25import Data.Maybe
28import Data.Text.Encoding (decodeUtf8) 26import Data.Text.Encoding (decodeUtf8)
29import OpenSSL 27import OpenSSL
30import OpenSSL.EVP.Digest
31import OpenSSL.EVP.PKey
32import OpenSSL.EVP.Sign
33import OpenSSL.PEM
34import OpenSSL.RSA 28import OpenSSL.RSA
35import Text.Email.Validate 29import Text.Email.Validate
36import qualified Data.Text as T 30import qualified Data.Text as T
37 31
38data Keys = Keys RSAKeyPair RSAPubKey
39readKeys :: String -> IO (Maybe Keys)
40readKeys privKeyData = do
41 keypair :: SomeKeyPair <- readPrivateKey privKeyData PwTTY
42 let (priv :: Maybe RSAKeyPair) = toKeyPair keypair
43 pub <- maybe (return Nothing) (fmap Just . rsaCopyPublic) priv
44 return $ Keys <$> priv <*> pub
45
46-------------------------------------------------------------------------------- 32--------------------------------------------------------------------------------
47-- | Sign return a payload with a nonce-protected header. 33-- | Sign return a payload with a nonce-protected header.
48signPayload :: Keys -> String -> ByteString -> IO LC.ByteString 34
49signPayload (Keys priv pub) nonce_ payload = withOpenSSL $ do 35signPayload' :: (ByteString -> IO ByteString) -> RSAPubKey -> String -> ByteString -> IO LC.ByteString
36signPayload' sign pub nonce_ payload = withOpenSSL $ do
50 let protected = b64 (header pub nonce_) 37 let protected = b64 (header pub nonce_)
51 Just dig <- getDigestByName "SHA256" 38 sig <- b64 <$> sign (B.concat [protected, ".", payload])
52 sig <- b64 <$> signBS dig priv (B.concat [protected, ".", payload])
53 return $ encode (Request (header' pub) protected payload sig) 39 return $ encode (Request (header' pub) protected payload sig)
54 40
55-------------------------------------------------------------------------------- 41--------------------------------------------------------------------------------