Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hsqueeze.hs @ 81879d92

History | View | Annotate | Download (10.1 kB)

1
{-| Node freeing scheduler
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2013 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.HTools.Program.Hsqueeze
27
  (main
28
  , options
29
  , arguments
30
  ) where
31

    
32
import Control.Applicative
33
import Control.Monad
34
import Data.Function
35
import Data.List
36
import Data.Maybe
37
import qualified Data.IntMap as IntMap
38
import Text.Printf (printf)
39

    
40
import Ganeti.BasicTypes
41
import Ganeti.Common
42
import Ganeti.HTools.CLI
43
import qualified Ganeti.HTools.Container as Container
44
import qualified Ganeti.HTools.Cluster as Cluster
45
import Ganeti.HTools.ExtLoader
46
import qualified Ganeti.HTools.Instance as Instance
47
import Ganeti.HTools.Loader
48
import qualified Ganeti.HTools.Node as Node
49
import Ganeti.HTools.Types
50
import Ganeti.Utils
51

    
52
-- | Options list and functions.
53
options :: IO [OptType]
54
options = do
55
  luxi <- oLuxiSocket
56
  return
57
    [ luxi
58
    , oDataFile
59
    , oMinResources
60
    , oTargetResources
61
    , oSaveCluster
62
    , oPrintCommands
63
    , oVerbose
64
    , oNoHeaders
65
    ]
66

    
67
-- | The list of arguments supported by the program.
68
arguments :: [ArgCompletion]
69
arguments = []
70

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

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

    
80
-- | Within a cluster configuration, decide if the node hosts only
81
-- externally-mirrored instances.
82
onlyExternal ::  (Node.List, Instance.List) -> Node.Node -> Bool
83
onlyExternal (_, il) nd =
84
  not
85
  . any (Instance.usesLocalStorage . flip Container.find il)
86
  $ Node.pList nd
87

    
88
-- | Predicate whether, in a configuration, all running instances are on
89
-- online nodes.
90
allInstancesOnOnlineNodes :: (Node.List, Instance.List) -> Bool
91
allInstancesOnOnlineNodes (nl, il) =
92
 all (not . Node.offline . flip Container.find nl . Instance.pNode)
93
 . IntMap.elems
94
 $ il
95

    
96
-- | Predicate whether, in a configuration, each node has enough resources 
97
-- to additionally host the given instance.
98
allNodesCapacityFor :: Instance.Instance -> (Node.List, Instance.List) -> Bool
99
allNodesCapacityFor inst (nl, _) =
100
  all (isOk . flip Node.addPri inst) . IntMap.elems $ nl
101

    
102
-- | Balance a configuration, possible for 0 steps, till no further improvement
103
-- is possible.
104
balance :: (Node.List, Instance.List) 
105
           -> ((Node.List, Instance.List), [MoveJob])
106
balance (nl, il) =
107
  let ini_cv = Cluster.compCV nl
108
      ini_tbl = Cluster.Table nl il ini_cv []
109
      balanceStep tbl = Cluster.tryBalance tbl True True False 0.0 0.0
110
      bTables = map fromJust . takeWhile isJust
111
                  $ iterate (>>= balanceStep) (Just ini_tbl)
112
      (Cluster.Table nl' il' _ _) = last bTables
113
      moves = zip bTables (drop 1 bTables) >>= Cluster.getMoves
114
  in ((nl', il'), reverse moves)
115

    
116
-- | In a configuration, mark a node as online or offline.
117
onlineOfflineNode :: Bool -> (Node.List, Instance.List) -> Ndx ->
118
                     (Node.List, Instance.List)
119
onlineOfflineNode offline (nl, il) ndx =
120
  let nd = Container.find ndx nl
121
      nd' = Node.setOffline nd offline
122
      nl' = Container.add ndx nd' nl
123
  in (nl', il)
124

    
125
-- | Offline or online a list nodes, and return the state after a balancing
126
-- attempt together with the sequence of moves that lead there.
127
onlineOfflineNodes :: Bool -> [Ndx] -> (Node.List, Instance.List)
128
                      -> ((Node.List, Instance.List), [MoveJob])
129
onlineOfflineNodes offline ndxs conf =
130
  let conf' = foldl (onlineOfflineNode offline) conf ndxs
131
  in balance conf'
132

    
133
-- | Offline a list of nodes, and return the state after balancing with
134
-- the sequence of moves that lead there.
135
offlineNodes :: [Ndx] -> (Node.List, Instance.List)
136
                -> ((Node.List, Instance.List), [MoveJob])
137
offlineNodes = onlineOfflineNodes True
138

    
139
-- | Online a list of nodes, and return the state after balancing with
140
-- the sequence of moves that lead there.
141
onlineNodes :: [Ndx] -> (Node.List, Instance.List)
142
               -> ((Node.List, Instance.List), [MoveJob])
143
onlineNodes = onlineOfflineNodes False
144

    
145
-- | Predicate on whether a list of nodes can be offlined or onlined
146
-- simultaneously in a given configuration, while still leaving enough
147
-- capacity on every node for the given instance.
148
canOnlineOffline :: Bool -> Instance.Instance -> (Node.List, Instance.List)
149
                    -> [Node.Node] ->Bool
150
canOnlineOffline offline inst conf nds = 
151
  let conf' = fst $ onlineOfflineNodes offline (map Node.idx nds) conf
152
  in allInstancesOnOnlineNodes conf' && allNodesCapacityFor inst conf'
153

    
154
-- | Predicate on whether a list of nodes can be offlined simultaneously.
155
canOffline :: Instance.Instance -> (Node.List, Instance.List) ->
156
              [Node.Node] -> Bool
157
canOffline = canOnlineOffline True
158

    
159
-- | Predicate on whether onlining a list of nodes suffices to get enough
160
-- free resources for given instance.
161
sufficesOnline :: Instance.Instance -> (Node.List, Instance.List)
162
                  -> [Node.Node] ->  Bool
163
sufficesOnline = canOnlineOffline False
164

    
165
-- | Greedily offline the nodes, starting from the last element, and return
166
-- the list of nodes that could simultaneously be offlined, while keeping
167
-- the resources specified by an instance.
168
greedyOfflineNodes :: Instance.Instance -> (Node.List, Instance.List) 
169
                      -> [Node.Node] -> [Node.Node]
170
greedyOfflineNodes _ _ [] = []
171
greedyOfflineNodes inst conf (nd:nds) =
172
  let nds' = greedyOfflineNodes inst conf nds
173
  in if canOffline inst conf (nd:nds') then nd:nds' else nds'
174

    
175
-- | Try to provide enough resources by onlining an initial segment of
176
-- a list of nodes. Return Nothing, if even onlining all of them is not
177
-- enough.
178
tryOnline :: Instance.Instance -> (Node.List, Instance.List) -> [Node.Node]
179
             -> Maybe [Node.Node]
180
tryOnline inst conf = listToMaybe . filter (sufficesOnline inst conf) . inits
181

    
182
-- | From a specification, name, and factor create an instance that uses that
183
-- factor times the specification, rounded down.
184
instanceFromSpecAndFactor :: String -> Double -> ISpec -> Instance.Instance
185
instanceFromSpecAndFactor name f spec =
186
  Instance.create name
187
    (floor (f * fromIntegral (iSpecMemorySize spec)))
188
    0 []
189
    (floor (f * fromIntegral (iSpecCpuCount spec)))
190
    Running [] False Node.noSecondary Node.noSecondary DTExt
191
    (floor (f * fromIntegral (iSpecSpindleUse spec)))
192
    []
193

    
194
-- | Main function.
195
main :: Options -> [String] -> IO ()
196
main opts args = do
197
  unless (null args) $ exitErr "This program doesn't take any arguments."
198

    
199
  let verbose = optVerbose opts
200
      targetf = optTargetResources opts
201
      minf = optMinResources opts
202

    
203
  ini_cdata@(ClusterData _ nlf ilf _ ipol) <- loadExternalData opts
204

    
205
  maybeSaveData (optSaveCluster opts) "original" "before hsqueeze run" ini_cdata
206

    
207
  let nodelist = IntMap.elems nlf
208
      offlineCandidates = 
209
        sortBy (flip compare `on` length . Node.pList)
210
        . filter (foldl (liftA2 (&&)) (const True)
211
                  [ not . Node.offline
212
                  , not . Node.isMaster
213
                  , onlyExternal (nlf, ilf)
214
                  ])
215
        $ nodelist
216
      onlineCandidates =
217
        filter (liftA2 (&&) Node.offline hasStandbyTag) nodelist
218
      conf = (nlf, ilf)
219
      std = iPolicyStdSpec ipol
220
      targetInstance = instanceFromSpecAndFactor "targetInstance" targetf std
221
      minInstance = instanceFromSpecAndFactor "targetInstance" minf std
222
      toOffline = greedyOfflineNodes targetInstance conf offlineCandidates
223
      ((fin_off_nl, fin_off_il), off_mvs) =
224
        offlineNodes (map Node.idx toOffline) conf
225
      final_off_cdata =
226
        ini_cdata { cdNodes = fin_off_nl, cdInstances = fin_off_il }
227
      off_jobs = Cluster.splitJobs off_mvs
228
      off_cmd =
229
        Cluster.formatCmds off_jobs
230
        ++ "\necho Power Commands\n"
231
        ++ (toOffline >>= printf "  gnt-node power -f off %s\n" . Node.alias)
232
      toOnline = tryOnline minInstance conf onlineCandidates
233
      nodesToOnline = fromMaybe onlineCandidates toOnline
234
      ((fin_on_nl, fin_on_il), on_mvs) =
235
        onlineNodes (map Node.idx nodesToOnline) conf
236
      final_on_cdata =
237
        ini_cdata { cdNodes = fin_on_nl, cdInstances = fin_on_il }
238
      on_jobs = Cluster.splitJobs on_mvs
239
      on_cmd =
240
        "echo Power Commands\n"
241
        ++ (nodesToOnline >>= printf "  gnt-node power -f on %s\n" . Node.alias)
242
        ++ Cluster.formatCmds on_jobs
243

    
244
  when (verbose > 1) . putStrLn 
245
    $ "Offline candidates: " ++ commaJoin (map Node.name offlineCandidates)
246

    
247
  when (verbose > 1) . putStrLn
248
    $ "Online candidates: " ++ commaJoin (map Node.name onlineCandidates)
249

    
250
  if not (allNodesCapacityFor minInstance conf)
251
    then do
252
      unless (optNoHeaders opts) $
253
        putStrLn "'Nodes to online'"
254
      mapM_ (putStrLn . Node.name) nodesToOnline
255
      when (verbose > 1 && isNothing toOnline) . putStrLn $
256
        "Onlining all nodes will not yield enough capacity"
257
      maybeSaveCommands "Commands to run:" opts on_cmd
258
      maybeSaveData (optSaveCluster opts)
259
         "squeezed" "after hsqueeze expansion" final_on_cdata
260
    else
261
      if null toOffline
262
        then do      
263
          unless (optNoHeaders opts) $
264
            putStrLn "'No action'"
265
          maybeSaveCommands "Commands to run:" opts "echo Nothing to do"
266
          maybeSaveData (optSaveCluster opts)
267
            "squeezed" "after hsqueeze doing nothing" ini_cdata
268
        else do
269
          unless (optNoHeaders opts) $
270
            putStrLn "'Nodes to offline'"
271
          mapM_ (putStrLn . Node.name) toOffline
272
          maybeSaveCommands "Commands to run:" opts off_cmd
273
          maybeSaveData (optSaveCluster opts)
274
            "squeezed" "after hsqueeze run" final_off_cdata