2014-03-31 03:37:54 +00:00
module Propellor.CmdLine where
2014-03-30 23:10:32 +00:00
2014-04-01 15:59:48 +00:00
import System.Environment ( getArgs )
2014-03-30 23:10:32 +00:00
import Data.List
import System.Exit
2014-04-01 15:59:48 +00:00
import System.Log.Logger
import System.Log.Formatter
import System.Log.Handler ( setFormatter , LogHandler )
import System.Log.Handler.Simple
2014-04-03 17:49:26 +00:00
import System.PosixCompat
2014-04-04 20:20:20 +00:00
import Control.Exception ( bracket )
import System.Posix.IO
2014-04-24 04:19:03 +00:00
import Data.Time.Clock.POSIX
2014-03-30 23:10:32 +00:00
2014-03-31 03:55:59 +00:00
import Propellor
2014-11-18 17:29:50 +00:00
import Propellor.Protocol
2014-11-11 16:58:53 +00:00
import Propellor.PrivData.Paths
import Propellor.Gpg
2014-04-01 17:51:58 +00:00
import qualified Propellor.Property.Docker as Docker
2014-04-04 06:06:19 +00:00
import qualified Propellor.Property.Docker.Shim as DockerShim
2014-03-30 23:10:32 +00:00
import Utility.FileMode
2014-03-31 03:55:59 +00:00
import Utility.SafeCommand
2014-04-10 20:03:49 +00:00
import Utility.UserInfo
2014-03-30 23:10:32 +00:00
2014-03-31 20:37:19 +00:00
usage :: IO a
usage = do
putStrLn $ unlines
[ " Usage: "
, " propellor "
, " propellor hostname "
, " propellor --spin hostname "
2014-06-19 18:41:55 +00:00
, " propellor --add-key keyid "
2014-07-06 19:56:56 +00:00
, " propellor --set field context "
, " propellor --dump field context "
, " propellor --edit field context "
, " propellor --list-fields "
2014-03-31 20:37:19 +00:00
]
exitFailure
2014-03-30 23:10:32 +00:00
processCmdLine :: IO CmdLine
processCmdLine = go =<< getArgs
where
2014-10-08 17:14:21 +00:00
go ( " --help " : _ ) = usage
go ( " --spin " : h : [] ) = return $ Spin h
2014-11-18 05:04:41 +00:00
go ( " --boot " : h : [] ) = return $ Boot h
2014-11-18 05:25:54 +00:00
go ( " --run " : h : [] ) = return $ Run h
2014-03-31 16:06:04 +00:00
go ( " --add-key " : k : [] ) = return $ AddKey k
2014-07-06 19:56:56 +00:00
go ( " --set " : f : c : [] ) = withprivfield f c Set
go ( " --dump " : f : c : [] ) = withprivfield f c Dump
go ( " --edit " : f : c : [] ) = withprivfield f c Edit
go ( " --list-fields " : [] ) = return ListFields
2014-04-01 06:37:48 +00:00
go ( " --continue " : s : [] ) = case readish s of
2014-03-31 20:37:19 +00:00
Just cmdline -> return $ Continue cmdline
2014-03-31 22:31:08 +00:00
Nothing -> errorMessage " --continue serialization failure "
2014-10-08 17:14:21 +00:00
go ( " --chain " : h : [] ) = return $ Chain h
2014-04-02 00:47:25 +00:00
go ( " --docker " : h : [] ) = return $ Docker h
2014-04-01 15:59:48 +00:00
go ( h : [] )
| " -- " ` isPrefixOf ` h = usage
| otherwise = return $ Run h
2014-03-30 23:10:32 +00:00
go [] = do
s <- takeWhile ( /= '\ n' ) <$> readProcess " hostname " [ " -f " ]
if null s
2014-03-31 22:31:08 +00:00
then errorMessage " Cannot determine hostname! Pass it on the command line. "
2014-03-30 23:10:32 +00:00
else return $ Run s
go _ = usage
2014-07-06 19:56:56 +00:00
withprivfield s c f = case readish s of
Just pf -> return $ f pf ( Context c )
2014-06-01 20:58:05 +00:00
Nothing -> errorMessage $ " Unknown privdata field " ++ s
2014-04-11 01:09:20 +00:00
defaultMain :: [ Host ] -> IO ()
defaultMain hostlist = do
2014-04-04 06:06:19 +00:00
DockerShim . cleanEnv
2014-04-01 15:59:48 +00:00
checkDebugMode
cmdline <- processCmdLine
debug [ " command line: " , show cmdline ]
go True cmdline
2014-03-30 23:10:32 +00:00
where
2014-03-31 20:37:19 +00:00
go _ ( Continue cmdline ) = go False cmdline
2014-07-06 19:56:56 +00:00
go _ ( Set field context ) = setPrivData field context
go _ ( Dump field context ) = dumpPrivData field context
go _ ( Edit field context ) = editPrivData field context
2014-07-06 20:44:13 +00:00
go _ ListFields = listPrivDataFields hostlist
2014-03-31 20:37:19 +00:00
go _ ( AddKey keyid ) = addKey keyid
2014-05-31 22:02:56 +00:00
go _ ( Chain hn ) = withhost hn $ \ h -> do
r <- runPropellor h $ ensureProperties $ hostProperties h
2014-04-01 18:47:30 +00:00
putStrLn $ " \ n " ++ show r
2014-04-11 01:09:20 +00:00
go _ ( Docker hn ) = Docker . chain hn
2014-03-31 22:53:27 +00:00
go True cmdline @ ( Spin _ ) = buildFirst cmdline $ go False cmdline
2014-03-31 21:57:12 +00:00
go True cmdline = updateFirst cmdline $ go False cmdline
2014-07-06 21:37:10 +00:00
go False ( Spin hn ) = withhost hn $ spin hn
2014-04-11 01:09:20 +00:00
go False ( Run hn ) = ifM ( ( == ) 0 <$> getRealUserID )
2014-05-31 22:02:56 +00:00
( onlyProcess $ withhost hn mainProperties
2014-04-11 01:09:20 +00:00
, go True ( Spin hn )
2014-04-03 17:58:21 +00:00
)
2014-11-18 05:10:53 +00:00
go False ( Boot _ ) = onlyProcess boot
2014-03-31 20:37:19 +00:00
2014-05-31 22:02:56 +00:00
withhost :: HostName -> ( Host -> IO () ) -> IO ()
2014-07-07 05:57:59 +00:00
withhost hn a = maybe ( unknownhost hn hostlist ) a ( findHost hostlist hn )
2014-03-30 23:10:32 +00:00
2014-04-04 20:20:20 +00:00
onlyProcess :: IO a -> IO a
onlyProcess a = bracket lock unlock ( const a )
where
lock = do
2014-04-04 22:34:03 +00:00
l <- createFile lockfile stdFileMode
2014-04-04 20:20:20 +00:00
setLock l ( WriteLock , AbsoluteSeek , 0 , 0 )
2014-04-04 22:34:03 +00:00
` catchIO ` const alreadyrunning
2014-04-04 20:20:20 +00:00
return l
unlock = closeFd
alreadyrunning = error " Propellor is already running on this host! "
lockfile = localdir </> " .lock "
2014-07-07 05:57:59 +00:00
unknownhost :: HostName -> [ Host ] -> IO a
unknownhost h hosts = errorMessage $ unlines
2014-04-08 22:42:54 +00:00
[ " Propellor does not know about host: " ++ h
2014-04-03 04:59:26 +00:00
, " (Perhaps you should specify the real hostname on the command line?) "
, " (Or, edit propellor's config.hs to configure this host) "
2014-07-07 05:57:59 +00:00
, " Known hosts: " ++ unwords ( map hostName hosts )
2014-03-31 03:02:10 +00:00
]
2014-03-31 22:53:27 +00:00
buildFirst :: CmdLine -> IO () -> IO ()
buildFirst cmdline next = do
oldtime <- getmtime
2014-03-31 23:31:35 +00:00
ifM ( actionMessage " Propellor build " $ boolSystem " make " [ Param " build " ] )
2014-03-31 22:53:27 +00:00
( do
newtime <- getmtime
if newtime == oldtime
then next
2014-07-07 06:01:57 +00:00
else void $ boolSystem " ./propellor " [ Param " --continue " , Param ( show cmdline ) ]
2014-03-31 22:53:27 +00:00
, errorMessage " Propellor build failed! "
)
where
getmtime = catchMaybeIO $ getModificationTime " propellor "
2014-04-03 16:33:36 +00:00
getCurrentBranch :: IO String
getCurrentBranch = takeWhile ( /= '\ n' )
<$> readProcess " git " [ " symbolic-ref " , " --short " , " HEAD " ]
2014-03-31 21:57:12 +00:00
updateFirst :: CmdLine -> IO () -> IO ()
updateFirst cmdline next = do
2014-04-03 16:33:36 +00:00
branchref <- getCurrentBranch
let originbranch = " origin " </> branchref
2014-03-31 22:39:39 +00:00
2014-03-31 23:31:35 +00:00
void $ actionMessage " Git fetch " $ boolSystem " git " [ Param " fetch " ]
2014-03-31 20:20:38 +00:00
2014-06-10 19:49:17 +00:00
oldsha <- getCurrentGitSha1 branchref
2014-04-10 20:12:06 +00:00
whenM ( doesFileExist keyring ) $ do
2014-04-03 17:49:26 +00:00
{- To verify origin branch commit's signature, have to
2014-03-31 20:20:38 +00:00
- convince gpg to use our keyring . While running git log .
- Which has no way to pass options to gpg .
- Argh ! - }
let gpgconf = privDataDir </> " gpg.conf "
writeFile gpgconf $ unlines
[ " keyring " ++ keyring
, " no-auto-check-trustdb "
]
-- gpg is picky about perms
modifyFileMode privDataDir ( removeModes otherGroupModes )
s <- readProcessEnv " git " [ " log " , " -n " , " 1 " , " --format=%G? " , originbranch ]
( Just [ ( " GNUPGHOME " , privDataDir ) ] )
2014-04-03 16:20:42 +00:00
nukeFile $ privDataDir </> " trustdb.gpg "
nukeFile $ privDataDir </> " pubring.gpg "
2014-03-31 20:20:38 +00:00
nukeFile $ privDataDir </> " gpg.conf "
2014-03-31 20:37:19 +00:00
if s == " U \ n " || s == " G \ n "
2014-03-31 20:42:25 +00:00
then do
putStrLn $ " git branch " ++ originbranch ++ " gpg signature verified; merging "
hFlush stdout
2014-06-10 19:49:17 +00:00
void $ boolSystem " git " [ Param " merge " , Param originbranch ]
else warningMessage $ " git branch " ++ originbranch ++ " is not signed with a trusted gpg key; refusing to deploy it! (Running with previous configuration instead.) "
2014-03-31 20:20:38 +00:00
2014-03-31 20:40:03 +00:00
newsha <- getCurrentGitSha1 branchref
2014-03-31 20:37:19 +00:00
if oldsha == newsha
2014-03-31 20:50:30 +00:00
then next
2014-03-31 23:31:35 +00:00
else ifM ( actionMessage " Propellor build " $ boolSystem " make " [ Param " build " ] )
2014-03-31 22:31:08 +00:00
( void $ boolSystem " ./propellor " [ Param " --continue " , Param ( show cmdline ) ]
, errorMessage " Propellor build failed! "
)
2014-03-31 20:20:38 +00:00
2014-03-31 20:40:03 +00:00
getCurrentGitSha1 :: String -> IO String
getCurrentGitSha1 branchref = readProcess " git " [ " show-ref " , " --hash " , branchref ]
2014-03-31 20:20:38 +00:00
2014-11-18 17:29:50 +00:00
-- spin handles deploying propellor to a remote host, if it's not already
-- installed there, or updating it if it is. Once the remote propellor is
-- updated, it's run.
2014-07-06 21:37:10 +00:00
spin :: HostName -> Host -> IO ()
spin hn hst = do
2014-03-31 16:06:04 +00:00
void $ gitCommit [ Param " --allow-empty " , Param " -a " , Param " -m " , Param " propellor spin " ]
2014-03-30 23:19:29 +00:00
void $ boolSystem " git " [ Param " push " ]
2014-04-11 01:09:20 +00:00
cacheparams <- toCommand <$> sshCachingParams hn
2014-11-18 17:29:50 +00:00
go cacheparams =<< hostprivdata
2014-11-18 05:25:54 +00:00
unlessM ( boolSystem " ssh " ( map Param ( cacheparams ++ [ " -t " , user , runcmd ] ) ) ) $
error $ " remote propellor failed (running: " ++ runcmd ++ " ) "
2014-03-31 19:40:16 +00:00
where
2014-07-06 21:37:10 +00:00
hostprivdata = show . filterPrivData hst <$> decryptPrivData
2014-11-18 17:29:50 +00:00
go cacheparams privdata = withBothHandles createProcessSuccess ( proc " ssh " $ cacheparams ++ [ user , bootstrapcmd ] ) $ \ ( toh , fromh ) -> do
2014-11-18 17:59:50 +00:00
let comm = do
status <- getMarked fromh statusMarker
case readish =<< status of
Just RepoUrl -> do
sendMarked toh repoUrlMarker
=<< ( fromMaybe " " <$> getRepoUrl )
comm
Just Ready -> do
sendprivdata toh " privdata " privDataMarker privdata
hClose toh
-- Display remaining output.
void $ tryIO $ forever $
showremote =<< hGetLine fromh
hClose fromh
Just NeedGitClone -> do
hClose toh
hClose fromh
sendGitClone hn
go cacheparams privdata
Nothing -> error $ " protocol error; received: " ++ show status
comm
2014-03-31 19:40:16 +00:00
2014-04-11 01:09:20 +00:00
user = " root@ " ++ hn
2014-03-31 19:40:16 +00:00
2014-11-18 05:01:50 +00:00
mkcmd = shellWrap . intercalate " ; "
bootstrapcmd = mkcmd
2014-03-31 20:45:32 +00:00
[ " if [ ! -d " ++ localdir ++ " ] "
, " then " ++ intercalate " && "
2014-07-07 06:04:21 +00:00
[ " apt-get update "
, " apt-get --no-install-recommends --no-upgrade -y install git make "
2014-03-31 20:45:32 +00:00
, " echo " ++ toMarked statusMarker ( show NeedGitClone )
]
, " else " ++ intercalate " && "
[ " cd " ++ localdir
2014-04-10 04:40:38 +00:00
, " if ! test -x ./propellor; then make deps build; fi "
2014-11-18 05:04:41 +00:00
, " ./propellor --boot " ++ hn
2014-03-30 23:10:32 +00:00
]
2014-03-31 20:52:58 +00:00
, " fi "
2014-03-30 23:10:32 +00:00
]
2014-03-31 19:40:16 +00:00
2014-11-18 05:25:54 +00:00
runcmd = mkcmd
[ " cd " ++ localdir ++ " && ./propellor --run " ++ hn ]
2014-11-18 05:01:50 +00:00
2014-03-31 18:44:38 +00:00
showremote s = putStrLn s
2014-11-18 17:29:50 +00:00
sendprivdata toh desc marker s = void $
2014-07-06 21:15:27 +00:00
actionMessage ( " Sending " ++ desc ++ " ( " ++ show ( length s ) ++ " bytes) to " ++ hn ) $ do
2014-03-31 22:44:10 +00:00
sendMarked toh marker s
2014-03-31 22:31:08 +00:00
return True
2014-03-30 23:10:32 +00:00
2014-09-25 19:11:19 +00:00
-- Initial git clone, used for bootstrapping.
2014-11-18 17:59:50 +00:00
sendGitClone :: HostName -> IO ()
sendGitClone hn = void $ actionMessage ( " Pushing git repository to " ++ hn ) $ do
2014-04-03 17:49:26 +00:00
branch <- getCurrentBranch
2014-04-11 01:09:20 +00:00
cacheparams <- sshCachingParams hn
2014-04-03 16:26:27 +00:00
withTmpFile " propellor.git " $ \ tmp _ -> allM id
2014-03-31 23:01:56 +00:00
[ boolSystem " git " [ Param " bundle " , Param " create " , File tmp , Param " HEAD " ]
2014-04-11 01:09:20 +00:00
, boolSystem " scp " $ cacheparams ++ [ File tmp , Param ( " root@ " ++ hn ++ " : " ++ remotebundle ) ]
, boolSystem " ssh " $ cacheparams ++ [ Param ( " root@ " ++ hn ) , Param $ unpackcmd branch ]
2014-03-31 22:31:08 +00:00
]
2014-03-31 19:40:16 +00:00
where
remotebundle = " /usr/local/propellor.git "
2014-04-03 17:49:26 +00:00
unpackcmd branch = shellWrap $ intercalate " && "
2014-03-31 19:40:16 +00:00
[ " git clone " ++ remotebundle ++ " " ++ localdir
, " cd " ++ localdir
2014-04-03 17:49:26 +00:00
, " git checkout -b " ++ branch
2014-03-31 19:40:16 +00:00
, " git remote rm origin "
, " rm -f " ++ remotebundle
]
2014-11-18 17:59:50 +00:00
-- Called "boot" for historical reasons, but what this really does is
-- update the privdata, repo url, and git repo over the ssh connection from the
-- client that ran propellor --spin.
2014-11-18 05:10:53 +00:00
boot :: IO ()
boot = do
2014-11-18 17:59:50 +00:00
sendMarked stdout statusMarker ( show RepoUrl )
maybe noop setRepoUrl
=<< getMarked stdin repoUrlMarker
2014-11-18 17:29:50 +00:00
sendMarked stdout statusMarker ( show Ready )
2014-03-30 23:19:29 +00:00
makePrivDataDir
2014-11-18 17:29:50 +00:00
maybe noop ( writeFileProtected privDataLocal )
=<< getMarked stdin privDataMarker
2014-03-30 23:10:32 +00:00
2014-11-18 17:59:50 +00:00
setRepoUrl :: String -> IO ()
setRepoUrl " " = return ()
setRepoUrl url = do
rs <- lines <$> readProcess " git " [ " remote " ]
let subcmd = if " origin " ` elem ` rs then " set-url " else " add "
void $ boolSystem " git " [ Param " remote " , Param subcmd , Param " origin " , Param url ]
-- same as --set-upstream-to, except origin branch
-- may not have been pulled yet
branch <- getCurrentBranch
let branchval s = " branch. " ++ branch ++ " . " ++ s
void $ boolSystem " git " [ Param " config " , Param ( branchval " remote " ) , Param " origin " ]
void $ boolSystem " git " [ Param " config " , Param ( branchval " merge " ) , Param $ " refs/heads/ " ++ branch ]
getRepoUrl :: IO ( Maybe String )
getRepoUrl = getM get urls
2014-03-30 23:10:32 +00:00
where
urls = [ " remote.deploy.url " , " remote.origin.url " ]
get u = do
v <- catchMaybeIO $
takeWhile ( /= '\ n' )
<$> readProcess " git " [ " config " , u ]
return $ case v of
Just url | not ( null url ) -> Just url
_ -> Nothing
2014-04-01 15:59:48 +00:00
checkDebugMode :: IO ()
checkDebugMode = go =<< getEnv " PROPELLOR_DEBUG "
where
go ( Just s )
| s == " 1 " = do
2014-05-11 13:19:21 +00:00
f <- setFormatter
<$> streamHandler stderr DEBUG
<*> pure ( simpleLogFormatter " [$time] $msg " )
updateGlobalLogger rootLoggerName $
setLevel DEBUG . setHandlers [ f ]
2014-05-14 23:34:26 +00:00
go _ = noop
2014-04-10 20:03:49 +00:00
2014-04-24 04:19:03 +00:00
-- Parameters can be passed to both ssh and scp, to enable a ssh connection
-- caching socket.
--
-- If the socket already exists, check if its mtime is older than 10
-- minutes, and if so stop that ssh process, in order to not try to
-- use an old stale connection. (atime would be nicer, but there's
-- a good chance a laptop uses noatime)
2014-04-10 20:03:49 +00:00
sshCachingParams :: HostName -> IO [ CommandParam ]
2014-04-11 01:09:20 +00:00
sshCachingParams hn = do
2014-04-10 20:03:49 +00:00
home <- myHomeDir
let cachedir = home </> " .ssh " </> " propellor "
createDirectoryIfMissing False cachedir
2014-04-11 01:09:20 +00:00
let socketfile = cachedir </> hn ++ " .sock "
2014-04-24 04:19:03 +00:00
let ps =
2014-04-10 20:03:49 +00:00
[ Param " -o " , Param ( " ControlPath= " ++ socketfile )
, Params " -o ControlMaster=auto -o ControlPersist=yes "
]
2014-04-24 04:19:03 +00:00
maybe noop ( expireold ps socketfile )
=<< catchMaybeIO ( getFileStatus socketfile )
return ps
where
expireold ps f s = do
now <- truncate <$> getPOSIXTime :: IO Integer
if modificationTime s > fromIntegral now - tenminutes
then touchFile f
else do
void $ boolSystem " ssh " $
[ Params " -O stop " ] ++ ps ++
[ Param " localhost " ]
nukeFile f
tenminutes = 600