propellor/src/Propellor/Server.hs

208 lines
6.2 KiB
Haskell
Raw Normal View History

2014-11-22 04:52:59 +00:00
-- When propellor --spin is running, the local host acts as a server,
-- which connects to the remote host's propellor and responds to its
-- requests.
2014-11-19 02:10:50 +00:00
module Propellor.Server (
update,
updateServer,
gitPushHelper
) where
import Data.List
import System.Exit
import System.PosixCompat
import System.Posix.IO
2014-11-22 04:25:00 +00:00
import System.Posix.Directory
2014-11-19 02:10:50 +00:00
import Control.Concurrent.Async
2014-11-22 04:25:00 +00:00
import Control.Exception (bracket)
2014-11-19 02:10:50 +00:00
import qualified Data.ByteString as B
import Propellor
import Propellor.Protocol
import Propellor.PrivData.Paths
import Propellor.Git
import Propellor.Ssh
import qualified Propellor.Shim as Shim
2014-11-19 02:10:50 +00:00
import Utility.FileMode
import Utility.SafeCommand
-- Update the privdata, repo url, and git repo over the ssh
2014-11-20 01:48:48 +00:00
-- connection, talking to the user's local propellor instance which is
2014-11-19 02:10:50 +00:00
-- running the updateServer
2014-11-22 16:57:07 +00:00
update :: Maybe HostName -> IO ()
update forhost = do
2014-11-22 19:19:20 +00:00
whenM hasGitRepo $
2014-11-22 04:44:13 +00:00
req NeedRepoUrl repoUrlMarker setRepoUrl
2014-11-22 16:57:07 +00:00
2014-11-19 02:10:50 +00:00
makePrivDataDir
2014-11-22 16:57:07 +00:00
createDirectoryIfMissing True (takeDirectory privfile)
2014-11-19 02:10:50 +00:00
req NeedPrivData privDataMarker $
2014-11-22 16:57:07 +00:00
writeFileProtected privfile
whenM hasGitRepo $
2014-11-22 04:44:13 +00:00
req NeedGitPush gitPushMarker $ \_ -> do
hin <- dup stdInput
hout <- dup stdOutput
hClose stdin
hClose stdout
unlessM (boolSystem "git" (pullparams hin hout)) $
errorMessage "git pull from client failed"
2014-11-19 02:10:50 +00:00
where
pullparams hin hout =
[ Param "pull"
, Param "--progress"
, Param "--upload-pack"
, Param $ "./propellor --gitpush " ++ show hin ++ " " ++ show hout
, Param "."
]
2014-11-22 16:57:07 +00:00
-- When --spin --relay is run, get a privdata file
-- to be relayed to the target host.
privfile = maybe privDataLocal privDataRelay forhost
2014-11-19 02:10:50 +00:00
-- The connect action should ssh to the remote host and run the provided
-- calback action.
2014-11-22 16:57:07 +00:00
updateServer :: HostName -> Maybe HostName -> Host -> (((Handle, Handle) -> IO ()) -> IO ()) -> IO ()
updateServer target relay hst connect = connect go
2014-11-19 02:10:50 +00:00
where
2014-11-22 16:57:07 +00:00
hn = fromMaybe target relay
2014-11-22 19:48:17 +00:00
relaying = relay == Just target
2014-11-19 02:10:50 +00:00
go (toh, fromh) = do
let loop = go (toh, fromh)
2014-11-22 19:48:17 +00:00
let restart = updateServer hn relay hst connect
let done = return ()
2014-11-19 02:10:50 +00:00
v <- (maybe Nothing readish <$> getMarked fromh statusMarker)
case v of
(Just NeedRepoUrl) -> do
sendRepoUrl toh
loop
(Just NeedPrivData) -> do
2014-11-22 19:48:17 +00:00
sendPrivData hn hst toh relaying
2014-11-19 02:10:50 +00:00
loop
(Just NeedGitClone) -> do
hClose toh
hClose fromh
sendGitClone hn
2014-11-22 19:48:17 +00:00
restart
(Just NeedPrecompiled) -> do
hClose toh
hClose fromh
sendPrecompiled hn
2014-11-22 19:48:17 +00:00
restart
(Just NeedGitPush) -> do
sendGitUpdate hn fromh toh
hClose fromh
hClose toh
done
Nothing -> done
2014-11-19 02:10:50 +00:00
sendRepoUrl :: Handle -> IO ()
sendRepoUrl toh = sendMarked toh repoUrlMarker =<< (fromMaybe "" <$> getRepoUrl)
2014-11-22 19:48:17 +00:00
sendPrivData :: HostName -> Host -> Handle -> Bool -> IO ()
sendPrivData hn hst toh relaying = do
2014-11-22 19:01:08 +00:00
privdata <- getdata
2014-11-19 02:10:50 +00:00
void $ actionMessage ("Sending privdata (" ++ show (length privdata) ++ " bytes) to " ++ hn) $ do
sendMarked toh privDataMarker privdata
return True
2014-11-22 19:01:08 +00:00
where
getdata
2014-11-22 19:48:17 +00:00
| relaying = do
2014-11-22 19:01:08 +00:00
let f = privDataRelay hn
d <- readFileStrictAnyEncoding f
nukeFile f
return d
2014-11-22 19:48:17 +00:00
| otherwise = show . filterPrivData hst <$> decryptPrivData
2014-11-19 02:10:50 +00:00
sendGitUpdate :: HostName -> Handle -> Handle -> IO ()
sendGitUpdate hn fromh toh =
void $ actionMessage ("Sending git update to " ++ hn) $ do
sendMarked toh gitPushMarker ""
(Nothing, Nothing, Nothing, h) <- createProcess p
(==) ExitSuccess <$> waitForProcess h
where
p = (proc "git" ["upload-pack", "."])
{ std_in = UseHandle fromh
, std_out = UseHandle toh
}
-- Initial git clone, used for bootstrapping.
sendGitClone :: HostName -> IO ()
sendGitClone hn = void $ actionMessage ("Clone git repository to " ++ hn) $ do
branch <- getCurrentBranch
2014-11-22 20:20:02 +00:00
cacheparams <- sshCachingParams hn
2014-11-19 02:10:50 +00:00
withTmpFile "propellor.git" $ \tmp _ -> allM id
[ boolSystem "git" [Param "bundle", Param "create", File tmp, Param "HEAD"]
, boolSystem "scp" $ cacheparams ++ [File tmp, Param ("root@"++hn++":"++remotebundle)]
, boolSystem "ssh" $ cacheparams ++ [Param ("root@"++hn), Param $ unpackcmd branch]
]
where
remotebundle = "/usr/local/propellor.git"
unpackcmd branch = shellWrap $ intercalate " && "
[ "git clone " ++ remotebundle ++ " " ++ localdir
, "cd " ++ localdir
, "git checkout -b " ++ branch
, "git remote rm origin"
, "rm -f " ++ remotebundle
]
-- Send a tarball containing the precompiled propellor, and libraries.
-- This should be reasonably portable, as long as the remote host has the
-- same architecture as the build host.
sendPrecompiled :: HostName -> IO ()
2014-11-22 04:32:04 +00:00
sendPrecompiled hn = void $ actionMessage ("Uploading locally compiled propellor as a last resort") $ do
2014-11-22 04:50:56 +00:00
bracket getWorkingDirectory changeWorkingDirectory $ \_ ->
withTmpDir "propellor" go
where
2014-11-22 04:50:56 +00:00
go tmpdir = do
2014-11-22 20:20:02 +00:00
cacheparams <- sshCachingParams hn
2014-11-22 04:50:56 +00:00
let shimdir = takeFileName localdir
createDirectoryIfMissing True (tmpdir </> shimdir)
changeWorkingDirectory (tmpdir </> shimdir)
me <- readSymbolicLink "/proc/self/exe"
2014-11-22 21:16:25 +00:00
me' <- catchDefaultIO me (readSymbolicLink me)
shim <- Shim.setup me' "."
2014-11-22 04:50:56 +00:00
when (shim /= "propellor") $
renameFile shim "propellor"
changeWorkingDirectory tmpdir
withTmpFile "propellor.tar." $ \tarball _ -> allM id
[ boolSystem "strip" [File me]
2014-11-22 05:13:53 +00:00
, boolSystem "tar" [Param "czf", File tarball, File shimdir]
2014-11-22 04:50:56 +00:00
, boolSystem "scp" $ cacheparams ++ [File tarball, Param ("root@"++hn++":"++remotetarball)]
, boolSystem "ssh" $ cacheparams ++ [Param ("root@"++hn), Param unpackcmd]
]
remotetarball = "/usr/local/propellor.tar"
2014-11-22 04:50:56 +00:00
2014-11-22 04:25:00 +00:00
unpackcmd = shellWrap $ intercalate " && "
[ "cd " ++ takeDirectory remotetarball
2014-11-22 05:13:53 +00:00
, "tar xzf " ++ remotetarball
, "rm -f " ++ remotetarball
]
2014-11-19 02:10:50 +00:00
-- Shim for git push over the propellor ssh channel.
-- Reads from stdin and sends it to hout;
-- reads from hin and sends it to stdout.
gitPushHelper :: Fd -> Fd -> IO ()
gitPushHelper hin hout = void $ fromstdin `concurrently` tostdout
where
fromstdin = do
h <- fdToHandle hout
connect stdin h
tostdout = do
h <- fdToHandle hin
connect h stdout
connect fromh toh = do
hSetBinaryMode fromh True
hSetBinaryMode toh True
b <- B.hGetSome fromh 40960
if B.null b
then do
hClose fromh
hClose toh
else do
B.hPut toh b
hFlush toh
connect fromh toh