summaryrefslogtreecommitdiffhomepage
path: root/BackupRecord.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-09-14 16:42:26 -0400
committerJoey Hess <joeyh@joeyh.name>2016-09-14 16:59:20 -0400
commita41cbda751d515032859d72656fda3d219300ecb (patch)
treefdc5324c56e0b67b6e74826cd6b8cd742984ecf0 /BackupRecord.hs
parenta68caf8b54b9d37deeaeddc6a28394d1587f1dc5 (diff)
downloadkeysafe-a41cbda751d515032859d72656fda3d219300ecb.tar.gz
Store information about backed up keys in ~/.keysafe/backup.log
This can be deleted by the user at any time, but it's useful in case a server is known to be compromised, or a problem is found with keysafe's implementation that makes a backup insecure. This commit was sponsored by Nick Daly on Patreon.
Diffstat (limited to 'BackupRecord.hs')
-rw-r--r--BackupRecord.hs79
1 files changed, 79 insertions, 0 deletions
diff --git a/BackupRecord.hs b/BackupRecord.hs
new file mode 100644
index 0000000..39e07fa
--- /dev/null
+++ b/BackupRecord.hs
@@ -0,0 +1,79 @@
+{- Copyright 2016 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
+{-# LANGUAGE DeriveGeneric, BangPatterns #-}
+
+module BackupRecord where
+
+import Types
+import Types.Cost
+import Types.Server
+import GHC.Generics
+import Data.Time.Clock.POSIX
+import Data.Aeson
+import Data.Maybe
+import System.FilePath
+import System.Directory
+import System.Posix.User
+import System.Posix.Files
+import qualified Data.ByteString.Lazy as B
+
+-- | Record 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.
+--
+-- That's why the Name used is not included; as knowing the name lets
+-- an attacker download shards and start password cracking.
+--
+-- 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 :: [HostName]
+ , secretKeySource :: String
+ , passwordEntropy :: Int
+ } deriving (Show, Generic)
+
+-- BackupRecord is serialized as JSON.
+instance ToJSON BackupRecord
+instance FromJSON BackupRecord
+
+mkBackupRecord :: [Server] -> SecretKeySource -> Entropy UnknownPassword -> IO BackupRecord
+mkBackupRecord servers sks (Entropy n) = BackupRecord
+ <$> getPOSIXTime
+ <*> pure (map serverName servers)
+ <*> pure (show sks)
+ <*> pure n
+
+backupRecordFile :: IO FilePath
+backupRecordFile = do
+ u <- getUserEntryForID =<< getEffectiveUserID
+ return $ homeDirectory u </> ".keysafe/backup.log"
+
+readBackupRecords :: IO [BackupRecord]
+readBackupRecords = do
+ f <- backupRecordFile
+ e <- doesFileExist f
+ if e
+ then fromMaybe [] . decode <$> B.readFile f
+ else return []
+
+storeBackupRecord :: BackupRecord -> IO ()
+storeBackupRecord r = do
+ !rs <- readBackupRecords
+ f <- backupRecordFile
+ let d = takeDirectory f
+ createDirectoryIfMissing True d
+ setFileMode d $
+ ownerReadMode
+ `unionFileModes` ownerWriteMode
+ `unionFileModes` ownerExecuteMode
+ setPermissions d
+ $ setOwnerReadable True
+ $ setOwnerWritable True
+ $ setOwnerExecutable True emptyPermissions
+ B.writeFile f $ encode (r:rs)