summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2013-12-13 04:03:01 -0500
committerjoe <joe@jerkface.net>2013-12-13 13:03:07 -0500
commitf493a48b45af08686186fa36ba96152175f7f3e8 (patch)
tree43041b5e63c67c89402ec290324d0106b2a7f917
parent30953649e78c1d051f8d5bc18ad25a3474baecb1 (diff)
Adapted to IO-based inteface pgpSign to reduce dependency on
random number generator interface. Conflicts: kiki.hs
-rw-r--r--kiki.hs187
1 files changed, 100 insertions, 87 deletions
diff --git a/kiki.hs b/kiki.hs
index baa187f..3dc0edd 100644
--- a/kiki.hs
+++ b/kiki.hs
@@ -23,8 +23,8 @@ import Control.Monad
23import qualified Text.Show.Pretty as PP 23import qualified Text.Show.Pretty as PP
24import Text.PrettyPrint as PP hiding ((<>)) 24import Text.PrettyPrint as PP hiding ((<>))
25import Data.List 25import Data.List
26import Data.OpenPGP.CryptoAPI hiding (sign) 26-- import Data.OpenPGP.CryptoAPI (verify,fingerprint,sign,decryptSecretKey)
27import qualified Data.OpenPGP.CryptoAPI as Stephen (sign) 27import OpenPGP
28import Data.Ord 28import Data.Ord
29import Data.Maybe 29import Data.Maybe
30import Data.Bits 30import Data.Bits
@@ -41,7 +41,7 @@ import qualified Crypto.Types.PubKey.ECC as ECC
41 41
42import Data.Char (toLower) 42import Data.Char (toLower)
43import qualified Crypto.PubKey.RSA as RSA 43import qualified Crypto.PubKey.RSA as RSA
44import Crypto.Random (newGenIO,SystemRandom) 44-- import Crypto.Random (newGenIO,SystemRandom)
45import Data.ASN1.Types 45import Data.ASN1.Types
46import Data.ASN1.Encoding 46import Data.ASN1.Encoding
47import Data.ASN1.BinaryEncoding 47import Data.ASN1.BinaryEncoding
@@ -63,7 +63,8 @@ import System.IO.Error
63import ControlMaybe 63import ControlMaybe
64import Data.Char 64import Data.Char
65import Control.Arrow (first,second) 65import Control.Arrow (first,second)
66-- import Data.Traversable hiding (mapM,forM) 66import Data.Traversable hiding (mapM,forM,sequence)
67import qualified Data.Traversable as Traversable (mapM,forM,sequence)
67import System.Console.CmdArgs 68import System.Console.CmdArgs
68-- import System.Posix.Time 69-- import System.Posix.Time
69import Data.Time.Clock.POSIX 70import Data.Time.Clock.POSIX
@@ -80,6 +81,7 @@ instance Default S.ByteString where def = S.empty
80isBitCoinKey p = 81isBitCoinKey p =
81 isKey p && key_algorithm p == ECDSA && ecc_curve p == oidToDER secp256k1_oid 82 isKey p && key_algorithm p == ECDSA && ecc_curve p == oidToDER secp256k1_oid
82 83
84{-
83sign seckeys dta hashalgo keyid timestamp g = r 85sign seckeys dta hashalgo keyid timestamp g = r
84 where 86 where
85 Message ks = seckeys 87 Message ks = seckeys
@@ -88,6 +90,7 @@ sign seckeys dta hashalgo keyid timestamp g = r
88 [k] | isBitCoinKey k -> btc_sign (Message [k]) dta hashalgo keyid timestamp g 90 [k] | isBitCoinKey k -> btc_sign (Message [k]) dta hashalgo keyid timestamp g
89 [k] -> Stephen.sign (Message [k]) dta hashalgo keyid timestamp g 91 [k] -> Stephen.sign (Message [k]) dta hashalgo keyid timestamp g
90 ks -> error $ "cannot determine a key to sign with" 92 ks -> error $ "cannot determine a key to sign with"
93-}
91 94
92{- 95{-
93btc_sign :: (CryptoRandomGen g) => 96btc_sign :: (CryptoRandomGen g) =>
@@ -1662,11 +1665,14 @@ doImportG doDecrypt db m0 tag fname key = do
1662 flip (flip maybe $ const $ return uids) has_torid $ do 1665 flip (flip maybe $ const $ return uids) has_torid $ do
1663 wkun <- doDecrypt (packet top) 1666 wkun <- doDecrypt (packet top)
1664 flip (maybe $ error "Bad passphrase?") wkun $ \wkun -> do 1667 flip (maybe $ error "Bad passphrase?") wkun $ \wkun -> do
1665 g <- newGenIO :: IO SystemRandom
1666 timestamp <- now
1667 let keyflags = keyFlags wkun (map packet $ flattenAllUids fname True uids) 1668 let keyflags = keyFlags wkun (map packet $ flattenAllUids fname True uids)
1668 uid = UserIDPacket idstr 1669 uid = UserIDPacket idstr
1669 sig_ov = fst $ torsig g (packet top) wkun uid timestamp keyflags 1670 -- sig_ov = fst $ torsig g (packet top) wkun uid timestamp keyflags
1671 tor_ov = torSigOver (packet top) wkun uid keyflags
1672 sig_ov <- pgpSign (Message [wkun])
1673 tor_ov
1674 SHA1
1675 (fingerprint wkun)
1670 flip (maybe $ warn "Failed to make signature" >> return uids) 1676 flip (maybe $ warn "Failed to make signature" >> return uids)
1671 (listToMaybe $ signatures_over sig_ov) 1677 (listToMaybe $ signatures_over sig_ov)
1672 $ \sig -> do 1678 $ \sig -> do
@@ -1697,8 +1703,6 @@ makeSig doDecrypt top fname subkey_p tag mbsig = do
1697 let wk = packet top 1703 let wk = packet top
1698 wkun <- doDecrypt wk 1704 wkun <- doDecrypt wk
1699 flip (maybe $ error "Bad passphrase?") wkun $ \wkun -> do 1705 flip (maybe $ error "Bad passphrase?") wkun $ \wkun -> do
1700 g <- newGenIO :: IO SystemRandom
1701 timestamp <- now
1702 let grip = fingerprint wk 1706 let grip = fingerprint wk
1703 addOrigin new_sig = do 1707 addOrigin new_sig = do
1704 flip (maybe $ error "Failed to make signature.") 1708 flip (maybe $ error "Failed to make signature.")
@@ -1706,21 +1710,8 @@ makeSig doDecrypt top fname subkey_p tag mbsig = do
1706 $ \new_sig -> do 1710 $ \new_sig -> do
1707 let mp' = MappedPacket new_sig (Map.singleton fname (origin new_sig (-1))) 1711 let mp' = MappedPacket new_sig (Map.singleton fname (origin new_sig (-1)))
1708 return (mp', Map.empty) 1712 return (mp', Map.empty)
1709 newSig = do 1713 parsedkey = [packet $ subkey_p]
1710 let parsedkey = [packet $ subkey_p] 1714 hashed0 =
1711 new_sig = fst $ sign (Message [wkun])
1712 (SubkeySignature wk
1713 (head parsedkey)
1714 (sigpackets 0x18
1715 hashed0
1716 ( IssuerPacket (fingerprint wk)
1717 : map EmbeddedSignaturePacket (signatures_over back_sig))))
1718 SHA1
1719 grip
1720 timestamp
1721 (g::SystemRandom)
1722
1723 hashed0 =
1724 [ KeyFlagsPacket 1715 [ KeyFlagsPacket
1725 { certify_keys = False 1716 { certify_keys = False
1726 , sign_data = False 1717 , sign_data = False
@@ -1734,22 +1725,31 @@ makeSig doDecrypt top fname subkey_p tag mbsig = do
1734 , notation_name = "usage@" 1725 , notation_name = "usage@"
1735 , notation_value = tag 1726 , notation_value = tag
1736 } 1727 }
1737 , SignatureCreationTimePacket (fromIntegral timestamp) 1728 -- implicitly added:
1729 -- , SignatureCreationTimePacket (fromIntegral timestamp)
1738 ] 1730 ]
1739 1731 subgrip = fingerprint (head parsedkey)
1740 subgrip = fingerprint (head parsedkey) 1732
1741 1733 back_sig <- pgpSign (Message parsedkey)
1742 back_sig = fst $ sign (Message parsedkey) 1734 (SubkeySignature wk
1743 (SubkeySignature wk 1735 (head parsedkey)
1744 (head parsedkey) 1736 (sigpackets 0x19
1745 (sigpackets 0x19 1737 hashed0
1746 hashed0 1738 [IssuerPacket subgrip]))
1747 [IssuerPacket subgrip])) 1739 SHA1
1748 SHA1 1740 subgrip
1749 subgrip 1741 let unhashed0 = ( IssuerPacket (fingerprint wk)
1750 timestamp 1742 : map EmbeddedSignaturePacket (signatures_over back_sig))
1751 (g::SystemRandom) 1743
1752 addOrigin new_sig 1744 new_sig <- pgpSign (Message [wkun])
1745 (SubkeySignature wk
1746 (head parsedkey)
1747 (sigpackets 0x18
1748 hashed0
1749 unhashed0))
1750 SHA1
1751 grip
1752 let newSig = addOrigin new_sig
1753 flip (maybe newSig) mbsig $ \(mp,trustmap) -> do 1753 flip (maybe newSig) mbsig $ \(mp,trustmap) -> do
1754 let sig = packet mp 1754 let sig = packet mp
1755 isCreation (SignatureCreationTimePacket {}) = True 1755 isCreation (SignatureCreationTimePacket {}) = True
@@ -1763,19 +1763,12 @@ makeSig doDecrypt top fname subkey_p tag mbsig = do
1763 exp = listToMaybe $ sort $ 1763 exp = listToMaybe $ sort $
1764 map unwrap es where unwrap (SignatureExpirationTimePacket x) = x 1764 map unwrap es where unwrap (SignatureExpirationTimePacket x) = x
1765 expires = liftA2 (+) stamp exp 1765 expires = liftA2 (+) stamp exp
1766 timestamp <- now
1766 if fmap ( (< timestamp) . fromIntegral) expires == Just True then do 1767 if fmap ( (< timestamp) . fromIntegral) expires == Just True then do
1767 warn $ "Unable to update expired signature" 1768 warn $ "Unable to update expired signature"
1768 return (mp,trustmap) 1769 return (mp,trustmap)
1769 else do 1770 else do
1770 let new_sig = fst $ sign (Message [wkun]) 1771 let times = (:) (SignatureExpirationTimePacket (fromIntegral timestamp))
1771 (SubkeySignature wk
1772 (packet subkey_p)
1773 [sig'] )
1774 SHA1
1775 (fingerprint wk)
1776 timestamp
1777 (g::SystemRandom)
1778 times = (:) (SignatureExpirationTimePacket (fromIntegral timestamp))
1779 $ maybeToList $ do 1772 $ maybeToList $ do
1780 e <- expires 1773 e <- expires
1781 return $ SignatureExpirationTimePacket (e - fromIntegral timestamp) 1774 return $ SignatureExpirationTimePacket (e - fromIntegral timestamp)
@@ -1784,6 +1777,12 @@ makeSig doDecrypt top fname subkey_p tag mbsig = do
1784 , notation_value = tag 1777 , notation_value = tag
1785 , human_readable = True } 1778 , human_readable = True }
1786 sig' = sig { hashed_subpackets = times ++ [notation] ++ qs } 1779 sig' = sig { hashed_subpackets = times ++ [notation] ++ qs }
1780 new_sig <- pgpSign (Message [wkun])
1781 (SubkeySignature wk
1782 (packet subkey_p)
1783 [sig'] )
1784 SHA1
1785 (fingerprint wk)
1787 addOrigin new_sig 1786 addOrigin new_sig
1788 1787
1789signature_time ov = case if null cs then ds else cs of 1788signature_time ov = case if null cs then ds else cs of
@@ -2049,12 +2048,13 @@ main = do
2049 return $ undata (snd elm) 2048 return $ undata (snd elm)
2050 2049
2051 undata (KeyData p _ _ _) = packet p 2050 undata (KeyData p _ _ _) = packet p
2052 g <- newGenIO 2051 -- g <- newGenIO
2053 stamp <- now 2052 -- stamp <- now
2054 wkun <- flip (maybe $ return Nothing) wk $ \wk -> do 2053 wkun <- flip (maybe $ return Nothing) wk $ \wk -> do
2055 wkun <- decrypt wk 2054 wkun <- decrypt wk
2056 maybe (error $ "Bad passphrase?") (return . Just) wkun 2055 maybe (error $ "Bad passphrase?") (return . Just) wkun
2057 return . snd $ Map.mapAccum (signTorIds stamp wkun keys) g use_db 2056 -- return . snd $ Map.mapAccum (signTorIds stamp wkun keys) g use_db
2057 Traversable.mapM (signTorIds wkun keys) use_db
2058 ret_db <- return $ fmap (const use_db) ret_db 2058 ret_db <- return $ fmap (const use_db) ret_db
2059 2059
2060 flip (maybe $ return ()) ret_db . const $ do 2060 flip (maybe $ return ()) ret_db . const $ do
@@ -2138,28 +2138,25 @@ main = do
2138 where 2138 where
2139 w0:ws = pub 2139 w0:ws = pub
2140 2140
2141 signTorIds timestamp selfkey keys 2141 signTorIds selfkey keys kd@(KeyData k ksigs umap submap) = do
2142 g kd@(KeyData k ksigs umap submap) = (g', KeyData k ksigs umap' submap) 2142 umap' <- Traversable.mapM signIfTor (Map.mapWithKey (,) umap)
2143 return (KeyData k ksigs umap' submap) :: IO KeyData
2143 where 2144 where
2144 _ = g :: SystemRandom
2145 mkey = packet k 2145 mkey = packet k
2146 (g',umap') = Map.mapAccumWithKey signIfTor g umap 2146 signIfTor (str,ps) =
2147 signIfTor g str ps = if isTorID str then {- trace (unlines 2147 if isTorID str
2148 [ "Found tor id: " 2148 then do
2149 ++show (str,fmap fingerprint selfkey) 2149 let uidxs0 = map packet $ flattenUid "" True (str,ps)
2150 , "additional = " ++ intercalate "," (map showPacket additional) 2150 -- addition<- signSelfAuthTorKeys' selfkey g keys grip timestamp mkey uidxs0
2151 ]) -} 2151 additional <- signSelfAuthTorKeys' selfkey keys grip mkey uidxs0
2152 (g',ps') 2152 let ps' = ( map ( (,tmap) . flip MappedPacket om) additional
2153 else (g,ps) 2153 ++ fst ps
2154 where 2154 , Map.union om (snd ps) )
2155 uidxs0 = map packet $ flattenUid "" True (str,ps) 2155 om = Map.singleton "--autosign" (origin p (-1)) where p = UserIDPacket str
2156 om = Map.singleton "--autosign" (origin p (-1)) where p = UserIDPacket str 2156 tmap = Map.empty
2157 tmap = Map.empty 2157 return ps'
2158 ps' = ( map ( (,tmap) . flip MappedPacket om) additional 2158 else return ps
2159 ++ fst ps 2159
2160 , Map.union om (snd ps) )
2161
2162 (uidxs, additional, xs'',g') = signSelfAuthTorKeys' selfkey g keys grip timestamp mkey uidxs0
2163 torbindings = getTorKeys (map packet $ flattenTop "" True kd) 2160 torbindings = getTorKeys (map packet $ flattenTop "" True kd)
2164 isTorID str = and [ uid_topdomain parsed == "onion" 2161 isTorID str = and [ uid_topdomain parsed == "onion"
2165 , uid_realname parsed `elem` ["","Anonymous"] 2162 , uid_realname parsed `elem` ["","Anonymous"]
@@ -2172,6 +2169,7 @@ main = do
2172 subdom = Char8.unpack subdom0 2169 subdom = Char8.unpack subdom0
2173 len = T.length (uid_subdomain parsed) 2170 len = T.length (uid_subdomain parsed)
2174 2171
2172 {-
2175 signSelfAuthTorKeys selfkey g sec grip timestamp xs = ys 2173 signSelfAuthTorKeys selfkey g sec grip timestamp xs = ys
2176 where 2174 where
2177 keys = filter isKey sec 2175 keys = filter isKey sec
@@ -2179,8 +2177,16 @@ main = do
2179 uidxs0 = map snd xs 2177 uidxs0 = map snd xs
2180 (uidxs, additional, xs'',g') = signSelfAuthTorKeys' selfkey g keys grip timestamp mainpubkey uidxs0 2178 (uidxs, additional, xs'',g') = signSelfAuthTorKeys' selfkey g keys grip timestamp mainpubkey uidxs0
2181 ys = uidxs++ additional++xs'' 2179 ys = uidxs++ additional++xs''
2180 -}
2182 2181
2183 signSelfAuthTorKeys' selfkey g keys grip timestamp mainpubkey (uid:xs') = (uid:sigs,additional,xs'',g') 2182 signSelfAuthTorKeys' selfkey keys grip mainpubkey (uid:xs') = do
2183 new_sig <- let wkun = fromJust selfkey
2184 tor_ov = torSigOver mainpubkey wkun uid flgs
2185 in pgpSign (Message [wkun])
2186 tor_ov
2187 SHA1
2188 (fingerprint wkun)
2189 return (additional new_sig) -- (uid:sigs,additional,xs'',g')
2184 where 2190 where
2185 (sigs, xs'') = span isSignaturePacket xs' 2191 (sigs, xs'') = span isSignaturePacket xs'
2186 overs sig = signatures $ Message (keys++[mainpubkey,uid,sig]) 2192 overs sig = signatures $ Message (keys++[mainpubkey,uid,sig])
@@ -2205,7 +2211,7 @@ main = do
2205 . (== keykey whosign) 2211 . (== keykey whosign)
2206 . keykey)) 2212 . keykey))
2207 vs 2213 vs
2208 additional = do 2214 additional new_sig = do
2209 guard $ {- trace (unlines $ [ "selfsigs = "++show (map ((\(_,_,k)->fingerprint k)) selfsigs) 2215 guard $ {- trace (unlines $ [ "selfsigs = "++show (map ((\(_,_,k)->fingerprint k)) selfsigs)
2210 , " for mainkey = "++fingerprint mainpubkey] ) 2216 , " for mainkey = "++fingerprint mainpubkey] )
2211 -} 2217 -}
@@ -2236,7 +2242,14 @@ main = do
2236 flgs = if keykey mainpubkey == keykey (fromJust selfkey) 2242 flgs = if keykey mainpubkey == keykey (fromJust selfkey)
2237 then keyFlags0 mainpubkey (map (\(x,_,_)->x) selfsigs) 2243 then keyFlags0 mainpubkey (map (\(x,_,_)->x) selfsigs)
2238 else [] 2244 else []
2239 (new_sig,g') = torsig g mainpubkey (fromJust selfkey) uid timestamp flgs 2245 -- (new_sig,g') = todo g mainpubkey (fromJust selfkey) uid timestamp flgs
2246 {-
2247 new_sig <- let wkun = fromJust selfkey
2248 in pgpSign (Message [wkun])
2249 tor_ov
2250 SHA1
2251 (fingerprint wkun)
2252 -}
2240 2253
2241 -- ys = uid:sigs++ additional++xs'' 2254 -- ys = uid:sigs++ additional++xs''
2242 2255
@@ -2488,6 +2501,7 @@ isSameKey a b = sort (key apub) == sort (key bpub)
2488 apub = secretToPublic a 2501 apub = secretToPublic a
2489 bpub = secretToPublic b 2502 bpub = secretToPublic b
2490 2503
2504{-
2491existingKey (prepk,pks) remainder wkun wk parsedkey tag pre uids subkeys output_file grip = do 2505existingKey (prepk,pks) remainder wkun wk parsedkey tag pre uids subkeys output_file grip = do
2492 -- putStrLn "Key already present." 2506 -- putStrLn "Key already present."
2493 let pk:trail = pks 2507 let pk:trail = pks
@@ -2637,6 +2651,7 @@ newKey wkun wk parsedkey tag pre uids subkeys output_file grip = do
2637 -} 2651 -}
2638 2652
2639 return () 2653 return ()
2654-}
2640 2655
2641 2656
2642 2657
@@ -2731,27 +2746,25 @@ seek_key (KeyUidMatch pat) ps = if null bs
2731groupTops ps = groupBy (\_ b -> not (isTopKey b)) ps 2746groupTops ps = groupBy (\_ b -> not (isTopKey b)) ps
2732 2747
2733 2748
2749{-
2734makeTorUID g timestamp wkun keyflags topkey torkey = uid:signatures_over sig 2750makeTorUID g timestamp wkun keyflags topkey torkey = uid:signatures_over sig
2735 where 2751 where
2736 torhash sub = maybe "" id $ derToBase32 <$> derRSA sub 2752 torhash sub = maybe "" id $ derToBase32 <$> derRSA sub
2737 s = "Anonymous <root@" ++ take 16 (torhash torkey) ++ ".onion>" 2753 s = "Anonymous <root@" ++ take 16 (torhash torkey) ++ ".onion>"
2738 uid = UserIDPacket s 2754 uid = UserIDPacket s
2739 sig = fst $ torsig g topkey wkun uid timestamp keyflags 2755 sig = fst $ torsig g topkey wkun uid timestamp keyflags
2756-}
2740 2757
2741torsig g topk wkun uid timestamp extras 2758-- torsig g topk wkun uid timestamp extras = todo
2742 = sign (Message [wkun]) 2759torSigOver topk wkun uid extras
2743 (CertificationSignature (secretToPublic topk) 2760 = CertificationSignature (secretToPublic topk)
2744 uid 2761 uid
2745 (sigpackets 0x13 2762 (sigpackets 0x13
2746 subpackets 2763 subpackets
2747 subpackets_unh)) 2764 subpackets_unh)
2748 SHA1
2749 (fingerprint wkun) {- (fromJust wkgrip) -}
2750 timestamp
2751 g
2752 where 2765 where
2753 subpackets = [ SignatureCreationTimePacket (fromIntegral timestamp) ] 2766 subpackets = -- implicit: [ SignatureCreationTimePacket (fromIntegral timestamp) ]
2754 ++ tsign 2767 tsign
2755 ++ extras 2768 ++ extras
2756 subpackets_unh = [IssuerPacket (fingerprint wkun)] 2769 subpackets_unh = [IssuerPacket (fingerprint wkun)]
2757 tsign = if keykey wkun == keykey topk 2770 tsign = if keykey wkun == keykey topk