summaryrefslogtreecommitdiffhomepage
path: root/Serialization.hs
blob: 172c6f9063a8ff8723aee86626654ac4022c6b00 (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
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE OverloadedStrings #-}

module Serialization where

import Types
import Cost
import Raaz.Core.Encode
import qualified Crypto.Argon2 as Argon2
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Monoid
import Data.Word
import Text.Read

instance Encodable ExpensiveHashTunable where
	toByteString (UseArgon2 o _) = B.intercalate (B.singleton sepChar)
		[ showb (Argon2.hashIterations o)
		, showb (Argon2.hashMemory o)
		, showb (Argon2.hashParallelism o)
		, case Argon2.hashVariant o of
			Argon2.Argon2i -> "argon2i"
			Argon2.Argon2d -> "argon2d"
		]
	  where
		showb = B8.pack . show
	fromByteString b = case B.split sepChar b of
		(i:m:p:v:[]) -> do
			o <- Argon2.HashOptions
				<$> readb i
				<*> readb m
				<*> readb p
				<*> case v of
					"argon2i" -> return Argon2.Argon2i
					"argon2d" -> return Argon2.Argon2d
					_ -> Nothing
			return $ UseArgon2 o unknownCost
		_ -> Nothing
	  where
		readb = readMaybe . B8.unpack

instance Encodable EncryptionTunable where
	toByteString UseAES256 = "AES"
	fromByteString "AES" = Just UseAES256
	fromByteString _  = Nothing

instance Encodable DecryptionPuzzleTunable where
	toByteString (KeyBlindingLeftSide _) = ">"
	fromByteString ">" = Just (KeyBlindingLeftSide unknownCost)
	fromByteString _  = Nothing

-- TODO
-- | An EncryptedSecretKey is serialized as first a md5sum of the rest
-- of the content, and then a SelfDescription EncryptedSecretKey,
-- and finally the 
--instance Encodable EncryptedSecretKey where
--	toByteString (EncryptedSecretKey b _) = b
--	fromByteString b = 

-- | 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 sepChar <> n
	fromByteString b = case B.break (== sepChar) b of
		(t, n)
			| B.null n -> Nothing
			| otherwise -> Just $
				KeyIdent (KeyType t) (Name (B.drop 1 n))

-- | 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 sepChar <> toByteString keyident
	fromByteString b = case B.break (== sepChar) 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

sepChar :: Word8
sepChar = 32