propellor/src/Propellor/PrivData.hs

92 lines
2.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE PackageImports #-}
2014-03-31 03:37:54 +00:00
module Propellor.PrivData where
2014-03-30 23:11:24 +00:00
import qualified Data.Map as M
import Control.Applicative
import System.FilePath
import System.IO
import System.Directory
import Data.Maybe
2014-04-13 16:57:35 +00:00
import Data.List
2014-03-30 23:11:24 +00:00
import Control.Monad
import "mtl" Control.Monad.Reader
2014-03-30 23:11:24 +00:00
2014-03-31 03:37:54 +00:00
import Propellor.Types
2014-04-11 01:09:20 +00:00
import Propellor.Attr
2014-03-31 22:31:08 +00:00
import Propellor.Message
2014-03-30 23:11:24 +00:00
import Utility.Monad
import Utility.PartialPrelude
import Utility.Exception
import Utility.Process
import Utility.Tmp
import Utility.SafeCommand
2014-03-31 01:01:18 +00:00
import Utility.Misc
2014-03-30 23:11:24 +00:00
2014-04-11 06:03:51 +00:00
-- | When the specified PrivDataField is available on the host Propellor
-- is provisioning, it provies the data to the action. Otherwise, it prints
-- a message to help the user make the necessary private data available.
withPrivData :: PrivDataField -> (String -> Propellor Result) -> Propellor Result
withPrivData field a = maybe missing a =<< liftIO (getPrivData field)
2014-03-30 23:11:24 +00:00
where
missing = do
host <- getHostName
2014-04-13 16:57:35 +00:00
let host' = if ".docker" `isSuffixOf` host
then "$parent_host"
else host
liftIO $ do
warningMessage $ "Missing privdata " ++ show field
2014-04-13 16:57:35 +00:00
putStrLn $ "Fix this by running: propellor --set "++host'++" '" ++ show field ++ "'"
return FailedChange
2014-03-30 23:11:24 +00:00
getPrivData :: PrivDataField -> IO (Maybe String)
getPrivData field = do
m <- catchDefaultIO Nothing $ readish <$> readFile privDataLocal
return $ maybe Nothing (M.lookup field) m
2014-03-31 01:01:18 +00:00
setPrivData :: HostName -> PrivDataField -> IO ()
setPrivData host field = do
putStrLn "Enter private data on stdin; ctrl-D when done:"
2014-04-01 22:42:32 +00:00
value <- chomp <$> hGetContentsStrict stdin
2014-03-30 23:19:29 +00:00
makePrivDataDir
2014-03-30 23:11:24 +00:00
let f = privDataFile host
m <- fromMaybe M.empty . readish <$> gpgDecrypt f
let m' = M.insert field value m
gpgEncrypt f (show m')
2014-03-31 01:01:18 +00:00
putStrLn "Private data set."
2014-03-30 23:11:24 +00:00
void $ boolSystem "git" [Param "add", File f]
2014-04-01 22:42:32 +00:00
where
chomp s
| end s == "\n" = chomp (beginning s)
| otherwise = s
2014-03-30 23:11:24 +00:00
2014-03-30 23:19:29 +00:00
makePrivDataDir :: IO ()
makePrivDataDir = createDirectoryIfMissing False privDataDir
2014-03-30 23:11:24 +00:00
privDataDir :: FilePath
privDataDir = "privdata"
privDataFile :: HostName -> FilePath
privDataFile host = privDataDir </> host ++ ".gpg"
privDataLocal :: FilePath
privDataLocal = privDataDir </> "local"
gpgDecrypt :: FilePath -> IO String
gpgDecrypt f = ifM (doesFileExist f)
( readProcess "gpg" ["--decrypt", f]
, return ""
)
gpgEncrypt :: FilePath -> String -> IO ()
gpgEncrypt f s = do
encrypted <- writeReadProcessEnv "gpg"
[ "--default-recipient-self"
, "--armor"
, "--encrypt"
]
Nothing
(Just $ flip hPutStr s)
Nothing
viaTmp writeFile f encrypted