diff options
-rw-r--r-- | KeyRing.hs | 151 | ||||
-rw-r--r-- | kiki.hs | 58 |
2 files changed, 114 insertions, 95 deletions
@@ -80,6 +80,10 @@ module KeyRing | |||
80 | , accBindings | 80 | , accBindings |
81 | , isSubkeySignature | 81 | , isSubkeySignature |
82 | , torhash | 82 | , torhash |
83 | , ParsedCert(..) | ||
84 | , parseCertBlob | ||
85 | , packetFromPublicRSAKey | ||
86 | , decodeBlob | ||
83 | ) where | 87 | ) where |
84 | 88 | ||
85 | import System.Environment | 89 | import System.Environment |
@@ -93,7 +97,7 @@ import Data.OpenPGP | |||
93 | import Data.Functor | 97 | import Data.Functor |
94 | import Data.Monoid | 98 | import Data.Monoid |
95 | import Data.Tuple ( swap ) | 99 | import Data.Tuple ( swap ) |
96 | import Data.Bits ( (.|.) ) | 100 | import Data.Bits ( (.|.), (.&.) ) |
97 | import Control.Applicative ( Applicative, pure, liftA2, (<*>) ) | 101 | import Control.Applicative ( Applicative, pure, liftA2, (<*>) ) |
98 | import System.Directory ( getHomeDirectory, doesFileExist, createDirectoryIfMissing ) | 102 | import System.Directory ( getHomeDirectory, doesFileExist, createDirectoryIfMissing ) |
99 | import Control.Arrow ( first, second ) | 103 | import Control.Arrow ( first, second ) |
@@ -107,17 +111,22 @@ import Data.ASN1.Types ( toASN1, ASN1Object, fromASN1 | |||
107 | import Data.ASN1.BitArray ( BitArray(..), toBitArray ) | 111 | import Data.ASN1.BitArray ( BitArray(..), toBitArray ) |
108 | import Data.ASN1.Encoding ( encodeASN1, encodeASN1', decodeASN1, decodeASN1' ) | 112 | import Data.ASN1.Encoding ( encodeASN1, encodeASN1', decodeASN1, decodeASN1' ) |
109 | import Data.ASN1.BinaryEncoding ( DER(..) ) | 113 | import Data.ASN1.BinaryEncoding ( DER(..) ) |
110 | import Data.Time.Clock.POSIX ( POSIXTime ) | 114 | import Data.Time.Clock.POSIX ( POSIXTime, utcTimeToPOSIXSeconds ) |
115 | import Data.Time.Clock ( UTCTime ) | ||
111 | import Data.Bits ( Bits ) | 116 | import Data.Bits ( Bits ) |
112 | import Data.Text.Encoding ( encodeUtf8 ) | 117 | import Data.Text.Encoding ( encodeUtf8 ) |
113 | import qualified Data.Map as Map | 118 | import qualified Data.Map as Map |
114 | import qualified Data.ByteString.Lazy as L ( unpack, null, readFile, writeFile | 119 | import qualified Data.ByteString.Lazy as L ( unpack, null, readFile, writeFile |
115 | , ByteString, toChunks, hGetContents, hPut, concat, fromChunks ) | 120 | , ByteString, toChunks, hGetContents, hPut, concat, fromChunks, splitAt |
116 | import qualified Data.ByteString as S ( ByteString, unpack, splitAt, concat, cons, spanEnd, hGetContents, readFile) | 121 | , index ) |
122 | import qualified Data.ByteString as S ( ByteString, unpack, splitAt, concat, cons, spanEnd, hGetContents, readFile, breakSubstring, drop, length, null ) | ||
117 | import qualified Crypto.Types.PubKey.ECC as ECC | 123 | import qualified Crypto.Types.PubKey.ECC as ECC |
118 | import qualified Codec.Binary.Base32 as Base32 | 124 | import qualified Codec.Binary.Base32 as Base32 |
119 | import qualified Codec.Binary.Base64 as Base64 | 125 | import qualified Codec.Binary.Base64 as Base64 |
120 | import qualified Crypto.Hash.SHA1 as SHA1 | 126 | import qualified Crypto.Hash.SHA1 as SHA1 |
127 | import qualified Data.X509 as X509 | ||
128 | import qualified Crypto.PubKey.RSA as RSA | ||
129 | import qualified Codec.Compression.GZip as GZip | ||
121 | import qualified Data.Text as T ( Text, unpack, pack, | 130 | import qualified Data.Text as T ( Text, unpack, pack, |
122 | strip, reverse, drop, break, dropAround, length ) | 131 | strip, reverse, drop, break, dropAround, length ) |
123 | import qualified System.Posix.Types as Posix | 132 | import qualified System.Posix.Types as Posix |
@@ -1378,7 +1387,74 @@ try x body = | |||
1378 | Left e -> return e | 1387 | Left e -> return e |
1379 | Right x -> body x | 1388 | Right x -> body x |
1380 | 1389 | ||
1381 | readKeyFromFile :: Bool -> String -> InputFile -> IO Message | 1390 | |
1391 | data ParsedCert = ParsedCert | ||
1392 | { pcertKey :: Packet | ||
1393 | , pcertTimestamp :: UTCTime | ||
1394 | , pcertBlob :: L.ByteString | ||
1395 | } | ||
1396 | deriving (Show,Eq) | ||
1397 | data SecretPEMData = PEMPacket Packet | PEMCertificate ParsedCert | ||
1398 | |||
1399 | spemPacket (PEMPacket p) = Just p | ||
1400 | spemPacket _ = Nothing | ||
1401 | |||
1402 | spemCert (PEMCertificate p) = Just p | ||
1403 | spemCert _ = Nothing | ||
1404 | |||
1405 | parseCertBlob comp bs = do | ||
1406 | asn1 <- either (const Nothing) Just | ||
1407 | $ decodeASN1 DER bs | ||
1408 | let asn1' = drop 2 asn1 | ||
1409 | cert <- either (const Nothing) (Just . fst) (fromASN1 asn1') | ||
1410 | let _ = cert :: X509.Certificate | ||
1411 | (notBefore,_) = X509.certValidity cert | ||
1412 | case X509.certPubKey cert of | ||
1413 | X509.PubKeyRSA key -> do | ||
1414 | let withoutkey = | ||
1415 | let ekey = Char8.toStrict $ encodeASN1 DER (toASN1 key []) | ||
1416 | (pre,post) = S.breakSubstring ekey $ Char8.toStrict bs | ||
1417 | post' = S.drop (S.length ekey) post | ||
1418 | len :: Word16 | ||
1419 | len = if S.null post then maxBound | ||
1420 | else fromIntegral $ S.length pre | ||
1421 | in if len < 4096 | ||
1422 | then encode len <> GZip.compress (Char8.fromChunks [pre,post']) | ||
1423 | else bs | ||
1424 | return | ||
1425 | ParsedCert { pcertKey = packetFromPublicRSAKey notBefore | ||
1426 | (MPI $ RSA.public_n key) | ||
1427 | (MPI $ RSA.public_e key) | ||
1428 | , pcertTimestamp = notBefore | ||
1429 | , pcertBlob = if comp then withoutkey | ||
1430 | else bs | ||
1431 | } | ||
1432 | _ -> Nothing | ||
1433 | |||
1434 | packetFromPublicRSAKey notBefore n e = | ||
1435 | PublicKeyPacket { version = 4 | ||
1436 | , timestamp = round $ utcTimeToPOSIXSeconds notBefore | ||
1437 | , key_algorithm = RSA | ||
1438 | , key = [('n',n),('e',e)] | ||
1439 | , is_subkey = True | ||
1440 | , v3_days_of_validity = Nothing | ||
1441 | } | ||
1442 | |||
1443 | decodeBlob cert = | ||
1444 | if 0 /= (bs `L.index` 0) .&. 0x10 | ||
1445 | then bs | ||
1446 | else let (keypos0,bs') = L.splitAt 2 bs | ||
1447 | keypos :: Word16 | ||
1448 | keypos = decode keypos0 | ||
1449 | ds = GZip.decompress bs' | ||
1450 | (prekey,postkey) = L.splitAt (fromIntegral keypos) ds | ||
1451 | in prekey <> key <> postkey | ||
1452 | where | ||
1453 | bs = pcertBlob cert | ||
1454 | key = maybe "" (encodeASN1 DER . flip toASN1 []) $ rsaKeyFromPacket $ pcertKey cert | ||
1455 | |||
1456 | |||
1457 | readKeyFromFile :: Bool -> String -> InputFile -> IO [SecretPEMData] | ||
1382 | readKeyFromFile False "PEM" fname = do | 1458 | readKeyFromFile False "PEM" fname = do |
1383 | -- warn $ fname ++ ": reading ..." | 1459 | -- warn $ fname ++ ": reading ..." |
1384 | let ctx = InputFileContext "" "" | 1460 | let ctx = InputFileContext "" "" |
@@ -1386,37 +1462,37 @@ readKeyFromFile False "PEM" fname = do | |||
1386 | -- Therefore, we should attempt to preserve it. | 1462 | -- Therefore, we should attempt to preserve it. |
1387 | timestamp <- getInputFileTime ctx fname | 1463 | timestamp <- getInputFileTime ctx fname |
1388 | input <- readInputFileL ctx fname | 1464 | input <- readInputFileL ctx fname |
1389 | let dta = fmap pemBlob $ listToMaybe $ scanAndParse (pemParser $ Just "RSA PRIVATE KEY") $ Char8.lines input | 1465 | let dta = catMaybes $ scanAndParse pkcs1 $ Char8.lines input |
1390 | -- Char8.putStrLn $ "dta = " <> dta | 1466 | pkcs1 = fmap (parseRSAPrivateKey . pemBlob) |
1391 | let rsa = do | 1467 | $ pemParser $ Just "RSA PRIVATE KEY" |
1392 | e <- decodeASN1 DER <$> dta | 1468 | cert = fmap (fmap (PEMPacket . pcertKey) . parseCertBlob False . pemBlob) |
1393 | asn1 <- either (const Nothing) Just e | 1469 | $ pemParser $ Just "CERTIFICATE" |
1394 | k <- either (const Nothing) (Just . fst) (fromASN1 asn1) | 1470 | parseRSAPrivateKey dta = do |
1395 | let _ = k :: RSAPrivateKey | 1471 | let e = decodeASN1 DER dta |
1396 | return k | 1472 | asn1 <- either (const $ mzero) return e |
1397 | -- putStrLn $ "rsa = "++ show rsa | 1473 | rsa <- either (const mzero) (return . fst) (fromASN1 asn1) |
1398 | return . Message $ do | 1474 | let _ = rsa :: RSAPrivateKey |
1399 | rsa <- maybeToList rsa | 1475 | return $ PEMPacket $ SecretKeyPacket |
1400 | return $ SecretKeyPacket | 1476 | { version = 4 |
1401 | { version = 4 | 1477 | , timestamp = toEnum (fromEnum timestamp) |
1402 | , timestamp = toEnum (fromEnum timestamp) | 1478 | , key_algorithm = RSA |
1403 | , key_algorithm = RSA | 1479 | , key = [ -- public fields... |
1404 | , key = [ -- public fields... | 1480 | ('n',rsaN rsa) |
1405 | ('n',rsaN rsa) | 1481 | ,('e',rsaE rsa) |
1406 | ,('e',rsaE rsa) | 1482 | -- secret fields |
1407 | -- secret fields | 1483 | ,('d',rsaD rsa) |
1408 | ,('d',rsaD rsa) | 1484 | ,('p',rsaQ rsa) -- Note: p & q swapped |
1409 | ,('p',rsaQ rsa) -- Note: p & q swapped | 1485 | ,('q',rsaP rsa) -- Note: p & q swapped |
1410 | ,('q',rsaP rsa) -- Note: p & q swapped | 1486 | ,('u',rsaCoefficient rsa) |
1411 | ,('u',rsaCoefficient rsa) | 1487 | ] |
1412 | ] | 1488 | -- , ecc_curve = def |
1413 | -- , ecc_curve = def | 1489 | , s2k_useage = 0 |
1414 | , s2k_useage = 0 | 1490 | , s2k = S2K 100 "" |
1415 | , s2k = S2K 100 "" | 1491 | , symmetric_algorithm = Unencrypted |
1416 | , symmetric_algorithm = Unencrypted | 1492 | , encrypted_data = "" |
1417 | , encrypted_data = "" | 1493 | , is_subkey = True |
1418 | , is_subkey = True | 1494 | } |
1419 | } | 1495 | return dta |
1420 | readKeyFromFile is_public fmt filename = error ("unimplemented key type: "++fmt) | 1496 | readKeyFromFile is_public fmt filename = error ("unimplemented key type: "++fmt) |
1421 | 1497 | ||
1422 | doImport | 1498 | doImport |
@@ -1429,7 +1505,8 @@ doImport doDecrypt db (fname,subspec,ms,_) = do | |||
1429 | let fetchkey = readKeyFromFile False "PEM" (ArgFile fname) | 1505 | let fetchkey = readKeyFromFile False "PEM" (ArgFile fname) |
1430 | flip (maybe $ return CannotImportMasterKey) | 1506 | flip (maybe $ return CannotImportMasterKey) |
1431 | subspec $ \tag -> do | 1507 | subspec $ \tag -> do |
1432 | Message parsedkey <- fetchkey | 1508 | ps <- fetchkey |
1509 | let parsedkey = mapMaybe spemPacket ps | ||
1433 | flip (maybe $ return $ KikiSuccess (db,[])) | 1510 | flip (maybe $ return $ KikiSuccess (db,[])) |
1434 | (listToMaybe parsedkey) $ \key -> do | 1511 | (listToMaybe parsedkey) $ \key -> do |
1435 | let (m0,tailms) = splitAt 1 ms | 1512 | let (m0,tailms) = splitAt 1 ms |
@@ -325,64 +325,6 @@ show_wip keyspec wkgrip db = do | |||
325 | let nwb = maybe 0x80 CryptoCoins.secretByteFromName $ snd s | 325 | let nwb = maybe 0x80 CryptoCoins.secretByteFromName $ snd s |
326 | putStrLn $ walletImportFormat nwb k | 326 | putStrLn $ walletImportFormat nwb k |
327 | 327 | ||
328 | packetFromPublicRSAKey notBefore n e = | ||
329 | PublicKeyPacket { version = 4 | ||
330 | , timestamp = round $ utcTimeToPOSIXSeconds notBefore | ||
331 | , key_algorithm = RSA | ||
332 | , key = [('n',n),('e',e)] | ||
333 | , is_subkey = True | ||
334 | , v3_days_of_validity = Nothing | ||
335 | } | ||
336 | |||
337 | data ParsedCert = ParsedCert | ||
338 | { pcertKey :: Packet | ||
339 | , pcertTimestamp :: UTCTime | ||
340 | , pcertBlob :: L.ByteString | ||
341 | } | ||
342 | deriving (Show,Eq) | ||
343 | |||
344 | parseCertBlob comp bs = do | ||
345 | asn1 <- either (const Nothing) Just | ||
346 | $ decodeASN1 DER bs | ||
347 | let asn1' = drop 2 asn1 | ||
348 | cert <- either (const Nothing) (Just . fst) (fromASN1 asn1') | ||
349 | let _ = cert :: Certificate | ||
350 | (notBefore,_) = certValidity cert | ||
351 | case certPubKey cert of | ||
352 | PubKeyRSA key -> do | ||
353 | let withoutkey = | ||
354 | let ekey = Char8.toStrict $ encodeASN1 DER (toASN1 key []) | ||
355 | (pre,post) = S.breakSubstring ekey $ Char8.toStrict bs | ||
356 | post' = S.drop (S.length ekey) post | ||
357 | len :: Word16 | ||
358 | len = if S.null post then maxBound | ||
359 | else fromIntegral $ S.length pre | ||
360 | in if len < 4096 | ||
361 | then encode len `L.append` GZip.compress (Char8.fromChunks [pre,post']) | ||
362 | else bs | ||
363 | return | ||
364 | ParsedCert { pcertKey = packetFromPublicRSAKey notBefore | ||
365 | (MPI $ public_n key) | ||
366 | (MPI $ public_e key) | ||
367 | , pcertTimestamp = notBefore | ||
368 | , pcertBlob = if comp then withoutkey | ||
369 | else bs | ||
370 | } | ||
371 | _ -> Nothing | ||
372 | |||
373 | decodeBlob cert = | ||
374 | if 0 /= (bs `L.index` 0) .&. 0x10 | ||
375 | then bs | ||
376 | else let (keypos0,bs') = L.splitAt 2 bs | ||
377 | keypos :: Word16 | ||
378 | keypos = decode keypos0 | ||
379 | ds = GZip.decompress bs' | ||
380 | (prekey,postkey) = L.splitAt (fromIntegral keypos) ds | ||
381 | in prekey <> key <> postkey | ||
382 | where | ||
383 | bs = pcertBlob cert | ||
384 | key = maybe L.empty (encodeASN1 DER . flip toASN1 []) $ rsaKeyFromPacket $ pcertKey cert | ||
385 | |||
386 | show_torhash pubkey _ = do | 328 | show_torhash pubkey _ = do |
387 | bs <- Char8.readFile pubkey | 329 | bs <- Char8.readFile pubkey |
388 | let parsekey f dta = do | 330 | let parsekey f dta = do |