Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Loader.hs @ f25e5aac

History | View | Annotate | Download (6.5 kB)

1 040afc35 Iustin Pop
{-| Loading data from external sources
2 040afc35 Iustin Pop
3 040afc35 Iustin Pop
This module holds the common code for loading the cluster state from external sources.
4 040afc35 Iustin Pop
5 040afc35 Iustin Pop
-}
6 040afc35 Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 040afc35 Iustin Pop
module Ganeti.HTools.Loader
29 446d8827 Iustin Pop
    ( mergeData
30 446d8827 Iustin Pop
    , checkData
31 446d8827 Iustin Pop
    , assignIndices
32 446d8827 Iustin Pop
    , lookupNode
33 5a1edeb6 Iustin Pop
    , lookupInstance
34 ed41c179 Iustin Pop
    , stripSuffix
35 19f38ee8 Iustin Pop
    , RqType(..)
36 19f38ee8 Iustin Pop
    , Request(..)
37 446d8827 Iustin Pop
    ) where
38 040afc35 Iustin Pop
39 78694255 Iustin Pop
import Data.Function (on)
40 e4c5beaf Iustin Pop
import Data.List
41 446d8827 Iustin Pop
import Data.Maybe (fromJust)
42 446d8827 Iustin Pop
import Text.Printf (printf)
43 e4c5beaf Iustin Pop
44 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Container as Container
45 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
46 e4c5beaf Iustin Pop
import qualified Ganeti.HTools.Node as Node
47 e4c5beaf Iustin Pop
48 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
49 e4c5beaf Iustin Pop
50 19f38ee8 Iustin Pop
-- * Types
51 19f38ee8 Iustin Pop
52 19f38ee8 Iustin Pop
{-| The request type.
53 19f38ee8 Iustin Pop
54 19f38ee8 Iustin Pop
This type denotes what request we got from Ganeti and also holds
55 19f38ee8 Iustin Pop
request-specific fields.
56 19f38ee8 Iustin Pop
57 19f38ee8 Iustin Pop
-}
58 19f38ee8 Iustin Pop
data RqType
59 19f38ee8 Iustin Pop
    = Allocate Instance.Instance Int -- ^ A new instance allocation
60 19f38ee8 Iustin Pop
    | Relocate Idx Int [Ndx]         -- ^ Move an instance to a new
61 19f38ee8 Iustin Pop
                                     -- secondary node
62 19f38ee8 Iustin Pop
    deriving (Show)
63 19f38ee8 Iustin Pop
64 19f38ee8 Iustin Pop
-- | A complete request, as received from Ganeti.
65 19f38ee8 Iustin Pop
data Request = Request RqType Node.List Instance.List String
66 19f38ee8 Iustin Pop
    deriving (Show)
67 19f38ee8 Iustin Pop
68 19f38ee8 Iustin Pop
-- * Functions
69 19f38ee8 Iustin Pop
70 9188aeef Iustin Pop
-- | Lookups a node into an assoc list.
71 608efcce Iustin Pop
lookupNode :: (Monad m) => [(String, Ndx)] -> String -> String -> m Ndx
72 040afc35 Iustin Pop
lookupNode ktn inst node =
73 040afc35 Iustin Pop
    case lookup node ktn of
74 040afc35 Iustin Pop
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
75 040afc35 Iustin Pop
      Just idx -> return idx
76 040afc35 Iustin Pop
77 9188aeef Iustin Pop
-- | Lookups an instance into an assoc list.
78 5a1edeb6 Iustin Pop
lookupInstance :: (Monad m) => [(String, Idx)] -> String -> m Idx
79 5a1edeb6 Iustin Pop
lookupInstance kti inst =
80 5a1edeb6 Iustin Pop
    case lookup inst kti of
81 5a1edeb6 Iustin Pop
      Nothing -> fail $ "Unknown instance '" ++ inst ++ "'"
82 5a1edeb6 Iustin Pop
      Just idx -> return idx
83 5a1edeb6 Iustin Pop
84 9188aeef Iustin Pop
-- | Given a list of elements (and their names), assign indices to them.
85 497e30a1 Iustin Pop
assignIndices :: (Element a) =>
86 497e30a1 Iustin Pop
                 [(String, a)]
87 040afc35 Iustin Pop
              -> (NameAssoc, [(Int, a)])
88 497e30a1 Iustin Pop
assignIndices =
89 497e30a1 Iustin Pop
    unzip . map (\ (idx, (k, v)) -> ((k, idx), (idx, setIdx v idx)))
90 040afc35 Iustin Pop
          . zip [0..]
91 e4c5beaf Iustin Pop
92 78694255 Iustin Pop
-- | Assoc element comparator
93 78694255 Iustin Pop
assocEqual :: (Eq a) => (a, b) -> (a, b) -> Bool
94 78694255 Iustin Pop
assocEqual = (==) `on` fst
95 78694255 Iustin Pop
96 9188aeef Iustin Pop
-- | For each instance, add its index to its primary and secondary nodes.
97 608efcce Iustin Pop
fixNodes :: [(Ndx, Node.Node)]
98 d71d0a1d Iustin Pop
         -> (Idx, Instance.Instance)
99 608efcce Iustin Pop
         -> [(Ndx, Node.Node)]
100 d71d0a1d Iustin Pop
fixNodes accu (idx, inst) =
101 d71d0a1d Iustin Pop
    let
102 d71d0a1d Iustin Pop
        pdx = Instance.pnode inst
103 d71d0a1d Iustin Pop
        sdx = Instance.snode inst
104 d71d0a1d Iustin Pop
        pold = fromJust $ lookup pdx accu
105 d71d0a1d Iustin Pop
        pnew = Node.setPri pold idx
106 d71d0a1d Iustin Pop
        pnew' = Node.addCpus pnew (Instance.vcpus inst)
107 d71d0a1d Iustin Pop
        ac1 = deleteBy assocEqual (pdx, pold) accu
108 d71d0a1d Iustin Pop
        ac2 = (pdx, pnew'):ac1
109 d71d0a1d Iustin Pop
    in
110 d71d0a1d Iustin Pop
      if sdx /= Node.noSecondary
111 d71d0a1d Iustin Pop
      then let sold = fromJust $ lookup sdx accu
112 d71d0a1d Iustin Pop
               snew = Node.setSec sold idx
113 d71d0a1d Iustin Pop
               ac3 = deleteBy assocEqual (sdx, sold) ac2
114 d71d0a1d Iustin Pop
           in (sdx, snew):ac3
115 d71d0a1d Iustin Pop
      else ac2
116 e4c5beaf Iustin Pop
117 f9fc7a63 Iustin Pop
-- | Compute the longest common suffix of a list of strings that
118 9188aeef Iustin Pop
-- | starts with a dot.
119 8472a321 Iustin Pop
longestDomain :: [String] -> String
120 e4c5beaf Iustin Pop
longestDomain [] = ""
121 8472a321 Iustin Pop
longestDomain (x:xs) =
122 8472a321 Iustin Pop
      foldr (\ suffix accu -> if all (isSuffixOf suffix) xs
123 e4c5beaf Iustin Pop
                              then suffix
124 e4c5beaf Iustin Pop
                              else accu)
125 e4c5beaf Iustin Pop
      "" $ filter (isPrefixOf ".") (tails x)
126 e4c5beaf Iustin Pop
127 9188aeef Iustin Pop
-- | Remove tail suffix from a string.
128 26b5d395 Iustin Pop
stripSuffix :: Int -> String -> String
129 9f6dcdea Iustin Pop
stripSuffix sflen name = take (length name - sflen) name
130 e4c5beaf Iustin Pop
131 9188aeef Iustin Pop
-- | Initializer function that loads the data from a node and instance
132 9188aeef Iustin Pop
-- list and massages it into the correct format.
133 e3a684c5 Iustin Pop
mergeData :: (Node.AssocList,
134 e3a684c5 Iustin Pop
              Instance.AssocList) -- ^ Data from either Text.loadData
135 e3a684c5 Iustin Pop
                                  -- or Rapi.loadData
136 262a08a2 Iustin Pop
          -> Result (Node.List, Instance.List, String)
137 e3a684c5 Iustin Pop
mergeData (nl, il) = do
138 e4c5beaf Iustin Pop
  let
139 d71d0a1d Iustin Pop
      nl2 = foldl' fixNodes nl il
140 e4c5beaf Iustin Pop
      il3 = Container.fromAssocList il
141 e4c5beaf Iustin Pop
      nl3 = Container.fromAssocList
142 9cf4267a Iustin Pop
            (map (\ (k, v) -> (k, Node.buildPeers v il3)) nl2)
143 8472a321 Iustin Pop
      node_names = map Node.name $ Container.elems nl3
144 8472a321 Iustin Pop
      inst_names = map Instance.name $ Container.elems il3
145 8472a321 Iustin Pop
      common_suffix = longestDomain (node_names ++ inst_names)
146 26b5d395 Iustin Pop
      csl = length common_suffix
147 262a08a2 Iustin Pop
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
148 262a08a2 Iustin Pop
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il3
149 8472a321 Iustin Pop
  return (snl, sil, common_suffix)
150 446d8827 Iustin Pop
151 9188aeef Iustin Pop
-- | Checks the cluster data for consistency.
152 262a08a2 Iustin Pop
checkData :: Node.List -> Instance.List
153 262a08a2 Iustin Pop
          -> ([String], Node.List)
154 dbd6700b Iustin Pop
checkData nl il =
155 446d8827 Iustin Pop
    Container.mapAccum
156 446d8827 Iustin Pop
        (\ msgs node ->
157 dbd6700b Iustin Pop
             let nname = Node.name node
158 9f6dcdea Iustin Pop
                 nilst = map (flip Container.find il) (Node.plist node)
159 446d8827 Iustin Pop
                 dilst = filter (not . Instance.running) nilst
160 446d8827 Iustin Pop
                 adj_mem = sum . map Instance.mem $ dilst
161 9f6dcdea Iustin Pop
                 delta_mem = truncate (Node.t_mem node)
162 9f6dcdea Iustin Pop
                             - Node.n_mem node
163 9f6dcdea Iustin Pop
                             - Node.f_mem node
164 9f6dcdea Iustin Pop
                             - nodeImem node il
165 446d8827 Iustin Pop
                             + adj_mem
166 9f6dcdea Iustin Pop
                 delta_dsk = truncate (Node.t_dsk node)
167 9f6dcdea Iustin Pop
                             - Node.f_dsk node
168 9f6dcdea Iustin Pop
                             - nodeIdsk node il
169 446d8827 Iustin Pop
                 newn = Node.setFmem (Node.setXmem node delta_mem)
170 446d8827 Iustin Pop
                        (Node.f_mem node - adj_mem)
171 9f6dcdea Iustin Pop
                 umsg1 = [printf "node %s is missing %d MB ram \
172 9f6dcdea Iustin Pop
                                 \and %d GB disk"
173 9f6dcdea Iustin Pop
                                 nname delta_mem (delta_dsk `div` 1024) |
174 9f6dcdea Iustin Pop
                                 delta_mem > 512 || delta_dsk > 1024]::[String]
175 446d8827 Iustin Pop
             in (msgs ++ umsg1, newn)
176 446d8827 Iustin Pop
        ) [] nl
177 446d8827 Iustin Pop
178 446d8827 Iustin Pop
-- | Compute the amount of memory used by primary instances on a node.
179 262a08a2 Iustin Pop
nodeImem :: Node.Node -> Instance.List -> Int
180 446d8827 Iustin Pop
nodeImem node il =
181 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
182 9f6dcdea Iustin Pop
    in sum . map (Instance.mem . rfind)
183 9f6dcdea Iustin Pop
           $ Node.plist node
184 446d8827 Iustin Pop
185 446d8827 Iustin Pop
-- | Compute the amount of disk used by instances on a node (either primary
186 446d8827 Iustin Pop
-- or secondary).
187 262a08a2 Iustin Pop
nodeIdsk :: Node.Node -> Instance.List -> Int
188 446d8827 Iustin Pop
nodeIdsk node il =
189 9f6dcdea Iustin Pop
    let rfind = flip Container.find il
190 9f6dcdea Iustin Pop
    in sum . map (Instance.dsk . rfind)
191 9f6dcdea Iustin Pop
           $ Node.plist node ++ Node.slist node