summaryrefslogtreecommitdiffhomepage
path: root/keysafe.hs
blob: 32361ab4ec2d9d822757aa323b249dac8d17b109 (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
{-# LANGUAGE OverloadedStrings #-}

{- Copyright 2016 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module Main where

import Types
import Tunables
import Encryption
import Shard
import Raaz.Core.Encode
import System.IO
import System.Posix.ByteString
import qualified Data.ByteString as B
import Control.DeepSeq

main :: IO ()
main = do
	storedemo
	retrievedemo

storedemo :: IO ()
storedemo = do
	kek <- genKeyEncryptionKey tunables name password
	let esk = encrypt kek secretkey
	let sis = shardIdents tunables name keyid
	shards <- genShards esk tunables
	mapM_ (uncurry storeShard) (zip (getIdents sis) shards)
  where
	password = Password "foo"
	name = Name "bar"
	tunables = testModeTunables -- defaultTunables
	keyid = KeyId gpgKey "foobar"
	secretkey = SecretKey "this is a gpg private key"

retrievedemo :: IO ()
retrievedemo = do
	let sis = shardIdents tunables name keyid
	-- we drop 1 to simulate not getting all shards from the servers
	let l = drop 1 $ zip [1..] (getIdents sis)
	shards <- mapM (uncurry retrieveShard) l
	let esk = combineShards tunables shards
	kek <- genKeyEncryptionKey tunables name password
	-- TODO: need to solve the encryption puzzle
	case decrypt kek esk of
		Just (SecretKey sk) -> print sk
		Nothing -> print ("Failed" :: String, esk)
  where
	password = Password "foo"
	name = Name "bar"
	tunables = testModeTunables -- defaultTunables
	keyid = KeyId gpgKey "foobar"

storeShard :: StorableObjectIdent -> Shard -> IO ()
storeShard i s = do
	print $ toByteString i
	fd <- openFd (toByteString i) WriteOnly (Just 0o666)
		(defaultFileFlags { exclusive = True } )
	h <- fdToHandle fd
	B.hPut h (toByteString s)
	hClose h

retrieveShard :: Int -> StorableObjectIdent -> IO Shard
retrieveShard n i = do
	fd <- openFd (toByteString i) ReadOnly Nothing defaultFileFlags
	h <- fdToHandle fd
	b <- B.hGetContents h
	b `deepseq` hClose h
	return (Shard n (StorableObject b))