module Propellor.Property.Conductor (
orchestrate,
Conductable(..),
) where
import Propellor.Base hiding (os)
import Propellor.Spin (spin')
import Propellor.PrivData.Paths
import Propellor.Types.Info
import qualified Propellor.Property.Ssh as Ssh
import qualified Data.Set as S
class Conductable c where
conducts :: c -> RevertableProperty
instance Conductable Host where
conducts h = conductorFor h <!> notConductorFor h
instance Conductable [Host] where
conducts hs =
propertyList desc (map (toProp . conducts) hs)
<!>
propertyList desc (map (toProp . revert . conducts) hs)
where
desc = cdesc $ unwords $ map hostName hs
data Orchestra
= Conductor Host [Orchestra]
| Conducted Host
instance Show Orchestra where
show (Conductor h l) = "Conductor " ++ hostName h ++ " (" ++ show l ++ ")"
show (Conducted h) = "Conducted " ++ hostName h
fullOrchestra :: Orchestra -> Bool
fullOrchestra (Conductor _ _) = True
fullOrchestra (Conducted _) = False
topHost :: Orchestra -> Host
topHost (Conducted h) = h
topHost (Conductor h _) = h
allHosts :: Orchestra -> [Host]
allHosts (Conducted h) = [h]
allHosts (Conductor h l) = h : concatMap allHosts l
mkOrchestra :: Host -> Orchestra
mkOrchestra = fromJust . go S.empty
where
go seen h
| S.member (hostName h) seen = Nothing
| otherwise = Just $ case getInfo (hostInfo h) of
ConductorFor [] -> Conducted h
ConductorFor l ->
let seen' = S.insert (hostName h) seen
in Conductor h (mapMaybe (go seen') l)
combineOrchestras :: Orchestra -> Orchestra -> Maybe Orchestra
combineOrchestras a b = combineOrchestras' a b <|> combineOrchestras' b a
combineOrchestras' :: Orchestra -> Orchestra -> Maybe Orchestra
combineOrchestras' (Conducted h) b
| sameHost h (topHost b) = Just b
| otherwise = Nothing
combineOrchestras' (Conductor h os) (Conductor h' os')
| sameHost h h' = Just $ Conductor h (concatMap combineos os')
where
combineos o = case mapMaybe (`combineOrchestras` o) os of
[] -> [o]
os'' -> os''
combineOrchestras' a@(Conductor h _) (Conducted h')
| sameHost h h' = Just a
combineOrchestras' (Conductor h os) b
| null (catMaybes (map snd osgrafts)) = Nothing
| otherwise = Just $ Conductor h (map (uncurry fromMaybe) osgrafts)
where
osgrafts = zip os (map (`combineOrchestras` b) os)
sameHost :: Host -> Host -> Bool
sameHost a b = hostName a == hostName b
deloop :: Host -> Orchestra -> Orchestra
deloop _ (Conducted h) = Conducted h
deloop thehost (Conductor htop ostop) = Conductor htop $
fst $ seekh [] ostop (sameHost htop thehost)
where
seekh l [] seen = (l, seen)
seekh l ((Conducted h) : rest) seen
| sameHost h thehost =
if seen
then seekh l rest seen
else seekh (Conducted h : l) rest True
| otherwise = seekh (Conducted h:l) rest seen
seekh l ((Conductor h os) : rest) seen
| sameHost h thehost =
if seen
then seekh l rest seen
else
let (os', _seen') = seekh [] os True
in seekh (Conductor h os' : l) rest True
| otherwise =
let (os', seen') = seekh [] os seen
in seekh (Conductor h os' : l) rest seen'
extractOrchestras :: [Host] -> [Orchestra]
extractOrchestras = filter fullOrchestra . go [] . map mkOrchestra
where
go os [] = os
go os (o:rest) =
let os' = zip os (map (combineOrchestras o) os)
in case catMaybes (map snd os') of
[] -> go (o:os) rest
[_] -> go (map (uncurry fromMaybe) os') rest
_ -> error "Bug: Host somehow ended up in multiple Orchestras!"
orchestrate :: [Host] -> [Host]
orchestrate hs = map go hs
where
go h
| isOrchestrated (getInfo (hostInfo h)) = h
| otherwise = foldl orchestrate' (removeold h) (map (deloop h) os)
os = extractOrchestras hs
removeold h = foldl removeold' h (oldconductorsof h)
removeold' h oldconductor = h & revert (conductedBy oldconductor)
oldconductors = zip hs (map (getInfo . hostInfo) hs)
oldconductorsof h = flip mapMaybe oldconductors $
\(oldconductor, NotConductorFor l) ->
if any (sameHost h) l
then Just oldconductor
else Nothing
orchestrate' :: Host -> Orchestra -> Host
orchestrate' h (Conducted _) = h
orchestrate' h (Conductor c l)
| sameHost h c = cont $ addConductorPrivData h (concatMap allHosts l)
| any (sameHost h) (map topHost l) = cont $ h & conductedBy c
| otherwise = cont h
where
cont h' = foldl orchestrate' h' l
conductorFor :: Host -> Property HasInfo
conductorFor h = infoProperty desc go (addInfo mempty (ConductorFor [h])) []
`requires` toProp (conductorKnownHost h)
`requires` Ssh.installed
where
desc = cdesc (hostName h)
go = ifM (isOrchestrated <$> askInfo)
( do
pm <- liftIO $ filterPrivData h
<$> readPrivDataFile privDataLocal
liftIO $ spin' (Just pm) Nothing (hostName h) h
noChange
, do
warningMessage "Can't conduct; either orchestrate has not been used, or there is a conductor loop."
return FailedChange
)
notConductorFor :: Host -> Property HasInfo
notConductorFor h = infoProperty desc (return NoChange) (addInfo mempty (NotConductorFor [h])) []
`requires` toProp (revert (conductorKnownHost h))
where
desc = "not " ++ cdesc (hostName h)
conductorKnownHost :: Host -> RevertableProperty
conductorKnownHost h =
mk Ssh.knownHost
<!>
mk Ssh.unknownHost
where
mk p = p [h] (hostName h) (User "root")
addConductorPrivData :: Host -> [Host] -> Host
addConductorPrivData h hs = h { hostInfo = hostInfo h <> i }
where
i = mempty
`addInfo` mconcat (map privinfo hs)
`addInfo` Orchestrated (Any True)
privinfo h' = forceHostContext (hostName h') $ getInfo (hostInfo h')
conductedBy :: Host -> RevertableProperty
conductedBy h = (setup <!> teardown)
`describe` ("conducted by " ++ hostName h)
where
setup = User "root" `Ssh.authorizedKeysFrom` (User "root", h)
`requires` Ssh.installed
teardown = User "root" `Ssh.unauthorizedKeysFrom` (User "root", h)
cdesc :: String -> Desc
cdesc n = "conducting " ++ n
newtype ConductorFor = ConductorFor [Host]
deriving (Typeable, Monoid)
newtype NotConductorFor = NotConductorFor [Host]
deriving (Typeable, Monoid)
instance Show ConductorFor where
show (ConductorFor l) = "ConductorFor " ++ show (map hostName l)
instance Show NotConductorFor where
show (NotConductorFor l) = "NotConductorFor " ++ show (map hostName l)
instance IsInfo ConductorFor where
propagateInfo _ = False
instance IsInfo NotConductorFor where
propagateInfo _ = False
newtype Orchestrated = Orchestrated Any
deriving (Typeable, Monoid, Show)
instance IsInfo Orchestrated where
propagateInfo _ = False
isOrchestrated :: Orchestrated -> Bool
isOrchestrated (Orchestrated v) = getAny v