module Ganeti.HTools.Repair
( InstanceData(..)
, parseInitTag
, getArData
, arStateName
, delCurTag
, setInitialState
, arStatusCmp
, updateTag
, detectBroken
) where
import Control.Monad (mplus, foldM)
import Data.Function (on)
import Data.List (sortBy, groupBy, intercalate)
import Data.Maybe (mapMaybe, fromJust)
import Data.Ord (comparing)
import System.Time (ClockTime(TOD))
import Ganeti.BasicTypes (GenericResult(..), Result)
import qualified Ganeti.Constants as C
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Instance as Instance
import qualified Ganeti.HTools.Node as Node
import qualified Ganeti.HTools.Tags.Constants as Tags
import Ganeti.HTools.Types
import Ganeti.OpCodes (OpCode(..))
import Ganeti.OpParams ( RecreateDisksInfo(RecreateDisksAll)
, ReplaceDisksMode(ReplaceNewSecondary)
)
import Ganeti.Types (makeJobIdS, fromJobId, mkNonEmpty, mkNonNegative)
import Ganeti.Utils (chompPrefix, sepSplit, tryRead, clockTimeToString)
data InstanceData = InstanceData { arInstance :: Instance.Instance
, arState :: AutoRepairStatus
, tagsToRemove :: [String]
}
deriving (Eq, Show)
parseInitTag :: String -> Maybe AutoRepairData
parseInitTag tag =
let parsePending = do
subtag <- chompPrefix Tags.autoRepairTagPending tag
case sepSplit ':' subtag of
[rtype, uuid, ts, jobs] -> makeArData rtype uuid ts jobs
_ -> fail ("Invalid tag: " ++ show tag)
parseResult = do
subtag <- chompPrefix Tags.autoRepairTagResult tag
case sepSplit ':' subtag of
[rtype, uuid, ts, result, jobs] -> do
arData <- makeArData rtype uuid ts jobs
result' <- autoRepairResultFromRaw result
return arData { arResult = Just result' }
_ -> fail ("Invalid tag: " ++ show tag)
makeArData rtype uuid ts jobs = do
rtype' <- autoRepairTypeFromRaw rtype
ts' <- tryRead "auto-repair time" ts
jobs' <- mapM makeJobIdS $ sepSplit '+' jobs
return AutoRepairData { arType = rtype'
, arUuid = uuid
, arTime = TOD ts' 0
, arJobs = jobs'
, arResult = Nothing
, arTag = tag
}
in
parsePending `mplus` parseResult
getArData :: AutoRepairStatus -> Maybe AutoRepairData
getArData status =
case status of
ArHealthy (Just d) -> Just d
ArFailedRepair d -> Just d
ArPendingRepair d -> Just d
ArNeedsRepair d -> Just d
_ -> Nothing
arStateName :: AutoRepairStatus -> String
arStateName status =
case status of
ArHealthy _ -> "Healthy"
ArFailedRepair _ -> "Failure"
ArPendingRepair _ -> "Pending repair"
ArNeedsRepair _ -> "Needs repair"
delCurTag :: InstanceData -> [String]
delCurTag instData =
let arData = getArData $ arState instData
rmTags = tagsToRemove instData
in
case arData of
Just d -> arTag d : rmTags
Nothing -> rmTags
setInitialState :: Instance.Instance -> Result InstanceData
setInitialState inst =
let arData = mapMaybe parseInitTag $ Instance.allTags inst
arData' = sortBy (comparing arUuid) arData
arGroups = groupBy ((==) `on` arUuid) arData'
arGroups' = sortBy (comparing $ minimum . map arTime) arGroups
in
foldM arStatusCmp (InstanceData inst (ArHealthy Nothing) []) arGroups'
arStatusCmp :: InstanceData -> [AutoRepairData] -> Result InstanceData
arStatusCmp instData arData =
let curSt = arState instData
arData' = sortBy (comparing keyfn) arData
keyfn d = (arResult d, arTime d)
newData = last arData'
newSt = case arResult newData of
Just ArSuccess -> ArHealthy $ Just newData
Just ArEnoperm -> ArHealthy $ Just newData
Just ArFailure -> ArFailedRepair newData
Nothing -> ArPendingRepair newData
in
case curSt of
ArFailedRepair _ -> Ok instData
ArHealthy _ -> Ok instData { arState = newSt
, tagsToRemove = delCurTag instData
}
ArPendingRepair d -> Bad (
"An unfinished repair was found in instance " ++
Instance.name (arInstance instData) ++ ": found tag " ++
show (arTag newData) ++ ", but older pending tag " ++
show (arTag d) ++ "exists.")
ArNeedsRepair _ -> Bad
"programming error: ArNeedsRepair found as an initial state"
updateTag :: AutoRepairData -> AutoRepairData
updateTag arData =
let ini = [autoRepairTypeToRaw $ arType arData,
arUuid arData,
clockTimeToString $ arTime arData]
end = [intercalate "+" . map (show . fromJobId) $ arJobs arData]
(pfx, middle) =
case arResult arData of
Nothing -> (Tags.autoRepairTagPending, [])
Just rs -> (Tags.autoRepairTagResult, [autoRepairResultToRaw rs])
in
arData { arTag = pfx ++ intercalate ":" (ini ++ middle ++ end) }
detectBroken :: Node.List -> Instance.Instance
-> Maybe (AutoRepairType, [OpCode])
detectBroken nl inst =
let disk = Instance.diskTemplate inst
iname = Instance.name inst
offPri = Node.offline $ Container.find (Instance.pNode inst) nl
offSec = Node.offline $ Container.find (Instance.sNode inst) nl
in
case disk of
DTDrbd8
| offPri && offSec ->
Just (
ArReinstall,
[ OpInstanceRecreateDisks { opInstanceName = iname
, opInstanceUuid = Nothing
, opRecreateDisksInfo = RecreateDisksAll
, opNodes = []
, opNodeUuids = Nothing
, opIallocator = mkNonEmpty "hail"
}
, OpInstanceReinstall { opInstanceName = iname
, opInstanceUuid = Nothing
, opOsType = Nothing
, opTempOsParams = Nothing
, opOsparamsPrivate = Nothing
, opOsparamsSecret = Nothing
, opForceVariant = False
}
])
| offPri ->
Just (
ArFailover,
[ OpInstanceFailover { opInstanceName = iname
, opInstanceUuid = Nothing
, opShutdownTimeout = fromJust $ mkNonNegative
C.defaultShutdownTimeout
, opIgnoreConsistency = False
, opTargetNode = Nothing
, opTargetNodeUuid = Nothing
, opIgnoreIpolicy = False
, opIallocator = Nothing
, opMigrationCleanup = False
}
])
| offSec ->
Just (
ArFixStorage,
[ OpInstanceReplaceDisks { opInstanceName = iname
, opInstanceUuid = Nothing
, opReplaceDisksMode = ReplaceNewSecondary
, opReplaceDisksList = []
, opRemoteNode = Nothing
, opRemoteNodeUuid = Nothing
, opIallocator = mkNonEmpty "hail"
, opEarlyRelease = False
, opIgnoreIpolicy = False
}
])
| otherwise -> Nothing
DTPlain
| offPri ->
Just (
ArReinstall,
[ OpInstanceRecreateDisks { opInstanceName = iname
, opInstanceUuid = Nothing
, opRecreateDisksInfo = RecreateDisksAll
, opNodes = []
, opNodeUuids = Nothing
, opIallocator = mkNonEmpty "hail"
}
, OpInstanceReinstall { opInstanceName = iname
, opInstanceUuid = Nothing
, opOsType = Nothing
, opTempOsParams = Nothing
, opOsparamsPrivate = Nothing
, opOsparamsSecret = Nothing
, opForceVariant = False
}
])
| otherwise -> Nothing
_ -> Nothing