summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
blob: b4d68f4908dd63a683bc0c89091bf386cbb03030 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
{-# 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)