summaryrefslogtreecommitdiffhomepage
path: root/CmdLine.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-10-06 14:38:59 -0400
committerJoey Hess <joeyh@joeyh.name>2016-10-06 14:49:24 -0400
commit61ab8bd1f576e633a2eea4b63033c368a6645602 (patch)
tree1eacccce62019f89360a605d2c0cac72993bfa65 /CmdLine.hs
parentb40d441c52f37584653e74fada9906cc8105c9f7 (diff)
downloadkeysafe-61ab8bd1f576e633a2eea4b63033c368a6645602.tar.gz
New --add-storage-directory and --add-server options
* New --add-storage-directory and --add-server options, which can be used to make keysafe backup/restore using additional locations. * Removed --store-local option; use --add-storage-directory instead. This commit was sponsored by Thomas Hochstein on Patreon.
Diffstat (limited to 'CmdLine.hs')
-rw-r--r--CmdLine.hs36
1 files changed, 27 insertions, 9 deletions
diff --git a/CmdLine.hs b/CmdLine.hs
index 702c97d..ef593a2 100644
--- a/CmdLine.hs
+++ b/CmdLine.hs
@@ -7,26 +7,27 @@ module CmdLine where
import Types
import Types.Storage
-import Types.Server (HostName)
+import Types.Server (HostName, Port)
import Types.Cost (Seconds(..))
+import Storage.Local
+import Storage.Network
import Tunables
import qualified Gpg
import Options.Applicative
import qualified Data.ByteString.UTF8 as BU8
import qualified Data.Text as T
import System.Directory
-import Network.Wai.Handler.Warp (Port)
data CmdLine = CmdLine
{ mode :: Maybe Mode
, secretkeysource :: Maybe SecretKeySource
- , localstorage :: Bool
, localstoragedirectory :: Maybe LocalStorageDirectory
, gui :: Bool
, testMode :: Bool
, customShareParams :: Maybe ShareParams
, name :: Maybe Name
, othername :: Maybe Name
+ , preferredStorage :: [Maybe LocalStorageDirectory -> Storage]
, serverConfig :: ServerConfig
, chaffMaxDelay :: Maybe Seconds
}
@@ -45,13 +46,13 @@ parse :: Parser CmdLine
parse = CmdLine
<$> optional parseMode
<*> optional (gpgswitch <|> fileswitch)
- <*> localstorageswitch
<*> optional localstoragedirectoryopt
<*> guiswitch
<*> testmodeswitch
<*> optional parseShareParams
<*> optional nameopt
<*> optional othernameopt
+ <*> many (addstoragedirectory <|> addserver)
<*> parseServerConfig
<*> optional chaffmaxdelayopt
where
@@ -65,14 +66,10 @@ parse = CmdLine
<> 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. (The default is to store data in the cloud.)"
- )
localstoragedirectoryopt = LocalStorageDirectory <$> option str
( long "store-directory"
<> metavar "DIR"
- <> help "Where to store data locally. (default: ~/.keysafe/objects/)"
+ <> help "Where to store data locally. For the client, data is stored here before it is uploaded to the server. For the server, this is where it stores its data. (default: ~/.keysafe/objects/)"
)
testmodeswitch = switch
( long "testmode"
@@ -97,6 +94,18 @@ parse = CmdLine
<> metavar "SECONDS"
<> help "Specify a delay between chaff uploads. Will delay a random amount between 0 and this many seconds."
)
+ addstoragedirectory = (\d _lsd -> localStorageOverride d)
+ <$> strOption
+ ( long "add-storage-directory"
+ <> metavar "DIR"
+ <> help "Add the directory to the list of locations keysafe will use for backup/restore of keys. Keysafe will use the directory first, before any of its built-in servers."
+ )
+ addserver = (\(h, p) lsd -> networkStorageOverride lsd h p)
+ <$> option hostPortOption
+ ( long "add-server"
+ <> metavar "HOST[:PORT]"
+ <> help "Add the server to the server list which keysafe will use for backup/restore of keys. Keysafe will use the server first before any of its built-in servers."
+ )
parseMode :: Parser Mode
parseMode =
@@ -226,3 +235,12 @@ secondsOption = Seconds . toRational <$> (auto :: ReadM Double)
nameOption :: ReadM Name
nameOption = Name . BU8.fromString <$> auto
+
+hostPortOption :: ReadM (HostName, Port)
+hostPortOption = eitherReader $ \s ->
+ case break (== ':') s of
+ ([], []) -> Left "need a hostname"
+ (h, ':':ps) -> case reads ps of
+ [(p, "")] -> Right (h, p)
+ _ -> Left $ "unable to parse port \"" ++ ps ++ "\""
+ (h, _) -> Right (h, 80)