summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-06 17:35:10 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-06 17:35:10 -0400
commit7192abc5d53aa5a6ee609ed30bd05f1575e67b65 (patch)
tree2f1d17f27b483a8deec001a12a55696b0eea5978 /Types.hs
parentfbd0bb3a2b2541e897708fb441ab1c8a2b5ab78e (diff)
downloadkeysafe-7192abc5d53aa5a6ee609ed30bd05f1575e67b65.tar.gz
some basic data types and expensive hashing
Diffstat (limited to 'Types.hs')
-rw-r--r--Types.hs78
1 files changed, 78 insertions, 0 deletions
diff --git a/Types.hs b/Types.hs
new file mode 100644
index 0000000..2be82a8
--- /dev/null
+++ b/Types.hs
@@ -0,0 +1,78 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Types where
+
+import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as B8
+import Raaz.Core.Encode
+import Data.Monoid
+import Data.Word
+import Data.Time.Clock
+import Text.Read
+
+-- | A password used to encrypt a key stored in keysafe.
+newtype Password = Password B.ByteString
+
+-- | A name associated with a key stored in keysafe.
+newtype Name = Name B.ByteString
+ deriving (Show)
+
+-- | The type of the key that is stored in keysafe.
+newtype KeyType = KeyType B.ByteString
+ deriving (Show)
+
+gpgKey :: KeyType
+gpgKey = KeyType "gpg"
+
+-- | Enough information to uniquely identify a key stored in keysafe.
+data KeyIdent = KeyIdent KeyType Name
+ deriving (Show)
+
+-- | A KeyIdent is serialized in the form "keytype name".
+-- For example "gpg Joey Hess"
+instance Encodable KeyIdent where
+ toByteString (KeyIdent (KeyType t) (Name n)) =
+ t <> B.singleton identSepChar <> n
+ fromByteString b = case B.break (== identSepChar) b of
+ (t, n)
+ | B.null n -> Nothing
+ | otherwise -> Just $
+ KeyIdent (KeyType t) (Name (B.drop 1 n))
+
+identSepChar :: Word8
+identSepChar = 32
+
+newtype ShardNum = ShardNum Int
+ deriving (Show)
+
+-- | Enough information to uniquely identify an object stored on a keysafe
+-- server for a key.
+data ObjectIdent = ObjectIdent ShardNum KeyIdent
+ deriving (Show)
+
+-- | An ObjectIdent is serialied in the form "shardnum keytype name"
+-- For example "1 gpg Joey Hess"
+instance Encodable ObjectIdent where
+ toByteString (ObjectIdent (ShardNum n) keyident) =
+ B8.pack (show n) <> B.singleton identSepChar <> toByteString keyident
+ fromByteString b = case B.break (== identSepChar) b of
+ (ns, rest)
+ | B.null ns -> Nothing
+ | otherwise -> do
+ keyident <- fromByteString (B.drop 1 rest)
+ n <- readMaybe (B8.unpack ns)
+ return $ ObjectIdent (ShardNum n) keyident
+
+-- | An estimated cost to perform an operation.
+data Cost = CPUCost Seconds | GPUCost Seconds
+ deriving (Show)
+
+newtype Seconds = Seconds NominalDiffTime
+ deriving (Show)
+
+data Benchmark t = Benchmark { expectedBenchmark :: t, actualBenchmark :: t }
+ deriving (Show)
+
+-- | In testing mode, the cryptographic difficulty is dialed back.
+data RunMode = SecureMode | TestingMode
+ deriving (Show)