summaryrefslogtreecommitdiffhomepage
path: root/Serialization.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-07 18:49:15 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-07 18:51:09 -0400
commit07bd29a80ed36c63296214af34689d0cce14751f (patch)
treec22aa59dde551c5fb7f54f26e406c70dc441171f /Serialization.hs
parent6f2d6120533070ce48bbc1e12465d1f7d603aec8 (diff)
downloadkeysafe-07bd29a80ed36c63296214af34689d0cce14751f.tar.gz
reorg, and working on serialization
Diffstat (limited to 'Serialization.hs')
-rw-r--r--Serialization.hs46
1 files changed, 46 insertions, 0 deletions
diff --git a/Serialization.hs b/Serialization.hs
new file mode 100644
index 0000000..3c23137
--- /dev/null
+++ b/Serialization.hs
@@ -0,0 +1,46 @@
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
+module Serialization where
+
+import Types
+import Raaz.Core.Encode
+import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as B8
+import Data.Monoid
+import Data.Word
+import Text.Read
+
+-- 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 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))
+
+-- | 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
+
+identSepChar :: Word8
+identSepChar = 32