summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--BackupLog.hs (renamed from BackupRecord.hs)62
-rw-r--r--keysafe.cabal2
-rw-r--r--keysafe.hs6
3 files changed, 40 insertions, 30 deletions
diff --git a/BackupRecord.hs b/BackupLog.hs
index 88a9b68..8e48bcd 100644
--- a/BackupRecord.hs
+++ b/BackupLog.hs
@@ -5,11 +5,11 @@
{-# LANGUAGE DeriveGeneric, BangPatterns #-}
-module BackupRecord where
+module BackupLog where
import Types
-import Types.Cost
import Types.Server
+import Types.Cost
import Utility.UserInfo
import GHC.Generics
import Data.Time.Clock.POSIX
@@ -20,7 +20,13 @@ import System.Directory
import System.Posix.Files
import qualified Data.ByteString.Lazy as B
--- | Record of a backup.
+data BackupLog = BackupLog POSIXTime BackupEvent
+ deriving (Show, Generic)
+
+instance ToJSON BackupLog
+instance FromJSON BackupLog
+
+-- | Log of a backup.
--
-- If an attacker cracks the user's system and finds this stored
-- on it, it should not help them recover keys from keysafe.
@@ -31,41 +37,45 @@ import qualified Data.ByteString.Lazy as B
-- Including the password entropy does let an attacker avoid trying
-- weak passwords and go right to passwords that are strong enough, but
-- this should only half the password crack time at worst.
-data BackupRecord = BackupRecord
- { backupDate :: POSIXTime
- , backupServers :: [ServerName]
- , secretKeySource :: SecretKeySource
- , passwordEntropy :: Int
- } deriving (Show, Generic)
+data BackupEvent = BackupSkipped SecretKeySource | BackupMade
+ { backupServers :: [ServerName]
+ , backupSecretKeySource :: SecretKeySource
+ , backupPasswordEntropy :: Int
+ }
+ deriving (Show, Generic)
--- BackupRecord is serialized as JSON.
-instance ToJSON BackupRecord
-instance FromJSON BackupRecord
+instance ToJSON BackupEvent
+instance FromJSON BackupEvent
-mkBackupRecord :: [Server] -> SecretKeySource -> Entropy UnknownPassword -> IO BackupRecord
-mkBackupRecord servers sks (Entropy n) = BackupRecord
+mkBackupLog :: BackupEvent -> IO BackupLog
+mkBackupLog evt = BackupLog
<$> getPOSIXTime
- <*> pure (map serverName servers)
- <*> pure sks
- <*> pure n
+ <*> pure evt
+
+backupMade :: [Server] -> SecretKeySource -> Entropy UnknownPassword -> BackupEvent
+backupMade servers sks (Entropy n) = BackupMade
+ { backupServers = map serverName servers
+ , backupSecretKeySource = sks
+ , backupPasswordEntropy = n
+ }
-backupRecordFile :: IO FilePath
-backupRecordFile = do
+backupLogFile :: IO FilePath
+backupLogFile = do
home <- myHomeDir
return $ home </> ".keysafe/backup.log"
-readBackupRecords :: IO [BackupRecord]
-readBackupRecords = do
- f <- backupRecordFile
+readBackupLogs :: IO [BackupLog]
+readBackupLogs = do
+ f <- backupLogFile
e <- doesFileExist f
if e
then fromMaybe [] . decode <$> B.readFile f
else return []
-storeBackupRecord :: BackupRecord -> IO ()
-storeBackupRecord r = do
- !rs <- readBackupRecords
- f <- backupRecordFile
+storeBackupLog :: BackupLog -> IO ()
+storeBackupLog r = do
+ !rs <- readBackupLogs
+ f <- backupLogFile
let d = takeDirectory f
createDirectoryIfMissing True d
setFileMode d $
diff --git a/keysafe.cabal b/keysafe.cabal
index dc90e3c..02622b7 100644
--- a/keysafe.cabal
+++ b/keysafe.cabal
@@ -78,7 +78,7 @@ Executable keysafe
Extra-Libraries: argon2
Other-Modules:
AutoStart
- BackupRecord
+ BackupLog
Benchmark
ByteStrings
Crypto.Argon2.FFI
diff --git a/keysafe.hs b/keysafe.hs
index 6d5186a..7fe27cf 100644
--- a/keysafe.hs
+++ b/keysafe.hs
@@ -19,7 +19,7 @@ import Cost
import SecretKey
import Share
import Storage
-import BackupRecord
+import BackupLog
import AutoStart
import HTTP.Server
import ServerBackup
@@ -114,10 +114,10 @@ backup cmdline storagelocations ui tunables secretkeysource secretkey = do
_ <- sis `seq` addpercent 25
let step = 50 `div` sum (map S.size shares)
storeShares storagelocations sis shares (addpercent step)
- backuprecord <- mkBackupRecord (mapMaybe getServer locs) secretkeysource passwordentropy
+ backuplog <- mkBackupLog $ backupMade (mapMaybe getServer locs) secretkeysource passwordentropy
case r of
StoreSuccess -> do
- storeBackupRecord backuprecord
+ storeBackupLog backuplog
if queued
then do
willautostart <- isAutoStartFileInstalled