summaryrefslogtreecommitdiff
path: root/src/Propellor/Gpg.hs
blob: 60b0d52d0c9836d77b30c92f062d49999a393b71 (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
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
module Propellor.Gpg where

import Control.Applicative
import System.IO
import System.FilePath
import System.Directory
import Data.Maybe
import Data.List.Utils
import Control.Monad

import Propellor.PrivData.Paths
import Propellor.Message
import Utility.SafeCommand
import Utility.Process
import Utility.Monad
import Utility.Misc
import Utility.Tmp
import Utility.FileSystemEncoding

type KeyId = String

keyring :: FilePath
keyring = privDataDir </> "keyring.gpg"

-- Lists the keys in propellor's keyring.
listPubKeys :: IO [KeyId]
listPubKeys = parse . lines <$> readProcess "gpg" listopts
  where
	listopts = useKeyringOpts ++ ["--with-colons", "--list-public-keys"]
	parse = mapMaybe (keyIdField . split ":")
	keyIdField ("pub":_:_:_:f:_) = Just f
	keyIdField _ = Nothing

useKeyringOpts :: [String]
useKeyringOpts =
	[ "--options"
	, "/dev/null"
	, "--no-default-keyring"
	, "--keyring", keyring
	]

addKey :: KeyId -> IO ()
addKey keyid = exitBool =<< allM (uncurry actionMessage)
	[ ("adding key to propellor's keyring", addkeyring)
	, ("staging propellor's keyring", gitAdd keyring)
	, ("updating encryption of any privdata", reencryptPrivData)
	, ("configuring git commit signing to use key", gitconfig)
	, ("committing changes", gitCommitKeyRing "add-key")
	]
  where
	addkeyring = do
		createDirectoryIfMissing True privDataDir
		boolSystem "sh"
			[ Param "-c"
			, Param $ "gpg --export " ++ keyid ++ " | gpg " ++
				unwords (useKeyringOpts ++ ["--import"])
			]

	gitconfig = ifM (snd <$> processTranscript "gpg" ["--list-secret-keys", keyid] Nothing)
		( boolSystem "git"
			[ Param "config"
			, Param "user.signingkey"
			, Param keyid
			]
		, do
			warningMessage $ "Cannot find a secret key for key " ++ keyid ++ ", so not configuring git user.signingkey to use this key."
			return True
		)

rmKey :: KeyId -> IO ()
rmKey keyid = exitBool =<< allM (uncurry actionMessage)
	[ ("removing key from propellor's keyring", rmkeyring)
	, ("staging propellor's keyring", gitAdd keyring)
	, ("updating encryption of any privdata", reencryptPrivData)
	, ("configuring git commit signing to not use key", gitconfig)
	, ("committing changes", gitCommitKeyRing "rm-key")
	]
  where
	rmkeyring = boolSystem "gpg" $
		(map Param useKeyringOpts) ++ 
		[ Param "--batch"
		, Param "--yes"
		, Param "--delete-key", Param keyid
		]
	
	gitconfig = ifM ((==) (keyid++"\n", True) <$> processTranscript "git" ["config", "user.signingkey"] Nothing)
		( boolSystem "git"
			[ Param "config"
			, Param "--unset"
			, Param "user.signingkey"
			]
		, return True
		)	

reencryptPrivData :: IO Bool
reencryptPrivData = ifM (doesFileExist privDataFile)
	( do
		gpgEncrypt privDataFile =<< gpgDecrypt privDataFile
		gitAdd privDataFile
	, return True
	)
	
gitAdd :: FilePath -> IO Bool
gitAdd f = boolSystem "git"
	[ Param "add"
	, File f
	]

gitCommitKeyRing :: String -> IO Bool
gitCommitKeyRing action = do
	-- Commit explicitly the keyring and privdata files, as other
	-- changes may be staged by the user and shouldn't be committed.
	tocommit <- filterM doesFileExist [ privDataFile, keyring]
	gitCommit $ (map File tocommit) ++ 
		[ Param "-m"
		, Param ("propellor " ++ action)
		]

-- Adds --gpg-sign if there's a keyring.
gpgSignParams :: [CommandParam] -> IO [CommandParam]
gpgSignParams ps = ifM (doesFileExist keyring)
	( return (ps ++ [Param "--gpg-sign"])
	, return ps
	)

-- Automatically sign the commit if there'a a keyring.
gitCommit :: [CommandParam] -> IO Bool
gitCommit ps = do
	ps' <- gpgSignParams ps
	boolSystem "git" (Param "commit" : ps')

gpgDecrypt :: FilePath -> IO String
gpgDecrypt f = ifM (doesFileExist f)
	( writeReadProcessEnv "gpg" ["--decrypt", f] Nothing Nothing (Just fileEncoding)
	, return ""
	)

-- Encrypt file to all keys in propellor's keyring.
gpgEncrypt :: FilePath -> String -> IO ()
gpgEncrypt f s = do
	keyids <- listPubKeys
	let opts =
		[ "--default-recipient-self"
		, "--armor"
		, "--encrypt"
		, "--trust-model", "always"
		] ++ concatMap (\k -> ["--recipient", k]) keyids
	encrypted <- writeReadProcessEnv "gpg" opts Nothing (Just writer) Nothing
	viaTmp writeFile f encrypted
  where
	writer h = do
		fileEncoding h
		hPutStr h s