2014-04-10 21:22:32 +00:00
|
|
|
{-# LANGUAGE PackageImports #-}
|
|
|
|
|
2014-03-31 03:37:54 +00:00
|
|
|
module Propellor.PrivData where
|
2014-03-30 23:11:24 +00:00
|
|
|
|
|
|
|
import Control.Applicative
|
|
|
|
import System.FilePath
|
|
|
|
import System.IO
|
|
|
|
import System.Directory
|
|
|
|
import Data.Maybe
|
2014-07-06 19:56:56 +00:00
|
|
|
import Data.Monoid
|
2014-07-06 20:44:13 +00:00
|
|
|
import Data.List
|
2014-03-30 23:11:24 +00:00
|
|
|
import Control.Monad
|
2014-06-19 18:41:55 +00:00
|
|
|
import Control.Monad.IfElse
|
2014-04-10 21:22:32 +00:00
|
|
|
import "mtl" Control.Monad.Reader
|
2014-07-06 19:56:56 +00:00
|
|
|
import qualified Data.Map as M
|
|
|
|
import qualified Data.Set as S
|
2014-03-30 23:11:24 +00:00
|
|
|
|
2014-03-31 03:37:54 +00:00
|
|
|
import Propellor.Types
|
2014-07-06 19:56:56 +00:00
|
|
|
import Propellor.Types.Info
|
2014-03-31 22:31:08 +00:00
|
|
|
import Propellor.Message
|
2014-07-06 21:54:06 +00:00
|
|
|
import Propellor.Info
|
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-06-19 18:41:55 +00:00
|
|
|
import Utility.FileMode
|
|
|
|
import Utility.Env
|
2014-07-06 20:32:05 +00:00
|
|
|
import Utility.Table
|
2014-03-30 23:11:24 +00:00
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
-- | Allows a Property to access the value of a specific PrivDataField,
|
|
|
|
-- for use in a specific Context.
|
|
|
|
--
|
|
|
|
-- Example use:
|
|
|
|
--
|
|
|
|
-- > withPrivData (PrivFile pemfile) (Context "joeyh.name") $ \getdata ->
|
|
|
|
-- > property "joeyh.name ssl cert" $ getdata $ \privdata ->
|
|
|
|
-- > liftIO $ writeFile pemfile privdata
|
|
|
|
-- > where pemfile = "/etc/ssl/certs/web.pem"
|
|
|
|
--
|
|
|
|
-- Note that if the value is not available, the action is not run
|
|
|
|
-- and instead it prints a message to help the user make the necessary
|
|
|
|
-- private data available.
|
2014-07-06 21:15:27 +00:00
|
|
|
--
|
|
|
|
-- The resulting Property includes Info about the PrivDataField
|
|
|
|
-- being used, which is necessary to ensure that the privdata is sent to
|
|
|
|
-- the remote host by propellor.
|
2014-07-06 19:56:56 +00:00
|
|
|
withPrivData
|
|
|
|
:: PrivDataField
|
|
|
|
-> Context
|
|
|
|
-> (((PrivData -> Propellor Result) -> Propellor Result) -> Property)
|
|
|
|
-> Property
|
|
|
|
withPrivData field context@(Context cname) mkprop = addinfo $ mkprop $ \a ->
|
|
|
|
maybe missing a =<< liftIO (getLocalPrivData field context)
|
|
|
|
where
|
|
|
|
missing = liftIO $ do
|
|
|
|
warningMessage $ "Missing privdata " ++ show field ++ " (for " ++ cname ++ ")"
|
|
|
|
putStrLn $ "Fix this by running: propellor --set '" ++ show field ++ "' '" ++ cname ++ "'"
|
|
|
|
return FailedChange
|
|
|
|
addinfo p = p { propertyInfo = propertyInfo p <> mempty { _privDataFields = S.singleton (field, context) } }
|
|
|
|
|
2014-07-06 21:54:06 +00:00
|
|
|
addPrivDataField :: (PrivDataField, Context) -> Property
|
|
|
|
addPrivDataField v = pureInfoProperty (show v) $
|
|
|
|
mempty { _privDataFields = S.singleton v }
|
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
{- Gets the requested field's value, in the specified context if it's
|
|
|
|
- available, from the host's local privdata cache. -}
|
|
|
|
getLocalPrivData :: PrivDataField -> Context -> IO (Maybe PrivData)
|
|
|
|
getLocalPrivData field context =
|
|
|
|
getPrivData field context . fromMaybe M.empty <$> localcache
|
2014-03-30 23:11:24 +00:00
|
|
|
where
|
2014-07-06 19:56:56 +00:00
|
|
|
localcache = catchDefaultIO Nothing $ readish <$> readFile privDataLocal
|
|
|
|
|
2014-07-06 23:40:03 +00:00
|
|
|
type PrivMap = M.Map (PrivDataField, Context) PrivData
|
|
|
|
|
2014-07-06 21:37:10 +00:00
|
|
|
{- Get only the set of PrivData that the Host's Info says it uses. -}
|
|
|
|
filterPrivData :: Host -> PrivMap -> PrivMap
|
|
|
|
filterPrivData host = M.filterWithKey (\k _v -> S.member k used)
|
|
|
|
where
|
|
|
|
used = _privDataFields $ hostInfo host
|
|
|
|
|
|
|
|
getPrivData :: PrivDataField -> Context -> PrivMap -> Maybe PrivData
|
2014-07-06 19:56:56 +00:00
|
|
|
getPrivData field context = M.lookup (field, context)
|
|
|
|
|
|
|
|
setPrivData :: PrivDataField -> Context -> IO ()
|
|
|
|
setPrivData field context = do
|
2014-03-31 01:01:18 +00:00
|
|
|
putStrLn "Enter private data on stdin; ctrl-D when done:"
|
2014-07-06 19:56:56 +00:00
|
|
|
setPrivDataTo field context =<< hGetContentsStrict stdin
|
2014-06-19 18:41:55 +00:00
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
dumpPrivData :: PrivDataField -> Context -> IO ()
|
|
|
|
dumpPrivData field context =
|
2014-06-19 18:41:55 +00:00
|
|
|
maybe (error "Requested privdata is not set.") putStrLn
|
2014-07-06 19:56:56 +00:00
|
|
|
=<< (getPrivData field context <$> decryptPrivData)
|
2014-06-19 18:41:55 +00:00
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
editPrivData :: PrivDataField -> Context -> IO ()
|
|
|
|
editPrivData field context = do
|
|
|
|
v <- getPrivData field context <$> decryptPrivData
|
2014-06-19 18:41:55 +00:00
|
|
|
v' <- withTmpFile "propellorXXXX" $ \f h -> do
|
|
|
|
hClose h
|
|
|
|
maybe noop (writeFileProtected f) v
|
|
|
|
editor <- getEnvDefault "EDITOR" "vi"
|
|
|
|
unlessM (boolSystem editor [File f]) $
|
|
|
|
error "Editor failed; aborting."
|
|
|
|
readFile f
|
2014-07-06 19:56:56 +00:00
|
|
|
setPrivDataTo field context v'
|
2014-06-19 18:41:55 +00:00
|
|
|
|
2014-07-06 20:44:13 +00:00
|
|
|
listPrivDataFields :: [Host] -> IO ()
|
|
|
|
listPrivDataFields hosts = do
|
2014-07-06 20:03:28 +00:00
|
|
|
m <- decryptPrivData
|
2014-07-07 07:42:35 +00:00
|
|
|
showtable "Currently set data:" $
|
|
|
|
map mkrow (M.keys m)
|
|
|
|
showtable "Data that would be used if set:" $
|
|
|
|
map mkrow (M.keys $ M.difference wantedmap m)
|
2014-06-19 18:56:50 +00:00
|
|
|
where
|
2014-10-08 17:14:21 +00:00
|
|
|
header = ["Field", "Context", "Used by"]
|
2014-07-07 07:42:35 +00:00
|
|
|
mkrow k@(field, (Context context)) =
|
2014-07-06 20:32:05 +00:00
|
|
|
[ shellEscape $ show field
|
|
|
|
, shellEscape context
|
2014-07-06 20:44:13 +00:00
|
|
|
, intercalate ", " $ sort $ fromMaybe [] $ M.lookup k usedby
|
2014-07-06 20:32:05 +00:00
|
|
|
]
|
2014-07-06 20:44:13 +00:00
|
|
|
mkhostmap host = M.fromList $ map (\k -> (k, [hostName host])) $
|
|
|
|
S.toList $ _privDataFields $ hostInfo host
|
2014-07-07 07:42:35 +00:00
|
|
|
usedby = M.unionsWith (++) $ map mkhostmap hosts
|
|
|
|
wantedmap = M.fromList $ zip (M.keys usedby) (repeat "")
|
|
|
|
showtable desc rows = do
|
|
|
|
putStrLn $ "\n" ++ desc
|
|
|
|
putStr $ unlines $ formatTable $ tableWithHeader header rows
|
2014-06-19 18:56:50 +00:00
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
setPrivDataTo :: PrivDataField -> Context -> PrivData -> IO ()
|
|
|
|
setPrivDataTo field context value = do
|
2014-03-30 23:19:29 +00:00
|
|
|
makePrivDataDir
|
2014-07-06 19:56:56 +00:00
|
|
|
m <- decryptPrivData
|
|
|
|
let m' = M.insert (field, context) (chomp value) m
|
|
|
|
gpgEncrypt privDataFile (show m')
|
2014-03-31 01:01:18 +00:00
|
|
|
putStrLn "Private data set."
|
2014-07-06 19:56:56 +00:00
|
|
|
void $ boolSystem "git" [Param "add", File privDataFile]
|
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-07-06 21:37:10 +00:00
|
|
|
decryptPrivData :: IO PrivMap
|
2014-07-06 19:56:56 +00:00
|
|
|
decryptPrivData = fromMaybe M.empty . readish <$> gpgDecrypt privDataFile
|
2014-06-01 20:58:05 +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"
|
|
|
|
|
2014-07-06 19:56:56 +00:00
|
|
|
privDataFile :: FilePath
|
|
|
|
privDataFile = privDataDir </> "privdata.gpg"
|
2014-03-30 23:11:24 +00:00
|
|
|
|
|
|
|
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
|