module Propellor.CmdLine (
	defaultMain,
	processCmdLine,
) where

import System.Environment (getArgs)
import Data.List
import System.Exit
import System.PosixCompat
import Network.Socket

import Propellor.Base
import Propellor.Gpg
import Propellor.Git
import Propellor.Git.VerifiedBranch
import Propellor.Bootstrap
import Propellor.Spin
import Propellor.Types.CmdLine
import qualified Propellor.Property.Docker as Docker
import qualified Propellor.Property.Chroot as Chroot
import qualified Propellor.Shim as Shim
import Utility.FileSystemEncoding

usage :: Handle -> IO ()
usage :: Handle -> IO ()
usage Handle
h = Handle -> String -> IO ()
hPutStrLn Handle
h (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
	[ String
"Usage:"
	, String
"  with no arguments, provision the current host"
	, String
""
	, String
"  --init"
	, String
"      initialize ~/.propellor"
	, String
"  hostname"
	, String
"      provision the current host as if it had the specified hostname"
	, String
"  --spin targethost [--via relayhost]"
	, String
"      provision the specified host"
	, String
"  --build"
	, String
"      recompile using your current config"
	, String
"  --add-key keyid"
	, String
"      add an additional signing key to the private data"
	, String
"  --rm-key keyid"
	, String
"      remove a signing key from the private data"
	, String
"  --list-fields"
	, String
"      list private data fields"
	, String
"  --set field context"
	, String
"      set a private data field"
	, String
"  --unset field context"
	, String
"      clear a private data field"
	, String
"  --unset-unused"
	, String
"      clear unused fields from the private data"
	, String
"  --dump field context"
	, String
"      show the content of a private data field"
	, String
"  --edit field context"
	, String
"      edit the content of a private data field"
	, String
"  --merge"
	, String
"      combine multiple spins into a single git commit"
	, String
"  --check"
	, String
"      double-check that propellor can actually run here"]

usageError :: [String] -> IO a
usageError :: [String] -> IO a
usageError [String]
ps = do
	Handle -> IO ()
usage Handle
stderr
	String -> IO a
forall a. HasCallStack => String -> a
error (String
"(Unexpected: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => a -> String
show [String]
ps)

processCmdLine :: IO CmdLine
processCmdLine :: IO CmdLine
processCmdLine = [String] -> IO CmdLine
go ([String] -> IO CmdLine) -> IO [String] -> IO CmdLine
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO [String]
getArgs
  where
	go :: [String] -> IO CmdLine
go (String
"--check":[String]
_) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return CmdLine
Check
	go (String
"--spin":[String]
ps) = case [String] -> [String]
forall a. [a] -> [a]
reverse [String]
ps of
		(String
r:String
"--via":[String]
hs) -> [String] -> Maybe String -> CmdLine
Spin
			([String] -> Maybe String -> CmdLine)
-> IO [String] -> IO (Maybe String -> CmdLine)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO String) -> [String] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO String
hostname ([String] -> [String]
forall a. [a] -> [a]
reverse [String]
hs)
			IO (Maybe String -> CmdLine) -> IO (Maybe String) -> IO CmdLine
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe String -> IO (Maybe String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Maybe String
forall a. a -> Maybe a
Just String
r)
		[String]
_ -> [String] -> Maybe String -> CmdLine
Spin ([String] -> Maybe String -> CmdLine)
-> IO [String] -> IO (Maybe String -> CmdLine)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO String) -> [String] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO String
hostname [String]
ps IO (Maybe String -> CmdLine) -> IO (Maybe String) -> IO CmdLine
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe String -> IO (Maybe String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing
	go (String
"--build":[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return CmdLine
Build
	go (String
"--add-key":String
k:[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return (CmdLine -> IO CmdLine) -> CmdLine -> IO CmdLine
forall a b. (a -> b) -> a -> b
$ String -> CmdLine
AddKey String
k
	go (String
"--rm-key":String
k:[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return (CmdLine -> IO CmdLine) -> CmdLine -> IO CmdLine
forall a b. (a -> b) -> a -> b
$ String -> CmdLine
RmKey String
k
	go (String
"--set":String
f:String
c:[]) = String
-> String -> (PrivDataField -> Context -> CmdLine) -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
String -> String -> (t -> Context -> a) -> m a
withprivfield String
f String
c PrivDataField -> Context -> CmdLine
Set
	go (String
"--unset":String
f:String
c:[]) = String
-> String -> (PrivDataField -> Context -> CmdLine) -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
String -> String -> (t -> Context -> a) -> m a
withprivfield String
f String
c PrivDataField -> Context -> CmdLine
Unset
	go (String
"--unset-unused":[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return CmdLine
UnsetUnused
	go (String
"--dump":String
f:String
c:[]) = String
-> String -> (PrivDataField -> Context -> CmdLine) -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
String -> String -> (t -> Context -> a) -> m a
withprivfield String
f String
c PrivDataField -> Context -> CmdLine
Dump
	go (String
"--edit":String
f:String
c:[]) = String
-> String -> (PrivDataField -> Context -> CmdLine) -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
String -> String -> (t -> Context -> a) -> m a
withprivfield String
f String
c PrivDataField -> Context -> CmdLine
Edit
	go (String
"--list-fields":[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return CmdLine
ListFields
	go (String
"--merge":[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return CmdLine
Merge
	go (String
"--help":[String]
_) = do
		Handle -> IO ()
usage Handle
stdout
		IO CmdLine
forall a. IO a
exitFailure
	go (String
"--boot":String
_:[]) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return (CmdLine -> IO CmdLine) -> CmdLine -> IO CmdLine
forall a b. (a -> b) -> a -> b
$ Maybe String -> CmdLine
Update Maybe String
forall a. Maybe a
Nothing -- for back-compat
	go (String
"--serialized":String
s:[]) = (CmdLine -> CmdLine) -> String -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
(t -> a) -> String -> m a
serialized CmdLine -> CmdLine
Serialized String
s
	go (String
"--continue":String
s:[]) = (CmdLine -> CmdLine) -> String -> IO CmdLine
forall t (m :: * -> *) a.
(Read t, MonadIO m) =>
(t -> a) -> String -> m a
serialized CmdLine -> CmdLine
Continue String
s
	go (String
"--gitpush":String
fin:String
fout:[String]
_) = CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return (CmdLine -> IO CmdLine) -> CmdLine -> IO CmdLine
forall a b. (a -> b) -> a -> b
$ Fd -> Fd -> CmdLine
GitPush (String -> Fd
forall a. Read a => String -> a
Prelude.read String
fin) (String -> Fd
forall a. Read a => String -> a
Prelude.read String
fout)
	go (String
"--run":String
h:[]) = [String] -> IO CmdLine
go [String
h]
	go (String
h:[])
		| String
"--" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
h = [String] -> IO CmdLine
forall a. [String] -> IO a
usageError [String
h]
		| Bool
otherwise = String -> CmdLine
Run (String -> CmdLine) -> IO String -> IO CmdLine
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
hostname String
h
	go [] = do
		String
s <- (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') (String -> String) -> IO String -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String] -> IO String
readProcess String
"hostname" [String
"-f"]
		if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s
			then String -> IO CmdLine
forall (m :: * -> *) a. MonadIO m => String -> m a
errorMessage String
"Cannot determine hostname! Pass it on the command line."
			else CmdLine -> IO CmdLine
forall (m :: * -> *) a. Monad m => a -> m a
return (CmdLine -> IO CmdLine) -> CmdLine -> IO CmdLine
forall a b. (a -> b) -> a -> b
$ String -> CmdLine
Run String
s
	go [String]
v = [String] -> IO CmdLine
forall a. [String] -> IO a
usageError [String]
v

	withprivfield :: String -> String -> (t -> Context -> a) -> m a
withprivfield String
s String
c t -> Context -> a
f = case String -> Maybe t
forall a. Read a => String -> Maybe a
readish String
s of
		Just t
pf -> a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$ t -> Context -> a
f t
pf (String -> Context
Context String
c)
		Maybe t
Nothing -> String -> m a
forall (m :: * -> *) a. MonadIO m => String -> m a
errorMessage (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"Unknown privdata field " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s

	serialized :: (t -> a) -> String -> m a
serialized t -> a
mk String
s = case String -> Maybe t
forall a. Read a => String -> Maybe a
readish String
s of
		Just t
cmdline -> a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$ t -> a
mk t
cmdline
		Maybe t
Nothing -> String -> m a
forall (m :: * -> *) a. MonadIO m => String -> m a
errorMessage (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"serialization failure (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"

data CanRebuild = CanRebuild | NoRebuild

-- | Runs propellor on hosts, as controlled by command-line options.
defaultMain :: [Host] -> IO ()
defaultMain :: [Host] -> IO ()
defaultMain [Host]
hostlist = IO () -> IO ()
forall (m :: * -> *) a. (MonadIO m, MonadMask m) => m a -> m a
withConcurrentOutput (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
	IO ()
useFileSystemEncoding
	IO ()
setupGpgEnv
	IO ()
Shim.cleanEnv
	IO ()
checkDebugMode
	CmdLine
cmdline <- IO CmdLine
processCmdLine
	[String] -> IO ()
debug [String
"command line: ", CmdLine -> String
forall a. Show a => a -> String
show CmdLine
cmdline]
	CanRebuild -> CmdLine -> IO ()
go CanRebuild
CanRebuild CmdLine
cmdline
  where
	go :: CanRebuild -> CmdLine -> IO ()
go CanRebuild
cr (Serialized CmdLine
cmdline) = CanRebuild -> CmdLine -> IO ()
go CanRebuild
cr CmdLine
cmdline
	go CanRebuild
_ CmdLine
Check = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
	go CanRebuild
cr CmdLine
Build = Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
buildFirst Maybe Host
forall a. Maybe a
Nothing CanRebuild
cr CmdLine
Build (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
	go CanRebuild
_ (Set PrivDataField
field Context
context) = PrivDataField -> Context -> IO ()
setPrivData PrivDataField
field Context
context
	go CanRebuild
_ (Unset PrivDataField
field Context
context) = PrivDataField -> Context -> IO ()
unsetPrivData PrivDataField
field Context
context
	go CanRebuild
_ (CmdLine
UnsetUnused) = [Host] -> IO ()
unsetPrivDataUnused [Host]
hostlist
	go CanRebuild
_ (Dump PrivDataField
field Context
context) = PrivDataField -> Context -> IO ()
dumpPrivData PrivDataField
field Context
context
	go CanRebuild
_ (Edit PrivDataField
field Context
context) = PrivDataField -> Context -> IO ()
editPrivData PrivDataField
field Context
context
	go CanRebuild
_ CmdLine
ListFields = [Host] -> IO ()
listPrivDataFields [Host]
hostlist
	go CanRebuild
_ (AddKey String
keyid) = String -> IO ()
addKey String
keyid
	go CanRebuild
_ (RmKey String
keyid) = String -> IO ()
rmKey String
keyid
	go CanRebuild
_ c :: CmdLine
c@(ChrootChain String
_ String
_ Bool
_ Bool
_ [ContainerCapability]
_) = [Host] -> CmdLine -> IO ()
Chroot.chain [Host]
hostlist CmdLine
c
	go CanRebuild
_ (DockerChain String
hn String
cid) = [Host] -> String -> String -> IO ()
Docker.chain [Host]
hostlist String
hn String
cid
	go CanRebuild
_ (DockerInit String
hn) = String -> IO ()
Docker.init String
hn
	go CanRebuild
_ (GitPush Fd
fin Fd
fout) = Fd -> Fd -> IO ()
gitPushHelper Fd
fin Fd
fout
	go CanRebuild
cr (Relay String
h) = IO ()
forceConsole IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
		Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst Maybe Host
forall a. Maybe a
Nothing CanRebuild
cr (Maybe String -> CmdLine
Update (String -> Maybe String
forall a. a -> Maybe a
Just String
h)) (Maybe String -> IO ()
update (String -> Maybe String
forall a. a -> Maybe a
Just String
h))
	go CanRebuild
_ (Update Maybe String
Nothing) = IO ()
forceConsole IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
		IO () -> IO ()
fetchFirst (IO () -> IO ()
forall a. IO a -> IO a
onlyprocess (Maybe String -> IO ()
update Maybe String
forall a. Maybe a
Nothing))
	go CanRebuild
_ (Update (Just String
h)) = Maybe String -> IO ()
update (String -> Maybe String
forall a. a -> Maybe a
Just String
h)
	go CanRebuild
_ CmdLine
Merge = IO ()
mergeSpin
	go CanRebuild
cr cmdline :: CmdLine
cmdline@(Spin [String]
hs Maybe String
mrelay) = Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
buildFirst Maybe Host
forall a. Maybe a
Nothing CanRebuild
cr CmdLine
cmdline (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
		Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mrelay) IO ()
commitSpin
		[String] -> (String -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
hs ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
hn -> String -> (Host -> IO ()) -> IO ()
withhost String
hn ((Host -> IO ()) -> IO ()) -> (Host -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe String -> String -> Host -> IO ()
spin Maybe String
mrelay String
hn
	go CanRebuild
cr cmdline :: CmdLine
cmdline@(Run String
hn) = IO Bool -> (IO (), IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m Bool -> (m a, m a) -> m a
ifM (UserID -> UserID -> Bool
forall a. Eq a => a -> a -> Bool
(==) UserID
0 (UserID -> Bool) -> IO UserID -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UserID
getRealUserID)
		( Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst ([Host] -> String -> Maybe Host
findHost [Host]
hostlist String
hn) CanRebuild
cr CmdLine
cmdline (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
runhost String
hn
		, IO () -> IO ()
fetchFirst (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ CanRebuild -> CmdLine -> IO ()
go CanRebuild
cr ([String] -> Maybe String -> CmdLine
Spin [String
hn] Maybe String
forall a. Maybe a
Nothing)
		)
	go CanRebuild
cr cmdline :: CmdLine
cmdline@(SimpleRun String
hn) = IO ()
forceConsole IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
		IO () -> IO ()
fetchFirst (Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
buildFirst ([Host] -> String -> Maybe Host
findHost [Host]
hostlist String
hn) CanRebuild
cr CmdLine
cmdline (String -> IO ()
runhost String
hn))
	-- When continuing after a rebuild, don't want to rebuild again.
	go CanRebuild
_ (Continue CmdLine
cmdline) = CanRebuild -> CmdLine -> IO ()
go CanRebuild
NoRebuild CmdLine
cmdline

	withhost :: HostName -> (Host -> IO ()) -> IO ()
	withhost :: String -> (Host -> IO ()) -> IO ()
withhost String
hn Host -> IO ()
a = IO () -> (Host -> IO ()) -> Maybe Host -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> [Host] -> IO ()
forall a. String -> [Host] -> IO a
unknownhost String
hn [Host]
hostlist) Host -> IO ()
a ([Host] -> String -> Maybe Host
findHost [Host]
hostlist String
hn)

	runhost :: String -> IO ()
runhost String
hn = IO () -> IO ()
forall a. IO a -> IO a
onlyprocess (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> (Host -> IO ()) -> IO ()
withhost String
hn Host -> IO ()
mainProperties

	onlyprocess :: IO a -> IO a
onlyprocess = String -> IO a -> IO a
forall a. String -> IO a -> IO a
onlyProcess (String
localdir String -> String -> String
</> String
".lock")

unknownhost :: HostName -> [Host] -> IO a
unknownhost :: String -> [Host] -> IO a
unknownhost String
h [Host]
hosts = String -> IO a
forall (m :: * -> *) a. MonadIO m => String -> m a
errorMessage (String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
	[ String
"Propellor does not know about host: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
h
	, String
"(Perhaps you should specify the real hostname on the command line?)"
	, String
"(Or, edit propellor's config.hs to configure this host)"
	, String
"Known hosts: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords ((Host -> String) -> [Host] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Host -> String
hostName [Host]
hosts)
	]

-- Builds propellor (when allowed) and if it looks like a new binary,
-- re-execs it to continue.
-- Otherwise, runs the IO action to continue.
--
-- The Host should only be provided when dependencies should be installed
-- as needed to build propellor.
buildFirst :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
buildFirst :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
buildFirst Maybe Host
h CanRebuild
CanRebuild CmdLine
cmdline IO ()
next = do
	Maybe UTCTime
oldtime <- IO (Maybe UTCTime)
getmtime
	Maybe Host -> IO ()
buildPropellor Maybe Host
h
	Maybe UTCTime
newtime <- IO (Maybe UTCTime)
getmtime
	if Maybe UTCTime
newtime Maybe UTCTime -> Maybe UTCTime -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe UTCTime
oldtime
		then IO ()
next
		else CmdLine -> IO ()
forall a. CmdLine -> IO a
continueAfterBuild CmdLine
cmdline
  where
	getmtime :: IO (Maybe UTCTime)
getmtime = IO UTCTime -> IO (Maybe UTCTime)
forall (m :: * -> *) a. MonadCatch m => m a -> m (Maybe a)
catchMaybeIO (IO UTCTime -> IO (Maybe UTCTime))
-> IO UTCTime -> IO (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ String -> IO UTCTime
getModificationTime String
"propellor"
buildFirst Maybe Host
_ CanRebuild
NoRebuild CmdLine
_ IO ()
next = IO ()
next

continueAfterBuild :: CmdLine -> IO a
continueAfterBuild :: CmdLine -> IO a
continueAfterBuild CmdLine
cmdline = Bool -> IO a
forall a. Bool -> IO a
go (Bool -> IO a) -> IO Bool -> IO a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> [CommandParam] -> IO Bool
boolSystem String
"./propellor"
	[ String -> CommandParam
Param String
"--continue"
	, String -> CommandParam
Param (CmdLine -> String
forall a. Show a => a -> String
show CmdLine
cmdline)
	]
  where
	go :: Bool -> IO a
go Bool
True = IO a
forall a. IO a
exitSuccess
	go Bool
False = ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)

fetchFirst :: IO () -> IO ()
fetchFirst :: IO () -> IO ()
fetchFirst IO ()
next = do
	IO Bool -> IO () -> IO ()
forall (m :: * -> *). Monad m => m Bool -> m () -> m ()
whenM IO Bool
hasOrigin (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
		IO Bool -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void IO Bool
fetchOrigin
	IO ()
next

updateFirst :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst Maybe Host
h CanRebuild
canrebuild CmdLine
cmdline IO ()
next = IO Bool -> (IO (), IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m Bool -> (m a, m a) -> m a
ifM IO Bool
hasOrigin
	( Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst' Maybe Host
h CanRebuild
canrebuild CmdLine
cmdline IO ()
next
	, IO ()
next
	)

-- If changes can be fetched from origin, builds propellor (when allowed)
-- and re-execs the updated propellor binary to continue.
-- Otherwise, runs the IO action to continue.
updateFirst' :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst' :: Maybe Host -> CanRebuild -> CmdLine -> IO () -> IO ()
updateFirst' Maybe Host
h CanRebuild
CanRebuild CmdLine
cmdline IO ()
next = IO Bool -> (IO (), IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m Bool -> (m a, m a) -> m a
ifM IO Bool
fetchOrigin
	( do
		Maybe Host -> IO ()
buildPropellor Maybe Host
h
		CmdLine -> IO ()
forall a. CmdLine -> IO a
continueAfterBuild CmdLine
cmdline
	, IO ()
next
	)
updateFirst' Maybe Host
_ CanRebuild
NoRebuild CmdLine
_ IO ()
next = IO ()
next

-- Gets the fully qualified domain name, given a string that might be
-- a short name to look up in the DNS.
hostname :: String -> IO HostName
hostname :: String -> IO String
hostname String
s = [AddrInfo] -> IO String
forall (f :: * -> *). Applicative f => [AddrInfo] -> f String
go ([AddrInfo] -> IO String) -> IO [AddrInfo] -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [AddrInfo] -> IO [AddrInfo] -> IO [AddrInfo]
forall (m :: * -> *) a. MonadCatch m => a -> m a -> m a
catchDefaultIO [] IO [AddrInfo]
dnslookup
  where
	dnslookup :: IO [AddrInfo]
dnslookup = Maybe AddrInfo -> Maybe String -> Maybe String -> IO [AddrInfo]
getAddrInfo (AddrInfo -> Maybe AddrInfo
forall a. a -> Maybe a
Just AddrInfo
canonname) (String -> Maybe String
forall a. a -> Maybe a
Just String
s) Maybe String
forall a. Maybe a
Nothing
	canonname :: AddrInfo
canonname = AddrInfo
defaultHints { addrFlags :: [AddrInfoFlag]
addrFlags = [AddrInfoFlag
AI_CANONNAME] }
	go :: [AddrInfo] -> f String
go (AddrInfo { addrCanonName :: AddrInfo -> Maybe String
addrCanonName = Just String
v } : [AddrInfo]
_) = String -> f String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
v
	go [AddrInfo]
_
		| String
"." String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
s = String -> f String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
s -- assume it's a fqdn
		| Bool
otherwise =
			String -> f String
forall a. HasCallStack => String -> a
error (String -> f String) -> String -> f String
forall a b. (a -> b) -> a -> b
$ String
"cannot find host " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in the DNS"