diff options
Diffstat (limited to 'lib/Types.hs')
-rw-r--r-- | lib/Types.hs | 263 |
1 files changed, 263 insertions, 0 deletions
diff --git a/lib/Types.hs b/lib/Types.hs new file mode 100644 index 0000000..9aa0340 --- /dev/null +++ b/lib/Types.hs | |||
@@ -0,0 +1,263 @@ | |||
1 | {-# LANGUAGE DeriveFunctor #-} | ||
2 | module Types where | ||
3 | |||
4 | import Data.Map as Map (Map) | ||
5 | import Data.OpenPGP | ||
6 | import Data.OpenPGP.Util | ||
7 | import FunctorToMaybe | ||
8 | import qualified System.Posix.Types as Posix | ||
9 | import qualified Data.ByteString.Lazy as L | ||
10 | |||
11 | -- | This type describes an idempotent transformation (merge or import) on a | ||
12 | -- set of GnuPG keyrings and other key files. | ||
13 | data KeyRingOperation = KeyRingOperation | ||
14 | { opFiles :: Map InputFile StreamInfo | ||
15 | -- ^ Indicates files to be read or updated. | ||
16 | , opPassphrases :: [PassphraseSpec] | ||
17 | -- ^ Indicates files or file descriptors where passphrases can be found. | ||
18 | , opTransforms :: [Transform] | ||
19 | -- ^ Transformations to be performed on the key pool after all files have | ||
20 | -- been read and before any have been written. | ||
21 | , opHome :: Maybe FilePath | ||
22 | -- ^ If provided, this is the directory where the 'HomeSec' and 'HomePub' | ||
23 | -- files reside. Otherwise, the evironment variable $GNUPGHOME is consulted | ||
24 | -- and if that is not set, it falls back to $HOME/.gnupg. | ||
25 | } | ||
26 | deriving (Eq,Show) | ||
27 | |||
28 | data InputFile = HomeSec | ||
29 | -- ^ A file named secring.gpg located in the home directory. | ||
30 | -- See 'opHome'. | ||
31 | | HomePub | ||
32 | -- ^ A file named pubring.gpg located in the home directory. | ||
33 | -- See 'opHome'. | ||
34 | | ArgFile FilePath | ||
35 | -- ^ Contents will be read or written from the specified path. | ||
36 | | FileDesc Posix.Fd | ||
37 | -- ^ Contents will be read or written from the specified file | ||
38 | -- descriptor. | ||
39 | | Pipe Posix.Fd Posix.Fd | ||
40 | -- ^ Contents will be read from the first descriptor and updated | ||
41 | -- content will be writen to the second. Note: Don't use Pipe | ||
42 | -- for 'Wallet' files. (TODO: Wallet support) | ||
43 | | Generate Int GenerateKeyParams | ||
44 | -- ^ New key packets will be generated if there is no | ||
45 | -- matching content already in the key pool. The integer is | ||
46 | -- a unique id number so that multiple generations can be | ||
47 | -- inserted into 'opFiles' | ||
48 | deriving (Eq,Ord,Show) | ||
49 | |||
50 | -- | This type describes how 'runKeyRing' will treat a file. | ||
51 | data StreamInfo = StreamInfo | ||
52 | { access :: Access | ||
53 | -- ^ Indicates whether the file is allowed to contain secret information. | ||
54 | , typ :: FileType | ||
55 | -- ^ Indicates the format and content type of the file. | ||
56 | , fill :: KeyFilter | ||
57 | -- ^ This filter controls what packets will be inserted into a file. | ||
58 | , spill :: KeyFilter | ||
59 | -- | ||
60 | -- ^ Use this to indicate whether or not a file's contents should be | ||
61 | -- available for updating other files. Note that although its type is | ||
62 | -- 'KeyFilter', it is usually interpretted as a boolean flag. Details | ||
63 | -- depend on 'typ' and are as follows: | ||
64 | -- | ||
65 | -- 'KeyRingFile': | ||
66 | -- | ||
67 | -- * 'KF_None' - The file's contents will not be shared. | ||
68 | -- | ||
69 | -- * otherwise - The file's contents will be shared. | ||
70 | -- | ||
71 | -- 'PEMFile': | ||
72 | -- | ||
73 | -- * 'KF_None' - The file's contents will not be shared. | ||
74 | -- | ||
75 | -- * 'KF_Match' - The file's key will be shared with the specified owner | ||
76 | -- key and usage tag. If 'fill' is also a 'KF_Match', then it must be | ||
77 | -- equal to this value; changing the usage or owner of a key is not | ||
78 | -- supported via the fill/spill mechanism. | ||
79 | -- | ||
80 | -- * otherwise - Unspecified. Do not use. | ||
81 | -- | ||
82 | -- 'WalletFile': | ||
83 | -- | ||
84 | -- * The 'spill' setting is ignored and the file's contents are shared. | ||
85 | -- (TODO) | ||
86 | -- | ||
87 | -- 'Hosts': | ||
88 | -- | ||
89 | -- * The 'spill' setting is ignored and the file's contents are shared. | ||
90 | -- (TODO) | ||
91 | -- | ||
92 | , initializer :: Initializer | ||
93 | -- ^ If 'typ' is 'PEMFile' and an 'External' 'initializer' string is set, | ||
94 | -- then it is interpretted as a shell command that may be used to create | ||
95 | -- the key if it does not exist. | ||
96 | , transforms :: [Transform] | ||
97 | -- ^ Per-file transformations that occur before the contents of a file are | ||
98 | -- spilled into the common pool. | ||
99 | } | ||
100 | deriving (Eq,Show) | ||
101 | |||
102 | |||
103 | -- | This type is used to indicate where to obtain passphrases. | ||
104 | data PassphraseSpec = PassphraseSpec | ||
105 | { passSpecRingFile :: Maybe FilePath | ||
106 | -- ^ If not Nothing, the passphrase is to be used for packets | ||
107 | -- from this file. | ||
108 | , passSpecKeySpec :: Maybe String | ||
109 | -- ^ Non-Nothing value reserved for future use. | ||
110 | -- (TODO: Use this to implement per-key passphrase associations). | ||
111 | , passSpecPassFile :: InputFile | ||
112 | -- ^ The passphrase will be read from this file or file descriptor. | ||
113 | } | ||
114 | -- | Use this to carry pasphrases from a previous run. | ||
115 | | PassphraseMemoizer PacketTranscoder | ||
116 | | PassphraseAgent | ||
117 | |||
118 | instance Show PassphraseSpec where | ||
119 | show (PassphraseSpec a b c) = "PassphraseSpec "++show (a,b,c) | ||
120 | show (PassphraseMemoizer _) = "PassphraseMemoizer" | ||
121 | instance Eq PassphraseSpec where | ||
122 | PassphraseSpec a b c == PassphraseSpec d e f | ||
123 | = and [a==d,b==e,c==f] | ||
124 | _ == _ | ||
125 | = False | ||
126 | |||
127 | |||
128 | |||
129 | data Transform = | ||
130 | Autosign | ||
131 | -- ^ This operation will make signatures for any tor-style UID | ||
132 | -- that matches a tor subkey and thus can be authenticated without | ||
133 | -- requring the judgement of a human user. | ||
134 | -- | ||
135 | -- A tor-style UID is one of the following form: | ||
136 | -- | ||
137 | -- > Anonymous <root@HOSTNAME.onion> | ||
138 | | DeleteSubkeyByFingerprint String | ||
139 | -- ^ Delete the subkey specified by the given fingerprint and any | ||
140 | -- associated signatures on that key. | ||
141 | | DeleteSubkeyByUsage String | ||
142 | -- ^ Delete the subkey specified by the given fingerprint and any | ||
143 | -- associated signatures on that key. | ||
144 | deriving (Eq,Ord,Show) | ||
145 | |||
146 | -- | Use this type to indicate whether a file of type 'KeyRingFile' is expected | ||
147 | -- to contain secret or public PGP key packets. Note that it is not supported | ||
148 | -- to mix both in the same file and that the secret key packets include all of | ||
149 | -- the information contained in their corresponding public key packets. | ||
150 | data Access = AutoAccess -- ^ secret or public as appropriate based on existing content. | ||
151 | -- (see 'rtRingAccess') | ||
152 | | Sec -- ^ secret information | ||
153 | | Pub -- ^ public information | ||
154 | deriving (Eq,Ord,Show) | ||
155 | |||
156 | data FileType = KeyRingFile | ||
157 | | PEMFile | ||
158 | | WalletFile | ||
159 | | DNSPresentation | ||
160 | | Hosts | ||
161 | deriving (Eq,Ord,Enum,Show) | ||
162 | |||
163 | -- type UsageTag = String | ||
164 | data Initializer = NoCreate | Internal GenerateKeyParams | External String | ||
165 | deriving (Eq,Ord,Show) | ||
166 | |||
167 | |||
168 | |||
169 | type PacketTranscoder = (SymmetricAlgorithm,S2K) -> MappedPacket -> IO (KikiCondition Packet) | ||
170 | type PacketDecrypter = MappedPacket -> IO (KikiCondition Packet) | ||
171 | |||
172 | -- | Note that the documentation here is intended for when this value is | ||
173 | -- assigned to 'fill'. For other usage, see 'spill'. | ||
174 | data KeyFilter = KF_None -- ^ No keys will be imported. | ||
175 | | KF_Match String -- ^ Only the key that matches the spec will be imported. | ||
176 | | KF_Subkeys -- ^ Subkeys will be imported if their owner key is | ||
177 | -- already in the ring. TODO: Even if their signatures | ||
178 | -- are bad? | ||
179 | | KF_Authentic -- ^ Keys are imported if they belong to an authenticated | ||
180 | -- identity (signed or self-authenticating). | ||
181 | | KF_All -- ^ All keys will be imported. | ||
182 | deriving (Eq,Ord,Show) | ||
183 | |||
184 | -- | The position and acces a packet had before the operation | ||
185 | data OriginFlags = OriginFlags | ||
186 | { originallyPublic :: Bool | ||
187 | -- ^ false if SecretKeyPacket | ||
188 | , originalNum :: Int | ||
189 | -- ^ packets are numbered, starting from 1.. | ||
190 | } deriving Show | ||
191 | |||
192 | type OriginMap = Map FilePath OriginFlags | ||
193 | |||
194 | type MappedPacket = OriginMapped Packet | ||
195 | data OriginMapped a = MappedPacket | ||
196 | { packet :: a | ||
197 | , locations :: OriginMap | ||
198 | } deriving Show | ||
199 | instance Functor OriginMapped where | ||
200 | fmap f (MappedPacket x ls) = MappedPacket (f x) ls | ||
201 | |||
202 | -- | This type is used to indicate success or failure | ||
203 | -- and in the case of success, return the computed object. | ||
204 | -- The 'FunctorToMaybe' class is implemented to facilitate | ||
205 | -- branching on failture. | ||
206 | data KikiCondition a = KikiSuccess a | ||
207 | | FailedToLock [FilePath] | ||
208 | | BadPassphrase | ||
209 | | FailedToMakeSignature | ||
210 | | CantFindHome | ||
211 | | AmbiguousKeySpec FilePath | ||
212 | | CannotImportMasterKey | ||
213 | | NoWorkingKey | ||
214 | deriving ( Functor, Show ) | ||
215 | |||
216 | instance FunctorToMaybe KikiCondition where | ||
217 | functorToMaybe (KikiSuccess a) = Just a | ||
218 | functorToMaybe _ = Nothing | ||
219 | |||
220 | instance Applicative KikiCondition where | ||
221 | pure a = KikiSuccess a | ||
222 | f <*> a = | ||
223 | case functorToEither f of | ||
224 | Right f -> case functorToEither a of | ||
225 | Right a -> pure (f a) | ||
226 | Left err -> err | ||
227 | Left err -> err | ||
228 | |||
229 | data InputFileContext = InputFileContext | ||
230 | { homesecPath :: FilePath | ||
231 | , homepubPath :: FilePath | ||
232 | } | ||
233 | |||
234 | |||
235 | -- | The 'KeyKey'-type is used to store the information of a key | ||
236 | -- which is used for finger-printing and as a lookup key into | ||
237 | -- maps. This type may be changed to an actual fingerprint in | ||
238 | -- in the future. | ||
239 | type KeyKey = [L.ByteString] | ||
240 | |||
241 | keykey :: Packet -> KeyKey | ||
242 | keykey key = | ||
243 | -- Note: The key's timestamp is normally included in it's fingerprint. | ||
244 | -- This is undesirable for kiki because it causes the same | ||
245 | -- key to be imported multiple times and show as apparently | ||
246 | -- distinct keys with different fingerprints. | ||
247 | -- Thus, we will remove the timestamp. | ||
248 | fingerprint_material (key {timestamp=0}) -- TODO: smaller key? | ||
249 | |||
250 | isKey :: Packet -> Bool | ||
251 | isKey (PublicKeyPacket {}) = True | ||
252 | isKey (SecretKeyPacket {}) = True | ||
253 | isKey _ = False | ||
254 | |||
255 | isUserID :: Packet -> Bool | ||
256 | isUserID (UserIDPacket {}) = True | ||
257 | isUserID _ = False | ||
258 | |||
259 | isTrust :: Packet -> Bool | ||
260 | isTrust (TrustPacket {}) = True | ||
261 | isTrust _ = False | ||
262 | |||
263 | |||