Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (9.2 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) -> (Node.List, Instance.List)
103
balance (nl, il) =
104
  let ini_cv = Cluster.compCV nl
105
      ini_tbl = Cluster.Table nl il ini_cv []
106
      balanceStep tbl = Cluster.tryBalance tbl True True False 0.0 0.0
107
      (Cluster.Table nl' il' _ _) = fromJust . last . takeWhile isJust
108
                                    $ iterate (>>= balanceStep) (Just ini_tbl)
109
  in (nl', il')
110

    
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 =
115
  let nd = Container.find ndx nl
116
      nd' = Node.setOffline nd offline
117
      nl' = Container.add ndx nd' nl
118
  in (nl', il)
119

    
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
126
  in balance conf'
127

    
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
145
  in allInstancesOnOnlineNodes conf' && allNodesCapacityFor inst conf'
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

    
158
-- | Greedily offline the nodes, starting from the last element, and return
159
-- the list of nodes that could simultaneously be offlined, while keeping
160
-- the resources specified by an instance.
161
greedyOfflineNodes :: Instance.Instance -> (Node.List, Instance.List) 
162
                      -> [Node.Node] -> [Node.Node]
163
greedyOfflineNodes _ _ [] = []
164
greedyOfflineNodes inst conf (nd:nds) =
165
  let nds' = greedyOfflineNodes inst conf 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
174

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

    
187
-- | Main function.
188
main :: Options -> [String] -> IO ()
189
main opts args = do
190
  unless (null args) $ exitErr "This program doesn't take any arguments."
191

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

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

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

    
200
  let nodelist = IntMap.elems nlf
201
      offlineCandidates = 
202
        sortBy (flip compare `on` length . Node.pList)
203
        . filter (foldl (liftA2 (&&)) (const True)
204
                  [ not . Node.offline
205
                  , not . Node.isMaster
206
                  , onlyExternal (nlf, ilf)
207
                  ])
208
        $ nodelist
209
      onlineCandidates =
210
        filter (liftA2 (&&) Node.offline hasStandbyTag) nodelist
211
      conf = (nlf, ilf)
212
      std = iPolicyStdSpec ipol
213
      targetInstance = instanceFromSpecAndFactor "targetInstance" targetf std
214
      minInstance = instanceFromSpecAndFactor "targetInstance" minf std
215
      toOffline = greedyOfflineNodes targetInstance conf offlineCandidates
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 }
224

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

    
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