diff options
Diffstat (limited to 'kiki.hs')
-rw-r--r-- | kiki.hs | 123 |
1 files changed, 69 insertions, 54 deletions
@@ -10,6 +10,7 @@ module Main where | |||
10 | 10 | ||
11 | import Debug.Trace | 11 | import Debug.Trace |
12 | import GHC.Exts (Down(..)) | 12 | import GHC.Exts (Down(..)) |
13 | import GHC.IO.Exception ( ioException, IOErrorType(..) ) | ||
13 | import Data.Tuple | 14 | import Data.Tuple |
14 | import Data.Binary | 15 | import Data.Binary |
15 | import Data.OpenPGP | 16 | import Data.OpenPGP |
@@ -41,6 +42,13 @@ import Control.Applicative | |||
41 | import System.Environment | 42 | import System.Environment |
42 | import System.Directory | 43 | import System.Directory |
43 | import System.Exit | 44 | import System.Exit |
45 | import System.Process | ||
46 | import System.Posix.IO (fdToHandle,fdRead) | ||
47 | import System.Posix.Files | ||
48 | import System.Posix.Signals | ||
49 | import System.Process.Internals (runGenProcess_,defaultSignal) | ||
50 | import System.IO (hPutStrLn,stderr) | ||
51 | import System.IO.Error | ||
44 | import ControlMaybe | 52 | import ControlMaybe |
45 | import Data.Char | 53 | import Data.Char |
46 | import Control.Arrow (first,second) | 54 | import Control.Arrow (first,second) |
@@ -48,13 +56,10 @@ import Data.Traversable hiding (mapM,forM) | |||
48 | import System.Console.CmdArgs | 56 | import System.Console.CmdArgs |
49 | -- import System.Posix.Time | 57 | -- import System.Posix.Time |
50 | import Data.Time.Clock.POSIX | 58 | import Data.Time.Clock.POSIX |
51 | import System.Posix.IO (fdToHandle,fdRead) | ||
52 | import System.Posix.Files | ||
53 | import Data.Monoid ((<>)) | 59 | import Data.Monoid ((<>)) |
54 | -- import Data.X509 | 60 | -- import Data.X509 |
55 | import qualified Data.Map as Map | 61 | import qualified Data.Map as Map |
56 | import DotLock | 62 | import DotLock |
57 | import System.IO (hPutStrLn,stderr) | ||
58 | 63 | ||
59 | 64 | ||
60 | warn str = hPutStrLn stderr str | 65 | warn str = hPutStrLn stderr str |
@@ -200,7 +205,13 @@ rsaPrivateKeyFromPacket pkt@(SecretKeyPacket {}) = do | |||
200 | MPI d <- lookup 'd' $ key pkt | 205 | MPI d <- lookup 'd' $ key pkt |
201 | MPI q <- lookup 'p' $ key pkt -- Note: p & q swapped | 206 | MPI q <- lookup 'p' $ key pkt -- Note: p & q swapped |
202 | MPI p <- lookup 'q' $ key pkt -- Note: p & q swapped | 207 | MPI p <- lookup 'q' $ key pkt -- Note: p & q swapped |
203 | coefficient <- lookup 'u' $ key pkt -- TODO: compute (inverse q) mod p | 208 | |
209 | -- Note: Here we fail if 'u' key is missing. | ||
210 | -- Ideally, it would be better to compute (inverse q) mod p | ||
211 | -- see Algebra.Structures.EuclideanDomain.extendedEuclidAlg | ||
212 | -- (package constructive-algebra) | ||
213 | coefficient <- lookup 'u' $ key pkt | ||
214 | |||
204 | let dmodp1 = MPI $ d `mod` (p - 1) | 215 | let dmodp1 = MPI $ d `mod` (p - 1) |
205 | dmodqminus1 = MPI $ d `mod` (q - 1) | 216 | dmodqminus1 = MPI $ d `mod` (q - 1) |
206 | return $ RSAPrivateKey | 217 | return $ RSAPrivateKey |
@@ -1155,9 +1166,12 @@ cross_merge keyrings f = do | |||
1155 | where isSecringKey (fn,Message ps) | 1166 | where isSecringKey (fn,Message ps) |
1156 | | fn==sec_n = listToMaybe ps | 1167 | | fn==sec_n = listToMaybe ps |
1157 | isSecringKey _ = Nothing | 1168 | isSecringKey _ = Nothing |
1158 | unlockFiles fsns | 1169 | -- unlockFiles fsns ----------- |
1159 | db' <- f (sec_n,fstkey) db | 1170 | ------------------------------- |
1160 | lk <- relock | 1171 | db' <- f (sec_n,fstkey) db |
1172 | -- lk <- relock --------------- | ||
1173 | let lk = (fsns,failed_locks) -- | ||
1174 | ------------------------------- | ||
1161 | maybe (if n==0 then pass 1 lk else return (lk,db)) | 1175 | maybe (if n==0 then pass 1 lk else return (lk,db)) |
1162 | (return . (lk,)) | 1176 | (return . (lk,)) |
1163 | db' | 1177 | db' |
@@ -1219,11 +1233,6 @@ parseSpec grip spec = (topspec,subspec) | |||
1219 | "" | top=="" && is40digitHex sub -> Nothing | 1233 | "" | top=="" && is40digitHex sub -> Nothing |
1220 | "" -> Just sub | 1234 | "" -> Just sub |
1221 | 1235 | ||
1222 | insertSubKey tag key (Just (KeyData p sigs uids subs)) = | ||
1223 | Just $ KeyData p sigs uids subs' | ||
1224 | where | ||
1225 | subs' = todo | ||
1226 | |||
1227 | splitAtMinBy comp xs = minimumBy comp' xxs | 1236 | splitAtMinBy comp xs = minimumBy comp' xxs |
1228 | where | 1237 | where |
1229 | xxs = zip (inits xs) (tails xs) | 1238 | xxs = zip (inits xs) (tails xs) |
@@ -1232,6 +1241,35 @@ splitAtMinBy comp xs = minimumBy comp' xxs | |||
1232 | compM Nothing mb = GT | 1241 | compM Nothing mb = GT |
1233 | compM _ _ = LT | 1242 | compM _ _ = LT |
1234 | 1243 | ||
1244 | |||
1245 | -- | systemEnv | ||
1246 | -- This is like System.Process.system except that it lets you set | ||
1247 | -- some environment variables. | ||
1248 | systemEnv _ "" = | ||
1249 | ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command") | ||
1250 | systemEnv vars cmd = do | ||
1251 | env0 <- getEnvironment | ||
1252 | let env1 = filter (isNothing . flip lookup vars . fst) env0 | ||
1253 | env = vars ++ env1 | ||
1254 | syncProcess "system" $ (shell cmd) {env=Just env} | ||
1255 | where | ||
1256 | -- This is a non-exported function from System.Process | ||
1257 | syncProcess fun c = do | ||
1258 | -- The POSIX version of system needs to do some manipulation of signal | ||
1259 | -- handlers. Since we're going to be synchronously waiting for the child, | ||
1260 | -- we want to ignore ^C in the parent, but handle it the default way | ||
1261 | -- in the child (using SIG_DFL isn't really correct, it should be the | ||
1262 | -- original signal handler, but the GHC RTS will have already set up | ||
1263 | -- its own handler and we don't want to use that). | ||
1264 | old_int <- installHandler sigINT Ignore Nothing | ||
1265 | old_quit <- installHandler sigQUIT Ignore Nothing | ||
1266 | (_,_,_,p) <- runGenProcess_ fun c | ||
1267 | (Just defaultSignal) (Just defaultSignal) | ||
1268 | r <- waitForProcess p | ||
1269 | _ <- installHandler sigINT old_int Nothing | ||
1270 | _ <- installHandler sigQUIT old_quit Nothing | ||
1271 | return r | ||
1272 | |||
1235 | doExport doDecrypt db (fname,subspec,ms,cmd) = | 1273 | doExport doDecrypt db (fname,subspec,ms,cmd) = |
1236 | case ms of | 1274 | case ms of |
1237 | [_] -> export | 1275 | [_] -> export |
@@ -1240,16 +1278,16 @@ doExport doDecrypt db (fname,subspec,ms,cmd) = | |||
1240 | where | 1278 | where |
1241 | ambiguous = error "Key specification is ambiguous." | 1279 | ambiguous = error "Key specification is ambiguous." |
1242 | shcmd = do | 1280 | shcmd = do |
1243 | -- | 1281 | let noop warning = do |
1244 | -- does ms contain exactly one key? | 1282 | warn warning |
1245 | -- yes -> export key | 1283 | return db |
1246 | -- no -> no keys? | 1284 | if null cmd then noop (fname ++ ": missing.") else do |
1247 | -- no -> ambiguous error | 1285 | let vars = [ ("file",fname) |
1248 | -- yes -> cmd | 1286 | , ("usage",maybe "" id subspec) ] |
1249 | -- if error warn | 1287 | e <- systemEnv vars cmd |
1250 | -- else need another pass | 1288 | case e of |
1251 | todo | 1289 | ExitFailure num -> noop $ fname ++ ": failed external (code="++show num++")" |
1252 | return Nothing | 1290 | ExitSuccess -> return Nothing -- need another pass |
1253 | export = do | 1291 | export = do |
1254 | let [(kk,KeyData key sigs uids subkeys)] = ms | 1292 | let [(kk,KeyData key sigs uids subkeys)] = ms |
1255 | p = flip (maybe (Just $ packet key)) subspec $ \tag -> do | 1293 | p = flip (maybe (Just $ packet key)) subspec $ \tag -> do |
@@ -1266,7 +1304,7 @@ doExport doDecrypt db (fname,subspec,ms,cmd) = | |||
1266 | _ -> ambiguous | 1304 | _ -> ambiguous |
1267 | flip (maybe shcmd) p $ \p -> do | 1305 | flip (maybe shcmd) p $ \p -> do |
1268 | pun <- doDecrypt p | 1306 | pun <- doDecrypt p |
1269 | flip (maybe shcmd) pun $ \pun -> do | 1307 | flip (maybe $ error "Bad passphrase?") pun $ \pun -> do |
1270 | warn $ "writing "++fname | 1308 | warn $ "writing "++fname |
1271 | writeKeyToFile False "PEM" fname pun | 1309 | writeKeyToFile False "PEM" fname pun |
1272 | return db | 1310 | return db |
@@ -1322,12 +1360,12 @@ doImport doDecrypt db (fname,subspec,ms,_) = do | |||
1322 | (xs',minsig,ys') = searchSubkeys tag wk key subsigs | 1360 | (xs',minsig,ys') = searchSubkeys tag wk key subsigs |
1323 | doInsert mbsig db = do | 1361 | doInsert mbsig db = do |
1324 | sig' <- makeSig doDecrypt top fname subkey_p tag mbsig | 1362 | sig' <- makeSig doDecrypt top fname subkey_p tag mbsig |
1325 | warn $ fname ++ ": new SignaturePacket" | 1363 | warn $ fname ++ ": yield SignaturePacket" |
1326 | let subs' = Map.insert subkk | 1364 | let subs' = Map.insert subkk |
1327 | (SubKey subkey_p $ xs'++[sig']++ys') | 1365 | (SubKey subkey_p $ xs'++[sig']++ys') |
1328 | subs | 1366 | subs |
1329 | return $ Map.insert kk (KeyData top topsigs uids subs') db | 1367 | return $ Map.insert kk (KeyData top topsigs uids subs') db |
1330 | when is_new (warn $ fname ++ ": new SecretKeyPacket") | 1368 | when is_new (warn $ fname ++ ": yield SecretKeyPacket "++fingerprint key) |
1331 | case minsig of | 1369 | case minsig of |
1332 | Nothing -> doInsert Nothing db -- we need to create a new sig | 1370 | Nothing -> doInsert Nothing db -- we need to create a new sig |
1333 | Just (True,sig) -> return db -- we can deduce is_new == False | 1371 | Just (True,sig) -> return db -- we can deduce is_new == False |
@@ -1564,37 +1602,14 @@ main = do | |||
1564 | let (imports,exports) = partition fst fs | 1602 | let (imports,exports) = partition fst fs |
1565 | use_db <- foldM (doImport decrypt) use_db (map snd imports) | 1603 | use_db <- foldM (doImport decrypt) use_db (map snd imports) |
1566 | ret_db <- foldM (doExport decrypt) (Just use_db) (map snd exports) | 1604 | ret_db <- foldM (doExport decrypt) (Just use_db) (map snd exports) |
1567 | {- | ||
1568 | forM_ pkeypairs $ \(spec,f,cmd) -> do | ||
1569 | let ms = filterMatches spec (Map.toList db) | ||
1570 | import_if_neccessary = todo | ||
1571 | -- read file | ||
1572 | -- is the key in ms? | ||
1573 | -- yes -> continue | ||
1574 | -- no -> import key | ||
1575 | -- need to write keyring files or remember imports | ||
1576 | export_or_create = todo | ||
1577 | -- does ms contain exactly one key? | ||
1578 | -- yes -> export key | ||
1579 | -- no -> no keys? | ||
1580 | -- no -> ambiguous error | ||
1581 | -- yes -> cmd | ||
1582 | -- if error warn | ||
1583 | -- else need another pass | ||
1584 | f_found <- doesFileExist f | ||
1585 | if f_found | ||
1586 | then import_if_neccessary | ||
1587 | else export_or_create | ||
1588 | return () | ||
1589 | -} | ||
1590 | |||
1591 | let ret_db = Just use_db | ||
1592 | 1605 | ||
1593 | let shspec = Map.fromList [("--show-wk", show_wk secfile grip) | 1606 | flip (maybe $ return ()) ret_db . const $ do |
1594 | ,("--show-all",show_all )] | 1607 | -- On last pass, interpret --show-* commands. |
1595 | shargs = mapMaybe (\x -> listToMaybe x >>= \x ->Map.lookup x shspec) sargs | 1608 | let shspec = Map.fromList [("--show-wk", show_wk secfile grip) |
1609 | ,("--show-all",show_all )] | ||
1610 | shargs = mapMaybe (\x -> listToMaybe x >>= \x ->Map.lookup x shspec) sargs | ||
1596 | 1611 | ||
1597 | forM_ shargs $ \cmd -> cmd use_db | 1612 | forM_ shargs $ \cmd -> cmd use_db |
1598 | return $ ret_db | 1613 | return $ ret_db |
1599 | 1614 | ||
1600 | return() | 1615 | return() |