summaryrefslogtreecommitdiffhomepage
path: root/CmdLine.hs
blob: 038a2106715c50284abbe77721e0ae06c2f5d7f1 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
{- Copyright 2016 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module CmdLine where

import Types
import Tunables
import qualified Gpg
import Options.Applicative
import qualified Data.ByteString.UTF8 as BU8
import System.Directory
import Network.Wai.Handler.Warp (Port)

data CmdLine = CmdLine
	{ mode :: Maybe Mode
	, secretkeysource :: Maybe SecretKeySource
	, localstorage :: Bool
	, gui :: Bool
	, testMode :: Bool
	, customShareParams :: Maybe ShareParams
	, serverConfig :: ServerConfig
	}

data Mode = Backup | Restore | UploadQueued | Server | Benchmark
	deriving (Show)

data ServerConfig = ServerConfig
	{ serverPort :: Port
	, serverAddress :: String
	}

parse :: Parser CmdLine
parse = CmdLine
	<$> optional (backup <|> restore <|> uploadqueued <|> server <|> benchmark)
	<*> optional (gpgswitch <|> fileswitch)
	<*> localstorageswitch
	<*> guiswitch
	<*> testmodeswitch
	<*> optional (ShareParams <$> totalobjects <*> neededobjects)
	<*> serverconfig
  where
	backup = flag' Backup
		( long "backup"
		<> help "Store a secret key in keysafe."
		)
	restore = flag' Restore
		( long "restore"
		<> help "Retrieve a secret key from keysafe."
		)
	uploadqueued = flag' UploadQueued
		( long "uploadqueued"
		<> help "Upload any data to servers that was queued by a previous --backup run."
		)
	server = flag' Server
		( long "server"
		<> help "Run as a keysafe server, accepting objects and storing them to ~/.keysafe/objects/local/"
		)
	benchmark = flag' Benchmark
		( long "benchmark"
		<> help "Benchmark speed of keysafe's cryptographic primitives."
		)
	gpgswitch = GpgKey . KeyId . BU8.fromString <$> strOption
		( long "gpgkeyid"
		<> metavar "KEYID"
		<> help "Specify keyid of gpg key to back up or restore. (When this option is used to back up a key, it must also be used at restore time.)"
		)
	fileswitch = KeyFile <$> strOption
		( long "keyfile"
		<> metavar "FILE"
		<> help "Specify secret key file to back up or restore. (The same filename must be used to restore a key as was used to back it up.)"
		)
	localstorageswitch = switch
		( long "store-local"
		<> help "Store data locally, in ~/.keysafe/objects/local/. (The default is to store data in the cloud.)"
		)
	testmodeswitch = switch
		( long "testmode"
		<> help "Avoid using expensive cryptographic operations to secure data. Use for testing only, not with real secret keys."
		)
	guiswitch = switch
		( long "gui"
		<> help "Use GUI interface for interaction. Default is to use readline interface when run in a terminal, and GUI otherwise."
		)
	totalobjects = option auto 
		( long "totalshares"
		<> metavar "M"
		<> help ("Configure the number of shares to split encrypted secret key into. (default: " ++ show (totalObjects (shareParams defaultTunables)) ++ ") (When this option is used to back up a key, it must also be provided at restore time.)")
		)
	neededobjects = option auto 
		( long "neededshares"
		<> metavar "N"
		<> help ("Configure the number of shares needed to restore. (default: " ++ show (neededObjects (shareParams defaultTunables)) ++ ") (When this option is used to back up a key, it must also be provided at restore time.)")
		)
	serverconfig = ServerConfig
		<$> option auto
			( long "port"
			<> metavar "P"
			<> value 80
			<> showDefault
			<> help "Port for server to listen on."
			)
		<*> option str
			( long "address"
			<> metavar "A"
			<> value "127.0.0.1"
			<> showDefault
			<> help "Address for server to bind to."
			)
get :: IO CmdLine
get = execParser opts
  where
	opts = info (helper <*> parse)
		( fullDesc
		<> header "keysafe - securely back up secret keys"
		)

-- | When a mode is not specified on the command line,
-- default to backing up if a secret key exists, and otherwise restoring.
selectMode :: CmdLine -> IO Mode
selectMode cmdline = case mode cmdline of
	Just m -> return m
	Nothing -> case secretkeysource cmdline of
		Just (KeyFile f) -> present <$> doesFileExist f
		_ -> present . not . null <$> Gpg.listSecretKeys
  where
	present True = Backup
	present False = Restore

customizeShareParams :: CmdLine -> Tunables -> Tunables
customizeShareParams cmdline t = case customShareParams cmdline of
	Nothing -> t
	Just ps -> t { shareParams = ps }