Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hsqueeze.hs @ bbc6620d

History | View | Annotate | Download (9.5 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

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

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

    
65
-- | The list of arguments supported by the program.
66
arguments :: [ArgCompletion]
67
arguments = []
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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
197
  let verbose = optVerbose opts
198
      targetf = optTargetResources opts
199
      minf = optMinResources opts
200

    
201
  ini_cdata@(ClusterData _ nlf ilf _ ipol) <- loadExternalData opts
202

    
203
  maybeSaveData (optSaveCluster opts) "original" "before hsqueeze run" ini_cdata
204

    
205
  let nodelist = IntMap.elems nlf
206
      offlineCandidates = 
207
        sortBy (flip compare `on` length . Node.pList)
208
        . filter (foldl (liftA2 (&&)) (const True)
209
                  [ not . Node.offline
210
                  , not . Node.isMaster
211
                  , onlyExternal (nlf, ilf)
212
                  ])
213
        $ nodelist
214
      onlineCandidates =
215
        filter (liftA2 (&&) Node.offline hasStandbyTag) nodelist
216
      conf = (nlf, ilf)
217
      std = iPolicyStdSpec ipol
218
      targetInstance = instanceFromSpecAndFactor "targetInstance" targetf std
219
      minInstance = instanceFromSpecAndFactor "targetInstance" minf std
220
      toOffline = greedyOfflineNodes targetInstance conf offlineCandidates
221
      (fin_off_nl, fin_off_il) =
222
        fst $ offlineNodes (map Node.idx toOffline) conf
223
      final_off_cdata =
224
        ini_cdata { cdNodes = fin_off_nl, cdInstances = fin_off_il }
225
      toOnline = tryOnline minInstance conf onlineCandidates
226
      nodesToOnline = fromMaybe onlineCandidates toOnline
227
      (fin_on_nl, fin_on_il) =
228
        fst $ onlineNodes (map Node.idx nodesToOnline) conf
229
      final_on_cdata =
230
        ini_cdata { cdNodes = fin_on_nl, cdInstances = fin_on_il }
231

    
232
  when (verbose > 1) . putStrLn 
233
    $ "Offline candidates: " ++ commaJoin (map Node.name offlineCandidates)
234

    
235
  when (verbose > 1) . putStrLn
236
    $ "Online candidates: " ++ commaJoin (map Node.name onlineCandidates)
237

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

    
258
          mapM_ (putStrLn . Node.name) toOffline
259

    
260
          maybeSaveData (optSaveCluster opts)
261
            "squeezed" "after hsqueeze run" final_off_cdata