Revision c407510c

b/src/Ganeti/HTools/Program/Hsqueeze.hs
55 55
  return
56 56
    [ luxi
57 57
    , oDataFile
58
    , oMinResources
58 59
    , oTargetResources
59 60
    , oSaveCluster
60 61
    , oVerbose
......
65 66
arguments :: [ArgCompletion]
66 67
arguments = []
67 68

  
69
-- | The tag-prefix indicating that hsqueeze should consider a node
70
-- as being standby.
71
standbyPrefix :: String
72
standbyPrefix = "htools:standby:"
73

  
74
-- | Predicate of having a standby tag.
75
hasStandbyTag :: Node.Node -> Bool
76
hasStandbyTag = any (standbyPrefix `isPrefixOf`) . Node.nTags
77

  
68 78
-- | Within a cluster configuration, decide if the node hosts only
69 79
-- externally-mirrored instances.
70 80
onlyExternal ::  (Node.List, Instance.List) -> Node.Node -> Bool
......
98 108
                                    $ iterate (>>= balanceStep) (Just ini_tbl)
99 109
  in (nl', il')
100 110

  
101
-- | In a configuration, mark a node as offline.
102
offlineNode :: (Node.List, Instance.List) -> Ndx -> (Node.List, Instance.List)
103
offlineNode (nl, il) ndx =
111
-- | In a configuration, mark a node as online or offline.
112
onlineOfflineNode :: Bool -> (Node.List, Instance.List) -> Ndx ->
113
                     (Node.List, Instance.List)
114
onlineOfflineNode offline (nl, il) ndx =
104 115
  let nd = Container.find ndx nl
105
      nd' = Node.setOffline nd True
116
      nd' = Node.setOffline nd offline
106 117
      nl' = Container.add ndx nd' nl
107 118
  in (nl', il)
108 119

  
109
-- | Offline a list node, and return the state after a balancing attempt.
110
offlineNodes :: [Ndx] -> (Node.List, Instance.List)
111
                -> (Node.List, Instance.List)
112
offlineNodes ndxs conf =
113
  let conf' = foldl offlineNode conf ndxs
120
-- | Offline or online a list nodes, and return the state after a balancing
121
-- attempt.
122
onlineOfflineNodes :: Bool -> [Ndx] -> (Node.List, Instance.List)
123
                      -> (Node.List, Instance.List)
124
onlineOfflineNodes offline ndxs conf =
125
  let conf' = foldl (onlineOfflineNode offline) conf ndxs
114 126
  in balance conf'
115 127

  
116
-- | Predicate on whether a list of nodes can be offlined simultaneously in a
117
-- given configuration, while still leaving enough capacity on every node for
118
-- the given instance
119
canOffline :: Instance.Instance -> [Node.Node] -> (Node.List, Instance.List)
120
              -> Bool
121
canOffline inst nds conf = 
122
  let conf' = offlineNodes (map Node.idx nds) conf
128
-- | Offline a list of nodes, and return the state after balancing.
129
offlineNodes :: [Ndx] -> (Node.List, Instance.List)
130
                -> (Node.List, Instance.List)
131
offlineNodes = onlineOfflineNodes True
132

  
133
-- | Online a list of nodes, and return the state after balancing.
134
onlineNodes :: [Ndx] -> (Node.List, Instance.List)
135
               -> (Node.List, Instance.List)
136
onlineNodes = onlineOfflineNodes False
137

  
138
-- | Predicate on whether a list of nodes can be offlined or onlined
139
-- simultaneously in a given configuration, while still leaving enough
140
-- capacity on every node for the given instance.
141
canOnlineOffline :: Bool -> Instance.Instance -> (Node.List, Instance.List)
142
                    -> [Node.Node] ->Bool
143
canOnlineOffline offline inst conf nds = 
144
  let conf' = onlineOfflineNodes offline (map Node.idx nds) conf
123 145
  in allInstancesOnOnlineNodes conf' && allNodesCapacityFor inst conf'
124 146

  
147
-- | Predicate on whether a list of nodes can be offlined simultaneously.
148
canOffline :: Instance.Instance -> (Node.List, Instance.List) ->
149
              [Node.Node] -> Bool
150
canOffline = canOnlineOffline True
151

  
152
-- | Predicate on whether onlining a list of nodes suffices to get enough
153
-- free resources for given instance.
154
sufficesOnline :: Instance.Instance -> (Node.List, Instance.List)
155
                  -> [Node.Node] ->  Bool
156
sufficesOnline = canOnlineOffline False
157

  
125 158
-- | Greedily offline the nodes, starting from the last element, and return
126 159
-- the list of nodes that could simultaneously be offlined, while keeping
127 160
-- the resources specified by an instance.
......
130 163
greedyOfflineNodes _ _ [] = []
131 164
greedyOfflineNodes inst conf (nd:nds) =
132 165
  let nds' = greedyOfflineNodes inst conf nds
133
  in if canOffline inst (nd:nds') conf then nd:nds' else nds'
166
  in if canOffline inst conf (nd:nds') then nd:nds' else nds'
167

  
168
-- | Try to provide enough resources by onlining an initial segment of
169
-- a list of nodes. Return Nothing, if even onlining all of them is not
170
-- enough.
171
tryOnline :: Instance.Instance -> (Node.List, Instance.List) -> [Node.Node]
172
             -> Maybe [Node.Node]
173
tryOnline inst conf = listToMaybe . filter (sufficesOnline inst conf) . inits
134 174

  
135 175
-- | From a specification, name, and factor create an instance that uses that
136 176
-- factor times the specification, rounded down.
......
151 191

  
152 192
  let verbose = optVerbose opts
153 193
      targetf = optTargetResources opts
194
      minf = optMinResources opts
154 195

  
155 196
  ini_cdata@(ClusterData _ nlf ilf _ ipol) <- loadExternalData opts
156 197

  
157 198
  maybeSaveData (optSaveCluster opts) "original" "before hsqueeze run" ini_cdata
158 199

  
159
  let offlineCandidates = 
200
  let nodelist = IntMap.elems nlf
201
      offlineCandidates = 
160 202
        sortBy (flip compare `on` length . Node.pList)
161 203
        . filter (foldl (liftA2 (&&)) (const True)
162 204
                  [ not . Node.offline
163 205
                  , not . Node.isMaster
164 206
                  , onlyExternal (nlf, ilf)
165 207
                  ])
166
        . IntMap.elems $ nlf
208
        $ nodelist
209
      onlineCandidates =
210
        filter (liftA2 (&&) Node.offline hasStandbyTag) nodelist
167 211
      conf = (nlf, ilf)
168 212
      std = iPolicyStdSpec ipol
169 213
      targetInstance = instanceFromSpecAndFactor "targetInstance" targetf std
214
      minInstance = instanceFromSpecAndFactor "targetInstance" minf std
170 215
      toOffline = greedyOfflineNodes targetInstance conf offlineCandidates
171
      (fin_nl, fin_il) = offlineNodes (map Node.idx toOffline) conf
172
      final_cdata = ini_cdata { cdNodes = fin_nl, cdInstances = fin_il }
216
      (fin_off_nl, fin_off_il) = offlineNodes (map Node.idx toOffline) conf
217
      final_off_cdata =
218
        ini_cdata { cdNodes = fin_off_nl, cdInstances = fin_off_il }
219
      toOnline = tryOnline minInstance conf onlineCandidates
220
      nodesToOnline = fromMaybe onlineCandidates toOnline
221
      (fin_on_nl, fin_on_il) = onlineNodes (map Node.idx nodesToOnline) conf
222
      final_on_cdata =
223
        ini_cdata { cdNodes = fin_on_nl, cdInstances = fin_on_il }
173 224

  
174 225
  when (verbose > 1) . putStrLn 
175 226
    $ "Offline candidates: " ++ commaJoin (map Node.name offlineCandidates)
176 227

  
177
  unless (optNoHeaders opts) $
178
    putStrLn "'Nodes to offline'"
179

  
180
  mapM_ (putStrLn . Node.name) toOffline
181

  
182
  maybeSaveData (optSaveCluster opts)
183
    "squeezed" "after hsqueeze run" final_cdata
184

  
185
  
228
  when (verbose > 1) . putStrLn
229
    $ "Online candidates: " ++ commaJoin (map Node.name onlineCandidates)
230

  
231
  if not (allNodesCapacityFor minInstance conf)
232
    then do
233
      unless (optNoHeaders opts) $
234
        putStrLn "'Nodes to online'"
235
      mapM_ (putStrLn . Node.name) nodesToOnline
236
      when (verbose > 1 && isNothing toOnline) . putStrLn $
237
        "Onlining all nodes will not yield enough capacity"
238
      maybeSaveData (optSaveCluster opts)
239
         "squeezed" "after hsqueeze expansion" final_on_cdata
240
    else
241
      if null toOffline
242
        then do      
243
          unless (optNoHeaders opts) $
244
            putStrLn "'No action'"
245
          maybeSaveData (optSaveCluster opts)
246
            "squeezed" "after hsqueeze doing nothing" ini_cdata
247
        else do
248
          unless (optNoHeaders opts) $
249
            putStrLn "'Nodes to offline'"
250

  
251
          mapM_ (putStrLn . Node.name) toOffline
252

  
253
          maybeSaveData (optSaveCluster opts)
254
            "squeezed" "after hsqueeze run" final_off_cdata

Also available in: Unified diff