{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances #-} module Types where import Cost import Entropy import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy as BL import Raaz.Core.Encode import Data.Monoid import Data.Word import Data.Time.Clock import Data.String import Text.Read -- | keysafe stores secret keys. newtype SecretKey = SecretKey B.ByteString -- | The secret key, encrypted with a password. data EncryptedSecretKey = EncryptedSecretKey B.ByteString (CostCalc BruteForceOp UnknownPassword) instance Bruteforceable EncryptedSecretKey UnknownPassword where getBruteCostCalc (EncryptedSecretKey _ cc) = cc -- | An object that can be stored on a keysafe server. data StorableObject = StorableObject BL.ByteString -- | A password used to encrypt a key stored in keysafe. newtype Password = Password B.ByteString deriving (IsString) -- | Naive calculation of the entropy of a password. -- Does not take common passwords and password generation patterns into -- account, so this is an overestimation of how hard a password -- is to crack. passwordEntropy :: Password -> Entropy UnknownPassword passwordEntropy (Password p) = Entropy $ floor $ totalEntropy p -- | 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 data Benchmark t = Benchmark { expectedBenchmark :: t, actualBenchmark :: t } deriving (Show)