summaryrefslogtreecommitdiff
path: root/kiki.hs
diff options
context:
space:
mode:
authorJames Crayne <jim.crayne@gmail.com>2016-04-24 01:04:49 -0400
committerJames Crayne <jim.crayne@gmail.com>2016-04-24 01:04:49 -0400
commitd5716df5c935fb17c4d1c8f9dbe8b32e2e6b32dc (patch)
tree35018b853cab418ca53b03940cca3d3bdd17b422 /kiki.hs
parent5000de4f1079004fa398e4b129896f5e59e9c9df (diff)
Documentation fixes
Diffstat (limited to 'kiki.hs')
-rw-r--r--kiki.hs164
1 files changed, 88 insertions, 76 deletions
diff --git a/kiki.hs b/kiki.hs
index 8ee88c6..f939fa4 100644
--- a/kiki.hs
+++ b/kiki.hs
@@ -1,5 +1,6 @@
1{-# LANGUAGE DoAndIfThenElse #-} 1{-# LANGUAGE DoAndIfThenElse #-}
2{-# LANGUAGE ViewPatterns #-} 2{-# LANGUAGE ViewPatterns #-}
3{-# LANGUAGE PatternGuards #-}
3{-# LANGUAGE TupleSections #-} 4{-# LANGUAGE TupleSections #-}
4{-# LANGUAGE OverloadedStrings #-} 5{-# LANGUAGE OverloadedStrings #-}
5{-# LANGUAGE RankNTypes #-} 6{-# LANGUAGE RankNTypes #-}
@@ -366,7 +367,7 @@ show_wip keyspec wkgrip db = do
366 putStrLn $ walletImportFormat nwb k 367 putStrLn $ walletImportFormat nwb k
367 368
368show_torhash pubkey _ = do 369show_torhash pubkey _ = do
369 bs <- Char8.readFile pubkey 370 bs <- Char8.readFile pubkey
370 let parsekey f dta = do 371 let parsekey f dta = do
371 let mdta = L.pack <$> Base64.decode (Char8.unpack dta) 372 let mdta = L.pack <$> Base64.decode (Char8.unpack dta)
372 e <- decodeASN1 DER <$> mdta 373 e <- decodeASN1 DER <$> mdta
@@ -402,7 +403,7 @@ show_cert keyspec wkgrip db = do
402 pems = map (writePEM "CERTIFICATE") qqs 403 pems = map (writePEM "CERTIFICATE") qqs
403 forM_ pems putStrLn 404 forM_ pems putStrLn
404 _ -> void $ warn (keyspec ++ ": ambiguous") 405 _ -> void $ warn (keyspec ++ ": ambiguous")
405 406
406{- 407{-
407show_cert certfile _ = do 408show_cert certfile _ = do
408 bs <- Char8.readFile certfile 409 bs <- Char8.readFile certfile
@@ -436,7 +437,7 @@ show_cert certfile _ = do
436 putStrLn "" 437 putStrLn ""
437 putStrLn $ maybe "" ((" gzip blob = " ++) . b64L . pcertBlob) e 438 putStrLn $ maybe "" ((" gzip blob = " ++) . b64L . pcertBlob) e
438 -} 439 -}
439 -- ASN1 starts: 440 -- ASN1 starts:
440 -- 1 2 3 4 5 6 7 8 441 -- 1 2 3 4 5 6 7 8
441 -- cl....pc.tag.......... 442 -- cl....pc.tag..........
442 -- Start Sequence tag = 0x10 443 -- Start Sequence tag = 0x10
@@ -508,16 +509,12 @@ kiki_usage bExport bImport bSecret cmd = putStr $
508 "show" -> unlines $ 509 "show" -> unlines $
509 ["kiki show [options...]" 510 ["kiki show [options...]"
510 ,"" 511 ,""
511 ," show displays infomration about keys stored in the data files which resides in" 512 ," show displays information about keys stored in the data files which resides in"
512 ," the home directory (see --homedir)." 513 ," the home directory (see --homedir)."
513 ,"" 514 ,""
514 ," The files pubring.gpg and subring.gpg in the directory specified by the " 515 ," The files pubring.gpg and subring.gpg in the directory specified by the "
515 ," --homedir option are implicitly included in the keyring set." 516 ," --homedir option are implicitly included in the keyring set."
516 ,"" 517 ,""
517 ," Subkeys that are imported with kiki are given an annotation \"usage@\" which"
518 ," indicates what the key is for. This tag can be used as a SPEC to select a"
519 ," particular key. Master keys may be specified by using fingerprints or by"
520 ," specifying a substring of an associated UID."
521 ,"Options: " 518 ,"Options: "
522 ] ++ commonOptions ++ 519 ] ++ commonOptions ++
523 [" --working" 520 [" --working"
@@ -562,10 +559,10 @@ kiki_usage bExport bImport bSecret cmd = putStr $
562 ,"" 559 ,""
563 ," --help Shows this help screen." 560 ," --help Shows this help screen."
564 ,"" 561 ,""
565 ] 562 ]
566 "sync-secret" -> unlines $ 563 "sync-secret" -> unlines $
567 ["kiki sync-secret [KEYSPEC ...]" 564 ["kiki sync-secret [KEYSPEC ...]"
568 ,"kiki sync-secret FLAGS [--keypairs KEYSPEC ...] [--keyrings FILE ...] [--hosts FILE ...]" 565 ,"kiki sync-secret FLAGS [--pems KEYSPEC ...] [--keyrings FILE ...] [--hosts FILE ...]"
569 ," [--wallets FILE ...]" 566 ," [--wallets FILE ...]"
570 ,"" 567 ,""
571 ," sync-secret syncs the information inside your OpenGPG keyring with information" 568 ," sync-secret syncs the information inside your OpenGPG keyring with information"
@@ -603,7 +600,7 @@ kiki_usage bExport bImport bSecret cmd = putStr $
603 ," are not included after the --keyrings option." 600 ," are not included after the --keyrings option."
604 ,"" 601 ,""
605 ," If KEYSPEC arguments appear prior to any of --keyrings, --wallets, or --hosts," 602 ," If KEYSPEC arguments appear prior to any of --keyrings, --wallets, or --hosts,"
606 ," then they are interpretted as if arguments to --keypairs." 603 ," then they are interpretted as if arguments to --pems."
607 ,"" 604 ,""
608 ] ++ syncflags ++ specifyingFiles 605 ] ++ syncflags ++ specifyingFiles
609 "sync-public" -> unlines $ 606 "sync-public" -> unlines $
@@ -679,7 +676,7 @@ kiki_usage bExport bImport bSecret cmd = putStr $
679 ,"" 676 ,""
680 ," (See 'kiki help spec' for more information.)" 677 ," (See 'kiki help spec' for more information.)"
681 ,"" 678 ,""
682 ] ++ syncflags ++ specifyingFiles 679 ] ++ syncflags ++ specifyingFiles
683 "export-public" -> unlines $ 680 "export-public" -> unlines $
684 ["kiki export-public [options...]" 681 ["kiki export-public [options...]"
685 ,"" 682 ,""
@@ -692,7 +689,7 @@ kiki_usage bExport bImport bSecret cmd = putStr $
692 ,"" 689 ,""
693 ," (See 'kiki help spec' for more information.)" 690 ," (See 'kiki help spec' for more information.)"
694 ,"" 691 ,""
695 ] ++ specifyingFiles 692 ] ++ syncflags ++ specifyingFiles
696 "spec" -> unlines keyspec 693 "spec" -> unlines keyspec
697 where 694 where
698 commonOptions :: [String] 695 commonOptions :: [String]
@@ -772,13 +769,15 @@ kiki_usage bExport bImport bSecret cmd = putStr $
772 ," 5E24CD442AA6965D2012E62A905C24185D5379C2" 769 ," 5E24CD442AA6965D2012E62A905C24185D5379C2"
773 ] 770 ]
774 771
775documentPassphraseFDFlag bExport bImport bSecret = 772documentPassphraseFDFlag bExport bImport bSecret =
773 if bSecret then
776 [" --passphrase-fd FD" 774 [" --passphrase-fd FD"
777 ," The file descripter from which to read a passphrase. If FD is" 775 ," The file descripter from which to read a passphrase. If FD is"
778 ," 0, then the passphrase is inputted via stdin. Note that this" 776 ," 0, then the passphrase is inputted via stdin. Note that this"
779 ," requires the user to issue CTRL-D to send EOF, so that kiki" 777 ," requires the user to issue CTRL-D to send EOF, so that kiki"
780 ," knows to continue." 778 ," knows to continue."
781 ,""] 779 ,""]
780 else []
782 781
783documentImportFlag bExport bImport bSecret = 782documentImportFlag bExport bImport bSecret =
784 if bImport then 783 if bImport then
@@ -804,14 +803,8 @@ documentAutoSignFlag bExport bImport bSecret =
804 ," 'tor' subkey corresponding to the address HOSTNAME.onion." 803 ," 'tor' subkey corresponding to the address HOSTNAME.onion."
805 ,""] 804 ,""]
806documentKeyPairsOption :: Bool -> Bool -> Bool -> [String] 805documentKeyPairsOption :: Bool -> Bool -> Bool -> [String]
807documentKeyPairsOption bExport bImport bSecret = 806documentKeyPairsOption bExport bImport bSecret =
808 [" --keypairs [KEYSPEC ...]" 807 [" --pems [KEYSPEC ...]"
809 ," A keypair is a secret key coupled with it's corresponding public"
810 ," key, both of which are ordinarily stored in a single file in PEM"
811 ," format. Users incognisant of the fact that the public key (which"
812 ," is also stored separately) is in this file, often think of it as"
813 ," their secret key file."
814 ,""
815 ] ++ case (bExport,bImport,bSecret) of 808 ] ++ case (bExport,bImport,bSecret) of
816 (True,True,True) -> -- sync-secret 809 (True,True,True) -> -- sync-secret
817 [" This option specifies the paths of such private PEM files which" 810 [" This option specifies the paths of such private PEM files which"
@@ -848,29 +841,27 @@ documentKeyPairsOption bExport bImport bSecret =
848 ] ++ afterSecond 841 ] ++ afterSecond
849 (False,True,False) -> -- import-public NOT-IMPLEMENTED 842 (False,True,False) -> -- import-public NOT-IMPLEMENTED
850 [" This option specifies the paths of PEM files, of both the" 843 [" This option specifies the paths of PEM files, of both the"
851 ," public and private variety, which either currently contain" 844 ," public and private variety, which currently contain keys to"
852 ," contain keys to be imported. If your working key has no subkey" 845 ," be imported. If your working key has no subkey with the"
853 ," with the given tag, and the file is empty or does not exist," 846 ," given tag, and the file is empty or does not exist, and a"
854 ," and a shell command is specified in braces, then the shell" 847 ," shell command is specified in braces, then the shell command"
855 ," command will be executed in a modified environment with the" 848 ," will be executed in a modified environment with the"
856 ," expectation of creating the PEM file for import. Files external" 849 ," expectation of creating the PEM file for import. Files"
857 ," to your OpenGPG keyring will not be modified by this command." 850 ," external to your OpenGPG keyring will not be modified by"
858 ," Unlike the import-secret command, this command leaves no" 851 ," this command. Unlike the import-secret command, this"
859 ," possibility of secret key information leaking from your OpenGPG" 852 ," command leaves no possibility of secret key information"
860 ," keyring. " 853 ," leaking from your OpenGPG keyring. "
861 ,"" 854 ,""
862 ] ++ afterSecond 855 ] ++ afterSecond
863 (True,False,True) -> -- export-secret 856 (True,False,True) -> -- export-secret
864 [" This option specifies the paths of such private PEM files, of" 857 [" This option specifies the paths of PEM files, of the private or"
865 ," both the public variety, to which kiki will export keys. These" 858 ," public variety, which lack information to be exported. Note that"
866 ," files will be updated with information from your OpenGPG" 859 ," files currently in the public format may be overwritten to update"
867 ," keyring, but your OpenGPG keyring will not be modified by this" 860 ," them to the private format which holds both public and private"
868 ," command. Unlike the export-secret comamnd, this command leaves" 861 ," key information."
869 ," no possibility that secret key information will leak from your"
870 ," OpenGPG keyring."
871 ,"" 862 ,""
872 ] ++ afterSecond 863 ] ++ afterSecond
873 (True,False,False) -> -- export-public NOT-IMPLEMENTED 864 (True,False,False) -> -- export-public
874 [" This option specifies the paths of PEM files, of the private or" 865 [" This option specifies the paths of PEM files, of the private or"
875 ," public variety, which lack public keys to be exported. Unlike" 866 ," public variety, which lack public keys to be exported. Unlike"
876 ," the export-secret command, this command leaves no possibility" 867 ," the export-secret command, this command leaves no possibility"
@@ -879,16 +870,42 @@ documentKeyPairsOption bExport bImport bSecret =
879 ,"" 870 ,""
880 ] ++ afterSecond 871 ] ++ afterSecond
881 _ -> afterSecond 872 _ -> afterSecond
882 where afterSecond = 873 where afterSecond =
883 [" Subkeys that are imported with kiki are given an annotation" 874 [" Subkeys that are imported with kiki are given an annotation"
884 ," \"usage@\" which indicates what the key is for. This tag can" 875 ," \"usage@\" which indicates what the key is for. This tag can"
885 ," be used as a SPEC to select a particular key. If a specifed PEM" 876 ] ++ if bImport then n000Import else n000Export
877 n000Import =
878 [" be used as a SPEC to select a particular key. If a specifed PEM"
886 ," file contains a novel key for an existing tag, it will imported," 879 ," file contains a novel key for an existing tag, it will imported,"
887 ," and you will have multiple keys with the same tag." 880 ," and you will have multiple keys with the same tag."
888 ,"" 881 ,""
889 ," Each KEYSPEC specifies that a key should match the content and" 882 ," Each KEYSPEC specifies that a key should match the content and"
890 ," timestamp of an external PKCS #1 private RSA key file." 883 ," timestamp of an external file which is in the PKCS #1 private"
891 ," " 884 ," RSA key format." -- " or in the PKCS #8 public key format."
885 ] ++ n0
886 n000Export =
887 [" be used as a SPEC to select a particular key."
888 ,""
889 ," (TODO: check) Each KEYSPEC specifies that a key should match the content and"
890 ," timestamp of an indicated external file which is either in PKCS #1"
891 ," private RSA key format or in PKCS #8 public key format (provided"
892 ," that the file already exists). If the file does not exist, it"
893 ] ++ (if bSecret then n00Secret else n00Public) ++ n0
894 n00Secret =
895 [" will be created and have PKCS #1 Private RSA Key format."
896 ]
897 n00Public =
898 [" will be created and have PKCS #8 Public Key format."
899 ]
900
901 n0 =
902 [""
903 ," If there is only one master key in your keyring and only one"
904 ," key is used for each purpose, then it is possible for SPEC in"
905 ," this case to merely be a tag which offers information about"
906 ," what this key is used for, for example, any of `tor',"
907 ," `ssh-client', `ssh-host', or `strongswan' will do."
908 ,""
892 ," KEYSPEC ::= tag '=' file" 909 ," KEYSPEC ::= tag '=' file"
893 ] ++ if bImport then " | tag '=' file '{' <shell command to create key file> '}'":next 910 ] ++ if bImport then " | tag '=' file '{' <shell command to create key file> '}'":next
894 else next 911 else next
@@ -902,14 +919,9 @@ documentKeyPairsOption bExport bImport bSecret =
902 next' = 919 next' =
903 ["" 920 [""
904 ," where the format of SPEC is documented in 'kiki help spec'." 921 ," where the format of SPEC is documented in 'kiki help spec'."
905 ,"" 922 ] ++ next''
906 ," If there is only one master key in your keyring and only one" 923 next'' = if bImport then timeStamps ++ next''' else next'''
907 ," key is used for each purpose, then it is possible for SPEC in" 924 timeStamps =
908 ," this case to merely be a tag which offers information about"
909 ," what this key is used for, for example, any of `tor',"
910 ," `ssh-client', `ssh-host', or `strongswan' will do."] ++ next''
911 next'' = if bImport then timeStamps ++ next''' else next'''
912 timeStamps =
913 ["" 925 [""
914 ," Your OpenGPG keyring contains time stamps for each subkey." 926 ," Your OpenGPG keyring contains time stamps for each subkey."
915 ," Timestamps of newly imported keys will reflect the mtimes of" 927 ," Timestamps of newly imported keys will reflect the mtimes of"
@@ -941,10 +953,10 @@ documentWalletsOption :: Bool -> Bool -> Bool -> [String]
941documentWalletsOption bExport bImport False = [] 953documentWalletsOption bExport bImport False = []
942documentWalletsOption bExport bImport True = 954documentWalletsOption bExport bImport True =
943 [" --wallets [FILE ...]" 955 [" --wallets [FILE ...]"
944 ," Provide wallet files with secret crypto-coin keys in Wallet" 956 ," Provide wallet files with secret crypto-coin keys in Wallet"
945 ," Import Format. The keys will be treated as subkeys of your" 957 ," Import Format. The keys will be treated as subkeys of your"
946 ," current working key (the one shown by --show-wk)." 958 ," current working key (the one shown by --show-wk)."
947 ,""] 959 ,""]
948 960
949documentHostsOption :: Bool -> Bool -> Bool -> [String] 961documentHostsOption :: Bool -> Bool -> Bool -> [String]
950documentHostsOption bExport bImport bSecret = 962documentHostsOption bExport bImport bSecret =
@@ -1036,11 +1048,11 @@ buildStreamInfo rtyp ftyp = StreamInfo { typ = ftyp
1036 1048
1037 1049
1038-- Flag-specific options 1050-- Flag-specific options
1039-- bSecret: --keypairs and --wallets 1051-- bSecret: --pems and --wallets
1040-- bImport: --import and --import-if-authentic 1052-- bImport: --import and --import-if-authentic
1041sync :: Bool -> Bool -> Bool -> String -> [String] -> IO () 1053sync :: Bool -> Bool -> Bool -> String -> [String] -> IO ()
1042sync bExport bImport bSecret cmdarg args_raw = do 1054sync bExport bImport bSecret cmdarg args_raw = do
1043 let (sargs,margs) = processArgs sargspec polyVariadicArgs "--keypairs" args_raw 1055 let (sargs,margs) = processArgs sargspec polyVariadicArgs "--pems" args_raw
1044 sargspec = [ ("--show-wk",0) 1056 sargspec = [ ("--show-wk",0)
1045 , ("--autosign",0) 1057 , ("--autosign",0)
1046 {-, ("--show-all",0) 1058 {-, ("--show-all",0)
@@ -1054,13 +1066,13 @@ sync bExport bImport bSecret cmdarg args_raw = do
1054 [ ("--import",0), ("--import-if-authentic",0) ] 1066 [ ("--import",0), ("--import-if-authentic",0) ]
1055 polyVariadicArgs = ["--keyrings" 1067 polyVariadicArgs = ["--keyrings"
1056 ,"--hosts" 1068 ,"--hosts"
1057 ,"--keypairs"] 1069 ,"--pems"]
1058 ++ do guard bSecret 1070 ++ do guard bSecret
1059 [ "--wallets" ] 1071 [ "--wallets" ]
1060 -- putStrLn $ "margs = " ++ show (Map.assocs margs) 1072 -- putStrLn $ "margs = " ++ show (Map.assocs margs)
1061 unkeysRef <- newIORef Map.empty 1073 unkeysRef <- newIORef Map.empty
1062 pwRef <- newIORef Nothing 1074 pwRef <- newIORef Nothing
1063 let keypairs0 = parseKeySpecs (fromMaybe [] $ Map.lookup "--keypairs" margs) 1075 let keypairs0 = parseKeySpecs (fromMaybe [] $ Map.lookup "--pems" margs)
1064 keyrings_ = fromMaybe [] $ Map.lookup "--keyrings" margs 1076 keyrings_ = fromMaybe [] $ Map.lookup "--keyrings" margs
1065 wallets = fromMaybe [] $ Map.lookup "--wallets" margs 1077 wallets = fromMaybe [] $ Map.lookup "--wallets" margs
1066 passphrase_fd = concat <$> Map.lookup "--passphrase-fd" margs 1078 passphrase_fd = concat <$> Map.lookup "--passphrase-fd" margs
@@ -1078,7 +1090,7 @@ sync bExport bImport bSecret cmdarg args_raw = do
1078 passfd = fmap (FileDesc . read) passphrase_fd 1090 passfd = fmap (FileDesc . read) passphrase_fd
1079 reftyp = if bExport then KF_Subkeys 1091 reftyp = if bExport then KF_Subkeys
1080 else KF_None 1092 else KF_None
1081 pems = flip map keypairs 1093 pems = flip map keypairs
1082 $ \(usage,path,cmd) -> 1094 $ \(usage,path,cmd) ->
1083 let cmd' = mfilter (not . null) (Just cmd) 1095 let cmd' = mfilter (not . null) (Just cmd)
1084 in if bExport 1096 in if bExport
@@ -1131,7 +1143,7 @@ sync bExport bImport bSecret cmdarg args_raw = do
1131 } 1143 }
1132 1144
1133 (\f -> maybe f (const $ kiki_usage bExport bImport bSecret cmdarg) $ Map.lookup "--help" margs) $ do 1145 (\f -> maybe f (const $ kiki_usage bExport bImport bSecret cmdarg) $ Map.lookup "--help" margs) $ do
1134 KikiResult rt report <- runKeyRing kikiOp 1146 KikiResult rt report <- runKeyRing kikiOp
1135 1147
1136 case rt of 1148 case rt of
1137 KikiSuccess rt -> do -- interpret --show-* commands. 1149 KikiSuccess rt -> do -- interpret --show-* commands.
@@ -1186,8 +1198,8 @@ kiki "help" [] = do
1186 return () 1198 return ()
1187 1199
1188kiki "help" args = forM_ args $ \arg -> case lookup arg commands of 1200kiki "help" args = forM_ args $ \arg -> case lookup arg commands of
1189 Nothing | arg == "spec" -> kiki_usage False False False arg 1201 Nothing | arg == "spec" -> kiki_usage False False False arg
1190 Nothing | arg == "SPEC" -> kiki_usage False False False arg 1202 Nothing | arg == "SPEC" -> kiki_usage False False False arg
1191 Nothing -> putStrLn $ "No help available for commmand '" ++ arg ++ "'." 1203 Nothing -> putStrLn $ "No help available for commmand '" ++ arg ++ "'."
1192 _ -> kiki arg ["--help"] 1204 _ -> kiki arg ["--help"]
1193 1205
@@ -1226,8 +1238,8 @@ kiki "show" args = do
1226 , ( HomePub, streaminfo { access = Pub }) 1238 , ( HomePub, streaminfo { access = Pub })
1227 ] 1239 ]
1228 ++ rings 1240 ++ rings
1229 ++ pems 1241 ++ pems
1230 ++ walts 1242 ++ walts
1231 ++ hosts 1243 ++ hosts
1232 , opPassphrases = do pfile <- maybeToList passfd 1244 , opPassphrases = do pfile <- maybeToList passfd
1233 return $ PassphraseSpec Nothing Nothing pfile 1245 return $ PassphraseSpec Nothing Nothing pfile
@@ -1236,7 +1248,7 @@ kiki "show" args = do
1236 } 1248 }
1237 1249
1238 (\f -> maybe f (const $ kiki_usage False False False "show") $ Map.lookup "--help" margs) $ do 1250 (\f -> maybe f (const $ kiki_usage False False False "show") $ Map.lookup "--help" margs) $ do
1239 KikiResult rt report <- runKeyRing kikiOp 1251 KikiResult rt report <- runKeyRing kikiOp
1240 1252
1241 input_key <- maybe (return Nothing) 1253 input_key <- maybe (return Nothing)
1242 (const $ fmap (Just . readPublicKey) Char8.getContents) 1254 (const $ fmap (Just . readPublicKey) Char8.getContents)
@@ -1348,7 +1360,7 @@ kiki "merge" args = do
1348 , op { opTransforms = opTransforms op ++ [DeleteSubKey fp] } ) 1360 , op { opTransforms = opTransforms op ++ [DeleteSubKey fp] } )
1349 1361
1350 doAutosign :: Bool -> StreamInfo -> KeyRingOperation -> (StreamInfo,KeyRingOperation) 1362 doAutosign :: Bool -> StreamInfo -> KeyRingOperation -> (StreamInfo,KeyRingOperation)
1351 doAutosign True flow op = 1363 doAutosign True flow op =
1352 if Map.null (opFiles op) 1364 if Map.null (opFiles op)
1353 then (flow, op { opTransforms = opTransforms op ++ [Autosign] }) 1365 then (flow, op { opTransforms = opTransforms op ++ [Autosign] })
1354 else (flow { transforms = transforms flow ++ [Autosign] }, op) 1366 else (flow { transforms = transforms flow ++ [Autosign] }, op)
@@ -1477,7 +1489,7 @@ kiki "init-key" args = do
1477 ipsecpathpub0 = fromMaybe "" rootdir ++ "/etc/ipsec.d/certs/%(onion).pem" 1489 ipsecpathpub0 = fromMaybe "" rootdir ++ "/etc/ipsec.d/certs/%(onion).pem"
1478 contactipsec0 = fromMaybe "" rootdir ++ "/etc/ipsec.d/certs/%(onion).pem" 1490 contactipsec0 = fromMaybe "" rootdir ++ "/etc/ipsec.d/certs/%(onion).pem"
1479 1491
1480 1492
1481 -- First, we ensure that the tor key exists and is imported 1493 -- First, we ensure that the tor key exists and is imported
1482 -- so that we know where to put the strongswan key. 1494 -- so that we know where to put the strongswan key.
1483 let passfd = fmap (FileDesc . read) $ lookup "passphrase-fd" args 1495 let passfd = fmap (FileDesc . read) $ lookup "passphrase-fd" args
@@ -1506,21 +1518,21 @@ kiki "init-key" args = do
1506 , opTransforms = [] 1518 , opTransforms = []
1507 } 1519 }
1508 doNothing = return () 1520 doNothing = return ()
1509 nop = KeyRingOperation 1521 nop = KeyRingOperation
1510 { opFiles = Map.empty 1522 { opFiles = Map.empty
1511 , opPassphrases = do pfd <- maybeToList passfd 1523 , opPassphrases = do pfd <- maybeToList passfd
1512 return $ PassphraseSpec Nothing Nothing pfd 1524 return $ PassphraseSpec Nothing Nothing pfd
1513 , opHome=homespec, opTransforms = [] 1525 , opHome=homespec, opTransforms = []
1514 } 1526 }
1515 if bUnprivileged then doNothing else mkdirFor torpath 1527 if bUnprivileged then doNothing else mkdirFor torpath
1516 KikiResult rt report <- runKeyRing (if bUnprivileged then nop else op) 1528 KikiResult rt report <- runKeyRing (if bUnprivileged then nop else op)
1517 forM_ report $ \(fname,act) -> do 1529 forM_ report $ \(fname,act) -> do
1518 putStrLn $ fname ++ ": " ++ reportString act 1530 putStrLn $ fname ++ ": " ++ reportString act
1519 rt <- case rt of 1531 rt <- case rt of
1520 BadPassphrase -> 1532 BadPassphrase ->
1521 error "Operation requires correct passphrase. (Hint: Use --passphrase-fd=0 to input it on stdin.)" 1533 error "Operation requires correct passphrase. (Hint: Use --passphrase-fd=0 to input it on stdin.)"
1522 _ -> unconditionally $ return rt 1534 _ -> unconditionally $ return rt
1523 1535
1524 -- Now import, export, or generate the remaining secret keys. 1536 -- Now import, export, or generate the remaining secret keys.
1525 let oname' = do wk <- rtWorkingKey rt 1537 let oname' = do wk <- rtWorkingKey rt
1526 onionNameForContact (keykey wk) (rtKeyDB rt) 1538 onionNameForContact (keykey wk) (rtKeyDB rt)
@@ -1553,17 +1565,17 @@ kiki "init-key" args = do
1553 forM_ report $ \(fname,act) -> do 1565 forM_ report $ \(fname,act) -> do
1554 putStrLn $ fname ++ ": " ++ reportString act 1566 putStrLn $ fname ++ ": " ++ reportString act
1555 rt <- case rt of 1567 rt <- case rt of
1556 BadPassphrase -> 1568 BadPassphrase ->
1557 error "Operation requires correct passphrase. (Hint: Use --passphrase-fd=0 to input it on stdin.)" 1569 error "Operation requires correct passphrase. (Hint: Use --passphrase-fd=0 to input it on stdin.)"
1558 _ -> unconditionally $ return rt 1570 _ -> unconditionally $ return rt
1559 1571
1560 -- Finally, export public keys if they do not exist. 1572 -- Finally, export public keys if they do not exist.
1561 flip (maybe $ warn "missing working key?") (rtGrip rt) $ \grip -> do 1573 flip (maybe $ warn "missing working key?") (rtGrip rt) $ \grip -> do
1562 gotc <- doesFileExist (sshcpathpub) 1574 gotc <- doesFileExist (sshcpathpub)
1563 when (not gotc) $ do 1575 when (not gotc) $ do
1564 either warn (writeFile sshcpathpub) 1576 either warn (writeFile sshcpathpub)
1565 $ show_ssh' "ssh-client" grip (rtKeyDB rt) 1577 $ show_ssh' "ssh-client" grip (rtKeyDB rt)
1566 if (not bUnprivileged) 1578 if (not bUnprivileged)
1567 then do 1579 then do
1568 goth <- doesFileExist (sshspathpub) 1580 goth <- doesFileExist (sshspathpub)
1569 when (not goth) $ do 1581 when (not goth) $ do