ganeti-htoolsSource codeContentsIndex
Ganeti.HTools.Cluster
Contents
Types
Utility functions
Balancing functions
Allocation functions
Formatting functions
Node group functions
Description

Implementation of cluster-wide logic.

This module holds all pure cluster-logic; I/O related functionality goes into the Main module for the individual binaries.

Synopsis
data AllocSolution = AllocSolution {
asFailures :: [FailMode]
asAllocs :: Int
asSolution :: Maybe AllocElement
asLog :: [String]
}
data EvacSolution = EvacSolution {
esMoved :: [(Idx, Gdx, [Ndx])]
esFailed :: [(Idx, String)]
esOpCodes :: [[OpCode]]
}
type AllocResult = (FailStats, List, List, [Instance], [CStats])
type AllocNodes = Either [Ndx] [(Ndx, [Ndx])]
emptyAllocSolution :: AllocSolution
emptyEvacSolution :: EvacSolution
data Table = Table List List Score [Placement]
data CStats = CStats {
csFmem :: Integer
csFdsk :: Integer
csAmem :: Integer
csAdsk :: Integer
csAcpu :: Integer
csMmem :: Integer
csMdsk :: Integer
csMcpu :: Integer
csImem :: Integer
csIdsk :: Integer
csIcpu :: Integer
csTmem :: Double
csTdsk :: Double
csTcpu :: Double
csVcpu :: Integer
csNcpu :: Double
csXmem :: Integer
csNmem :: Integer
csScore :: Score
csNinst :: Int
}
type AllocMethod = List -> List -> Maybe Int -> Instance -> AllocNodes -> [Instance] -> [CStats] -> Result AllocResult
type EvacInnerState = Either String (List, Instance, Score, Ndx)
verifyN1 :: [Node] -> [Node]
computeBadItems :: List -> List -> ([Node], [Instance])
instanceNodes :: List -> Instance -> (Ndx, Ndx, Node, Node)
emptyCStats :: CStats
updateCStats :: CStats -> Node -> CStats
totalResources :: List -> CStats
computeAllocationDelta :: CStats -> CStats -> AllocStats
detailedCVInfo :: [(Double, String)]
detailedCVWeights :: [Double]
compDetailedCV :: [Node] -> [Double]
compCVNodes :: [Node] -> Double
compCV :: List -> Double
getOnline :: List -> [Node]
compareTables :: Table -> Table -> Table
applyMove :: List -> Instance -> IMove -> OpResult (List, Instance, Ndx, Ndx)
allocateOnSingle :: List -> Instance -> Ndx -> OpResult AllocElement
allocateOnPair :: List -> Instance -> Ndx -> Ndx -> OpResult AllocElement
checkSingleStep :: Table -> Instance -> Table -> IMove -> Table
possibleMoves :: MirrorType -> Bool -> Bool -> Ndx -> [IMove]
checkInstanceMove :: [Ndx] -> Bool -> Bool -> Table -> Instance -> Table
checkMove :: [Ndx] -> Bool -> Bool -> Table -> [Instance] -> Table
doNextBalance :: Table -> Int -> Score -> Bool
tryBalance :: Table -> Bool -> Bool -> Bool -> Score -> Score -> Maybe Table
collapseFailures :: [FailMode] -> FailStats
bestAllocElement :: Maybe AllocElement -> Maybe AllocElement -> Maybe AllocElement
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolution
sumAllocs :: AllocSolution -> AllocSolution -> AllocSolution
describeSolution :: AllocSolution -> String
annotateSolution :: AllocSolution -> AllocSolution
reverseEvacSolution :: EvacSolution -> EvacSolution
genAllocNodes :: List -> List -> Int -> Bool -> Result AllocNodes
tryAlloc :: Monad m => List -> List -> Instance -> AllocNodes -> m AllocSolution
solutionDescription :: List -> (Gdx, Result AllocSolution) -> [String]
filterMGResults :: List -> [(Gdx, Result AllocSolution)] -> [(Gdx, AllocSolution)]
sortMGResults :: List -> [(Gdx, AllocSolution)] -> [(Gdx, AllocSolution)]
findBestAllocGroup :: List -> List -> List -> Maybe [Gdx] -> Instance -> Int -> Result (Gdx, AllocSolution, [String])
tryMGAlloc :: List -> List -> List -> Instance -> Int -> Result AllocSolution
failOnSecondaryChange :: Monad m => EvacMode -> DiskTemplate -> m ()
nodeEvacInstance :: List -> List -> EvacMode -> Instance -> Gdx -> [Ndx] -> Result (List, List, [OpCode])
evacOneNodeOnly :: List -> List -> Instance -> Gdx -> [Ndx] -> Result (List, List, [OpCode])
evacOneNodeInner :: List -> Instance -> Gdx -> (Ndx -> IMove) -> EvacInnerState -> Ndx -> EvacInnerState
evacDrbdAllInner :: List -> List -> Instance -> Gdx -> (Ndx, Ndx) -> Result (List, List, [OpCode], Score)
availableGroupNodes :: [(Gdx, [Ndx])] -> IntSet -> Gdx -> Result [Ndx]
updateEvacSolution :: (List, List, EvacSolution) -> Idx -> Result (List, List, [OpCode]) -> (List, List, EvacSolution)
tryNodeEvac :: List -> List -> List -> EvacMode -> [Idx] -> Result (List, List, EvacSolution)
tryChangeGroup :: List -> List -> List -> [Gdx] -> [Idx] -> Result (List, List, EvacSolution)
iterateAlloc :: AllocMethod
tieredAlloc :: AllocMethod
computeMoves :: Instance -> String -> IMove -> String -> String -> (String, [String])
printSolutionLine :: List -> List -> Int -> Int -> Placement -> Int -> (String, [String])
involvedNodes :: List -> Placement -> [Ndx]
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
splitJobs :: [MoveJob] -> [JobSet]
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
formatCmds :: [JobSet] -> String
printNodes :: List -> [String] -> String
printInsts :: List -> List -> String
printStats :: String -> List -> String
iMoveToJob :: List -> List -> Idx -> IMove -> [OpCode]
instanceGroup :: List -> Instance -> Result Gdx
instancePriGroup :: List -> Instance -> Gdx
findSplitInstances :: List -> List -> [Instance]
splitCluster :: List -> List -> [(Gdx, (List, List))]
nodesToEvacuate :: List -> EvacMode -> [Idx] -> IntSet
Types
data AllocSolution Source
Allocation/relocation solution.
Constructors
AllocSolution
asFailures :: [FailMode]Failure counts
asAllocs :: IntGood allocation count
asSolution :: Maybe AllocElementThe actual allocation result
asLog :: [String]Informational messages
data EvacSolution Source
Node evacuation/group change iallocator result type. This result type consists of actual opcodes (a restricted subset) that are transmitted back to Ganeti.
Constructors
EvacSolution
esMoved :: [(Idx, Gdx, [Ndx])]Instances moved successfully
esFailed :: [(Idx, String)]Instances which were not relocated
esOpCodes :: [[OpCode]]List of jobs
type AllocResult = (FailStats, List, List, [Instance], [CStats])Source
Allocation results, as used in iterateAlloc and tieredAlloc.
type AllocNodes = Either [Ndx] [(Ndx, [Ndx])]Source

A type denoting the valid allocation mode/pairs.

For a one-node allocation, this will be a Left [Ndx], whereas for a two-node allocation, this will be a Right [(Ndx, [Ndx])]. In the latter case, the list is basically an association list, grouped by primary node and holding the potential secondary nodes in the sub-list.

emptyAllocSolution :: AllocSolutionSource
The empty solution we start with when computing allocations.
emptyEvacSolution :: EvacSolutionSource
The empty evac solution.
data Table Source
The complete state for the balancing solution.
Constructors
Table List List Score [Placement]
data CStats Source
Cluster statistics data type.
Constructors
CStats
csFmem :: IntegerCluster free mem
csFdsk :: IntegerCluster free disk
csAmem :: IntegerCluster allocatable mem
csAdsk :: IntegerCluster allocatable disk
csAcpu :: IntegerCluster allocatable cpus
csMmem :: IntegerMax node allocatable mem
csMdsk :: IntegerMax node allocatable disk
csMcpu :: IntegerMax node allocatable cpu
csImem :: IntegerInstance used mem
csIdsk :: IntegerInstance used disk
csIcpu :: IntegerInstance used cpu
csTmem :: DoubleCluster total mem
csTdsk :: DoubleCluster total disk
csTcpu :: DoubleCluster total cpus
csVcpu :: IntegerCluster total virtual cpus
csNcpu :: DoubleEquivalent to csIcpu but in terms of physical CPUs, i.e. normalised used phys CPUs
csXmem :: IntegerUnnacounted for mem
csNmem :: IntegerNode own memory
csScore :: ScoreThe cluster score
csNinst :: IntThe total number of instances
type AllocMethodSource
 = ListNode list
-> ListInstance list
-> Maybe IntOptional allocation limit
-> InstanceInstance spec for allocation
-> AllocNodesWhich nodes we should allocate on
-> [Instance]Allocated instances
-> [CStats]Running cluster stats
-> Result AllocResultAllocation result
A simple type for allocation functions.
type EvacInnerState = Either String (List, Instance, Score, Ndx)Source
A simple type for the running solution of evacuations.
Utility functions
verifyN1 :: [Node] -> [Node]Source
Verifies the N+1 status and return the affected nodes.
computeBadItems :: List -> List -> ([Node], [Instance])Source

Computes the pair of bad nodes and instances.

The bad node list is computed via a simple verifyN1 check, and the bad instance list is the list of primary and secondary instances of those nodes.

instanceNodes :: List -> Instance -> (Ndx, Ndx, Node, Node)Source
Extracts the node pairs for an instance. This can fail if the instance is single-homed. FIXME: this needs to be improved, together with the general enhancement for handling non-DRBD moves.
emptyCStats :: CStatsSource
Zero-initializer for the CStats type.
updateCStats :: CStats -> Node -> CStatsSource
Update stats with data from a new node.
totalResources :: List -> CStatsSource
Compute the total free disk and memory in the cluster.
computeAllocationDelta :: CStats -> CStats -> AllocStatsSource

Compute the delta between two cluster state.

This is used when doing allocations, to understand better the available cluster resources. The return value is a triple of the current used values, the delta that was still allocated, and what was left unallocated.

detailedCVInfo :: [(Double, String)]Source
The names and weights of the individual elements in the CV list.
detailedCVWeights :: [Double]Source
Holds the weights used by compCVNodes for each metric.
compDetailedCV :: [Node] -> [Double]Source
Compute the mem and disk covariance.
compCVNodes :: [Node] -> DoubleSource
Compute the total variance.
compCV :: List -> DoubleSource
Wrapper over compCVNodes for callers that have a List.
getOnline :: List -> [Node]Source
Compute online nodes from a List.
Balancing functions
compareTables :: Table -> Table -> TableSource
Compute best table. Note that the ordering of the arguments is important.
applyMove :: List -> Instance -> IMove -> OpResult (List, Instance, Ndx, Ndx)Source
Applies an instance move to a given node list and instance.
allocateOnSingle :: List -> Instance -> Ndx -> OpResult AllocElementSource
Tries to allocate an instance on one given node.
allocateOnPair :: List -> Instance -> Ndx -> Ndx -> OpResult AllocElementSource
Tries to allocate an instance on a given pair of nodes.
checkSingleStepSource
:: TableThe original table
-> InstanceThe instance to move
-> TableThe current best table
-> IMoveThe move to apply
-> TableThe final best table
Tries to perform an instance move and returns the best table between the original one and the new one.
possibleMovesSource
:: MirrorTypeThe mirroring type of the instance
-> BoolWhether the secondary node is a valid new node
-> BoolWhether we can change the primary node
-> NdxTarget node candidate
-> [IMove]List of valid result moves
Given the status of the current secondary as a valid new node and the current candidate target node, generate the possible moves for a instance.
checkInstanceMoveSource
:: [Ndx]Allowed target node indices
-> BoolWhether disk moves are allowed
-> BoolWhether instance moves are allowed
-> TableOriginal table
-> InstanceInstance to move
-> TableBest new table for this instance
Compute the best move for a given instance.
checkMoveSource
:: [Ndx]Allowed target node indices
-> BoolWhether disk moves are allowed
-> BoolWhether instance moves are allowed
-> TableThe current solution
-> [Instance]List of instances still to move
-> TableThe new solution
Compute the best next move.
doNextBalanceSource
:: TableThe starting table
-> IntRemaining length
-> ScoreScore at which to stop
-> BoolThe resulting table and commands
Check if we are allowed to go deeper in the balancing.
tryBalanceSource
:: TableThe starting table
-> BoolAllow disk moves
-> BoolAllow instance moves
-> BoolOnly evacuate moves
-> ScoreMin gain threshold
-> ScoreMin gain
-> Maybe TableThe resulting table and commands
Run a balance move.
Allocation functions
collapseFailures :: [FailMode] -> FailStatsSource
Build failure stats out of a list of failures.
bestAllocElement :: Maybe AllocElement -> Maybe AllocElement -> Maybe AllocElementSource
Compares two Maybe AllocElement and chooses the besst score.
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolutionSource
Update current Allocation solution and failure stats with new elements.
sumAllocs :: AllocSolution -> AllocSolution -> AllocSolutionSource
Sums two AllocSolution structures.
describeSolution :: AllocSolution -> StringSource
Given a solution, generates a reasonable description for it.
annotateSolution :: AllocSolution -> AllocSolutionSource
Annotates a solution with the appropriate string.
reverseEvacSolution :: EvacSolution -> EvacSolutionSource

Reverses an evacuation solution.

Rationale: we always concat the results to the top of the lists, so for proper jobset execution, we should reverse all lists.

genAllocNodesSource
:: ListGroup list
-> ListThe node map
-> IntThe number of nodes required
-> BoolWhether to drop or not unallocable nodes
-> Result AllocNodesThe (monadic) result
Generate the valid node allocation singles or pairs for a new instance.
tryAllocSource
:: Monad m
=> ListThe instance list
-> ListThe instance to allocate
-> InstanceThe allocation targets
-> AllocNodesPossible solution list
-> m AllocSolution
Try to allocate an instance on the cluster.
solutionDescription :: List -> (Gdx, Result AllocSolution) -> [String]Source
Given a group/result, describe it as a nice (list of) messages.
filterMGResults :: List -> [(Gdx, Result AllocSolution)] -> [(Gdx, AllocSolution)]Source
From a list of possibly bad and possibly empty solutions, filter only the groups with a valid result. Note that the result will be reversed compared to the original list.
sortMGResults :: List -> [(Gdx, AllocSolution)] -> [(Gdx, AllocSolution)]Source
Sort multigroup results based on policy and score.
findBestAllocGroupSource
:: ListThe group list
-> ListThe node list
-> ListThe instance list
-> Maybe [Gdx]The allowed groups
-> InstanceThe instance to allocate
-> IntRequired number of nodes
-> Result (Gdx, AllocSolution, [String])

Finds the best group for an instance on a multi-group cluster.

Only solutions in preferred and last_resort groups will be accepted as valid, and additionally if the allowed groups parameter is not null then allocation will only be run for those group indices.

tryMGAllocSource
:: ListThe group list
-> ListThe node list
-> ListThe instance list
-> InstanceThe instance to allocate
-> IntRequired number of nodes
-> Result AllocSolutionPossible solution list
Try to allocate an instance on a multi-group cluster.
failOnSecondaryChange :: Monad m => EvacMode -> DiskTemplate -> m ()Source

Function which fails if the requested mode is change secondary.

This is useful since except DRBD, no other disk template can execute change secondary; thus, we can just call this function instead of always checking for secondary mode. After the call to this function, whatever mode we have is just a primary change.

nodeEvacInstanceSource
:: ListThe node list (cluster-wide)
-> ListInstance list (cluster-wide)
-> EvacModeThe evacuation mode
-> InstanceThe instance to be evacuated
-> GdxThe group we're targetting
-> [Ndx]The list of available nodes for allocation
-> Result (List, List, [OpCode])

Run evacuation for a single instance.

Note: this function should correctly execute both intra-group evacuations (in all modes) and inter-group evacuations (in the ChangeAll mode). Of course, this requires that the correct list of target nodes is passed.

evacOneNodeOnlySource
:: ListThe node list (cluster-wide)
-> ListInstance list (cluster-wide)
-> InstanceThe instance to be evacuated
-> GdxThe group we're targetting
-> [Ndx]The list of available nodes for allocation
-> Result (List, List, [OpCode])

Generic function for changing one node of an instance.

This is similar to nodeEvacInstance but will be used in a few of its sub-patterns. It folds the inner function evacOneNodeInner over the list of available nodes, which results in the best choice for relocation.

evacOneNodeInnerSource
:: ListCluster node list
-> InstanceInstance being evacuated
-> GdxThe group index of the instance
-> Ndx -> IMoveOperation constructor
-> EvacInnerStateCurrent best solution
-> NdxNode we're evaluating as target
-> EvacInnerStateNew best solution

Inner fold function for changing one node of an instance.

Depending on the instance disk template, this will either change the secondary (for DRBD) or the primary node (for shared storage). However, the operation is generic otherwise.

The running solution is either a Left String, which means we don't have yet a working solution, or a Right (...), which represents a valid solution; it holds the modified node list, the modified instance (after evacuation), the score of that solution, and the new secondary node index.

evacDrbdAllInnerSource
:: ListCluster node list
-> ListCluster instance list
-> InstanceThe instance to be moved
-> GdxThe target group index (which can differ from the current group of the instance)
-> (Ndx, Ndx)Tuple of new primary/secondary nodes
-> Result (List, List, [OpCode], Score)

Compute result of changing all nodes of a DRBD instance.

Given the target primary and secondary node (which might be in a different group or not), this function will execute all the required steps and assuming all operations succceed, will return the modified node and instance lists, the opcodes needed for this and the new group score.

availableGroupNodesSource
:: [(Gdx, [Ndx])]Group index/node index assoc list
-> IntSetNodes that are excluded
-> GdxThe group for which we query the nodes
-> Result [Ndx]List of available node indices
Computes the nodes in a given group which are available for allocation.
updateEvacSolution :: (List, List, EvacSolution) -> Idx -> Result (List, List, [OpCode]) -> (List, List, EvacSolution)Source
Updates the evac solution with the results of an instance evacuation.
tryNodeEvacSource
:: ListThe cluster groups
-> ListThe node list (cluster-wide, not per group)
-> ListInstance list (cluster-wide)
-> EvacModeThe evacuation mode
-> [Idx]List of instance (indices) to be evacuated
-> Result (List, List, EvacSolution)
Node-evacuation IAllocator mode main function.
tryChangeGroupSource
:: ListThe cluster groups
-> ListThe node list (cluster-wide)
-> ListInstance list (cluster-wide)
-> [Gdx]Target groups; if empty, any groups not being evacuated
-> [Idx]List of instance (indices) to be evacuated
-> Result (List, List, EvacSolution)

Change-group IAllocator mode main function.

This is very similar to tryNodeEvac, the only difference is that we don't choose as target group the current instance group, but instead:

1. at the start of the function, we compute which are the target groups; either no groups were passed in, in which case we choose all groups out of which we don't evacuate instance, or there were some groups passed, in which case we use those

2. for each instance, we use findBestAllocGroup to choose the best group to hold the instance, and then we do what tryNodeEvac does, except for this group instead of the current instance group.

Note that the correct behaviour of this function relies on the function nodeEvacInstance to be able to do correctly both intra-group and inter-group moves when passed the ChangeAll mode.

iterateAlloc :: AllocMethodSource

Standard-sized allocation method.

This places instances of the same size on the cluster until we're out of space. The result will be a list of identically-sized instances.

tieredAlloc :: AllocMethodSource

Tiered allocation method.

This places instances on the cluster, and decreases the spec until we can allocate again. The result will be a list of decreasing instance specs.

Formatting functions
computeMovesSource
:: InstanceThe instance to be moved
-> StringThe instance name
-> IMoveThe move being performed
-> StringNew primary
-> StringNew secondary
-> (String, [String])Tuple of moves and commands list; moves is containing either f for failover or r:name for replace secondary, while the command list holds gnt-instance commands (without that prefix), e.g "failover instance1"
Given the original and final nodes, computes the relocation description.
printSolutionLineSource
:: ListThe node list
-> ListThe instance list
-> IntMaximum node name length
-> IntMaximum instance name length
-> PlacementThe current placement
-> IntThe index of the placement in the solution
-> (String, [String])
Converts a placement to string format.
involvedNodesSource
:: ListInstance list, used for retrieving the instance from its index; note that this must be the original instance list, so that we can retrieve the old nodes
-> PlacementThe placement we're investigating, containing the new nodes and instance index
-> [Ndx]Resulting list of node indices

Return the instance and involved nodes in an instance move.

Note that the output list length can vary, and is not required nor guaranteed to be of any specific length.

mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])Source
Inner function for splitJobs, that either appends the next job to the current jobset, or starts a new jobset.
splitJobs :: [MoveJob] -> [JobSet]Source
Break a list of moves into independent groups. Note that this will reverse the order of jobs.
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]Source
Given a list of commands, prefix them with gnt-instance and also beautify the display a little.
formatCmds :: [JobSet] -> StringSource
Given a list of commands, prefix them with gnt-instance and also beautify the display a little.
printNodes :: List -> [String] -> StringSource
Print the node list.
printInsts :: List -> List -> StringSource
Print the instance list.
printStats :: String -> List -> StringSource
Shows statistics for a given node list.
iMoveToJobSource
:: ListThe node list; only used for node names, so any version is good (before or after the operation)
-> ListThe instance list; also used for names only
-> IdxThe index of the instance being moved
-> IMoveThe actual move to be described
-> [OpCode]The list of opcodes equivalent to the given move
Convert a placement into a list of OpCodes (basically a job).
Node group functions
instanceGroup :: List -> Instance -> Result GdxSource
Computes the group of an instance.
instancePriGroup :: List -> Instance -> GdxSource
Computes the group of an instance per the primary node.
findSplitInstances :: List -> List -> [Instance]Source
Compute the list of badly allocated instances (split across node groups).
splitCluster :: List -> List -> [(Gdx, (List, List))]Source
Splits a cluster into the component node groups.
nodesToEvacuateSource
:: ListThe cluster-wide instance list
-> EvacModeThe evacuation mode we're using
-> [Idx]List of instance indices being evacuated
-> IntSetSet of node indices
Compute the list of nodes that are to be evacuated, given a list of instances and an evacuation mode.
Produced by Haddock version 2.6.0