Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ 9491766c

History | View | Annotate | Download (12.5 kB)

1 eaa64cd8 Iustin Pop
{-| Implementation of the Ganeti configuration database.
2 eaa64cd8 Iustin Pop
3 eaa64cd8 Iustin Pop
-}
4 eaa64cd8 Iustin Pop
5 eaa64cd8 Iustin Pop
{-
6 eaa64cd8 Iustin Pop
7 eaa64cd8 Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
8 eaa64cd8 Iustin Pop
9 eaa64cd8 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 eaa64cd8 Iustin Pop
it under the terms of the GNU General Public License as published by
11 eaa64cd8 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 eaa64cd8 Iustin Pop
(at your option) any later version.
13 eaa64cd8 Iustin Pop
14 eaa64cd8 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 eaa64cd8 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 eaa64cd8 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 eaa64cd8 Iustin Pop
General Public License for more details.
18 eaa64cd8 Iustin Pop
19 eaa64cd8 Iustin Pop
You should have received a copy of the GNU General Public License
20 eaa64cd8 Iustin Pop
along with this program; if not, write to the Free Software
21 eaa64cd8 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 eaa64cd8 Iustin Pop
02110-1301, USA.
23 eaa64cd8 Iustin Pop
24 eaa64cd8 Iustin Pop
-}
25 eaa64cd8 Iustin Pop
26 eaa64cd8 Iustin Pop
module Ganeti.Config
27 eaa64cd8 Iustin Pop
    ( LinkIpMap
28 da45c352 Iustin Pop
    , NdParamObject(..)
29 eaa64cd8 Iustin Pop
    , loadConfig
30 eaa64cd8 Iustin Pop
    , getNodeInstances
31 da45c352 Iustin Pop
    , getNodeRole
32 da45c352 Iustin Pop
    , getNodeNdParams
33 eaa64cd8 Iustin Pop
    , getDefaultNicLink
34 0ec87781 Iustin Pop
    , getDefaultHypervisor
35 eaa64cd8 Iustin Pop
    , getInstancesIpByLink
36 eaa64cd8 Iustin Pop
    , getNode
37 eaa64cd8 Iustin Pop
    , getInstance
38 4cd428db Iustin Pop
    , getGroup
39 da45c352 Iustin Pop
    , getGroupNdParams
40 e5cb098c Agata Murawska
    , getGroupIpolicy
41 90d033ef Iustin Pop
    , getGroupDiskParams
42 e5cb098c Agata Murawska
    , getGroupNodes
43 e5cb098c Agata Murawska
    , getGroupInstances
44 da45c352 Iustin Pop
    , getGroupOfNode
45 eaa64cd8 Iustin Pop
    , getInstPrimaryNode
46 d81ec8b7 Iustin Pop
    , getInstMinorsForNode
47 9491766c Hrvoje Ribicic
    , getInstAllNodes
48 05092772 Helga Velroyen
    , getNetwork
49 eaa64cd8 Iustin Pop
    , buildLinkIpInstnameMap
50 7b2ead5a Iustin Pop
    , instNodes
51 eaa64cd8 Iustin Pop
    ) where
52 eaa64cd8 Iustin Pop
53 2cdaf225 Iustin Pop
import Control.Monad (liftM)
54 9491766c Hrvoje Ribicic
import Data.List (foldl', nub)
55 eaa64cd8 Iustin Pop
import qualified Data.Map as M
56 7b2ead5a Iustin Pop
import qualified Data.Set as S
57 eaa64cd8 Iustin Pop
import qualified Text.JSON as J
58 eaa64cd8 Iustin Pop
59 eaa64cd8 Iustin Pop
import Ganeti.BasicTypes
60 eaa64cd8 Iustin Pop
import qualified Ganeti.Constants as C
61 5183e8be Iustin Pop
import Ganeti.Errors
62 5183e8be Iustin Pop
import Ganeti.JSON
63 eaa64cd8 Iustin Pop
import Ganeti.Objects
64 22381768 Iustin Pop
import Ganeti.Types
65 eaa64cd8 Iustin Pop
66 eaa64cd8 Iustin Pop
-- | Type alias for the link and ip map.
67 eaa64cd8 Iustin Pop
type LinkIpMap = M.Map String (M.Map String String)
68 eaa64cd8 Iustin Pop
69 da45c352 Iustin Pop
-- | Type class denoting objects which have node parameters.
70 da45c352 Iustin Pop
class NdParamObject a where
71 da45c352 Iustin Pop
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
72 da45c352 Iustin Pop
73 eaa64cd8 Iustin Pop
-- | Reads the config file.
74 eaa64cd8 Iustin Pop
readConfig :: FilePath -> IO String
75 eaa64cd8 Iustin Pop
readConfig = readFile
76 eaa64cd8 Iustin Pop
77 eaa64cd8 Iustin Pop
-- | Parses the configuration file.
78 eaa64cd8 Iustin Pop
parseConfig :: String -> Result ConfigData
79 eaa64cd8 Iustin Pop
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
80 eaa64cd8 Iustin Pop
81 eaa64cd8 Iustin Pop
-- | Wrapper over 'readConfig' and 'parseConfig'.
82 eaa64cd8 Iustin Pop
loadConfig :: FilePath -> IO (Result ConfigData)
83 eaa64cd8 Iustin Pop
loadConfig = fmap parseConfig . readConfig
84 eaa64cd8 Iustin Pop
85 eaa64cd8 Iustin Pop
-- * Query functions
86 eaa64cd8 Iustin Pop
87 7b2ead5a Iustin Pop
-- | Computes the nodes covered by a disk.
88 7b2ead5a Iustin Pop
computeDiskNodes :: Disk -> S.Set String
89 7b2ead5a Iustin Pop
computeDiskNodes dsk =
90 7b2ead5a Iustin Pop
  case diskLogicalId dsk of
91 7b2ead5a Iustin Pop
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
92 7b2ead5a Iustin Pop
    _ -> S.empty
93 7b2ead5a Iustin Pop
94 7b2ead5a Iustin Pop
-- | Computes all disk-related nodes of an instance. For non-DRBD,
95 7b2ead5a Iustin Pop
-- this will be empty, for DRBD it will contain both the primary and
96 7b2ead5a Iustin Pop
-- the secondaries.
97 7b2ead5a Iustin Pop
instDiskNodes :: Instance -> S.Set String
98 7b2ead5a Iustin Pop
instDiskNodes = S.unions . map computeDiskNodes . instDisks
99 7b2ead5a Iustin Pop
100 7b2ead5a Iustin Pop
-- | Computes all nodes of an instance.
101 7b2ead5a Iustin Pop
instNodes :: Instance -> S.Set String
102 7b2ead5a Iustin Pop
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
103 7b2ead5a Iustin Pop
104 7b2ead5a Iustin Pop
-- | Computes the secondary nodes of an instance. Since this is valid
105 7b2ead5a Iustin Pop
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
106 7b2ead5a Iustin Pop
-- extra primary insert.
107 7b2ead5a Iustin Pop
instSecondaryNodes :: Instance -> S.Set String
108 7b2ead5a Iustin Pop
instSecondaryNodes inst =
109 7b2ead5a Iustin Pop
  instPrimaryNode inst `S.delete` instDiskNodes inst
110 7b2ead5a Iustin Pop
111 eaa64cd8 Iustin Pop
-- | Get instances of a given node.
112 1a4f3b38 Michele Tartara
-- The node is specified through its UUID.
113 eaa64cd8 Iustin Pop
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
114 eaa64cd8 Iustin Pop
getNodeInstances cfg nname =
115 84835174 Iustin Pop
    let all_inst = M.elems . fromContainer . configInstances $ cfg
116 eaa64cd8 Iustin Pop
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
117 7b2ead5a Iustin Pop
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
118 eaa64cd8 Iustin Pop
    in (pri_inst, sec_inst)
119 eaa64cd8 Iustin Pop
120 da45c352 Iustin Pop
-- | Computes the role of a node.
121 da45c352 Iustin Pop
getNodeRole :: ConfigData -> Node -> NodeRole
122 da45c352 Iustin Pop
getNodeRole cfg node
123 5b11f8db Iustin Pop
  | nodeName node == clusterMasterNode (configCluster cfg) = NRMaster
124 da45c352 Iustin Pop
  | nodeMasterCandidate node = NRCandidate
125 da45c352 Iustin Pop
  | nodeDrained node = NRDrained
126 da45c352 Iustin Pop
  | nodeOffline node = NROffline
127 da45c352 Iustin Pop
  | otherwise = NRRegular
128 da45c352 Iustin Pop
129 eaa64cd8 Iustin Pop
-- | Returns the default cluster link.
130 eaa64cd8 Iustin Pop
getDefaultNicLink :: ConfigData -> String
131 eaa64cd8 Iustin Pop
getDefaultNicLink =
132 84835174 Iustin Pop
  nicpLink . (M.! C.ppDefault) . fromContainer .
133 84835174 Iustin Pop
  clusterNicparams . configCluster
134 eaa64cd8 Iustin Pop
135 0ec87781 Iustin Pop
-- | Returns the default cluster hypervisor.
136 0ec87781 Iustin Pop
getDefaultHypervisor :: ConfigData -> Hypervisor
137 0ec87781 Iustin Pop
getDefaultHypervisor cfg =
138 0ec87781 Iustin Pop
  case clusterEnabledHypervisors $ configCluster cfg of
139 0ec87781 Iustin Pop
    -- FIXME: this case shouldn't happen (configuration broken), but
140 0ec87781 Iustin Pop
    -- for now we handle it here because we're not authoritative for
141 0ec87781 Iustin Pop
    -- the config
142 0ec87781 Iustin Pop
    []  -> XenPvm
143 0ec87781 Iustin Pop
    x:_ -> x
144 0ec87781 Iustin Pop
145 eaa64cd8 Iustin Pop
-- | Returns instances of a given link.
146 eaa64cd8 Iustin Pop
getInstancesIpByLink :: LinkIpMap -> String -> [String]
147 eaa64cd8 Iustin Pop
getInstancesIpByLink linkipmap link =
148 eaa64cd8 Iustin Pop
  M.keys $ M.findWithDefault M.empty link linkipmap
149 eaa64cd8 Iustin Pop
150 0fc8e521 Iustin Pop
-- | Generic lookup function that converts from a possible abbreviated
151 0fc8e521 Iustin Pop
-- name to a full name.
152 5183e8be Iustin Pop
getItem :: String -> String -> M.Map String a -> ErrorResult a
153 0fc8e521 Iustin Pop
getItem kind name allitems = do
154 0fc8e521 Iustin Pop
  let lresult = lookupName (M.keys allitems) name
155 5183e8be Iustin Pop
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
156 5183e8be Iustin Pop
                        ECodeNoEnt
157 0fc8e521 Iustin Pop
  fullname <- case lrMatchPriority lresult of
158 0fc8e521 Iustin Pop
                PartialMatch -> Ok $ lrContent lresult
159 0fc8e521 Iustin Pop
                ExactMatch -> Ok $ lrContent lresult
160 0fc8e521 Iustin Pop
                MultipleMatch -> err "has multiple matches"
161 0fc8e521 Iustin Pop
                FailMatch -> err "not found"
162 0fc8e521 Iustin Pop
  maybe (err "not found after successfull match?!") Ok $
163 0fc8e521 Iustin Pop
        M.lookup fullname allitems
164 0fc8e521 Iustin Pop
165 1c3231aa Thomas Thrainer
-- | Looks up a node by name or uuid.
166 5183e8be Iustin Pop
getNode :: ConfigData -> String -> ErrorResult Node
167 1c3231aa Thomas Thrainer
getNode cfg name =
168 1c3231aa Thomas Thrainer
  let nodes = fromContainer (configNodes cfg)
169 1c3231aa Thomas Thrainer
  in case getItem "Node" name nodes of
170 1c3231aa Thomas Thrainer
       -- if not found by uuid, we need to look it up by name
171 1c3231aa Thomas Thrainer
       Ok node -> Ok node
172 1c3231aa Thomas Thrainer
       Bad _ -> let by_name = M.mapKeys
173 1c3231aa Thomas Thrainer
                              (nodeName . (M.!) nodes) nodes
174 1c3231aa Thomas Thrainer
                in getItem "Node" name by_name
175 eaa64cd8 Iustin Pop
176 da4a52a3 Thomas Thrainer
-- | Looks up an instance by name or uuid.
177 5183e8be Iustin Pop
getInstance :: ConfigData -> String -> ErrorResult Instance
178 84835174 Iustin Pop
getInstance cfg name =
179 da4a52a3 Thomas Thrainer
  let instances = fromContainer (configInstances cfg)
180 da4a52a3 Thomas Thrainer
  in case getItem "Instance" name instances of
181 da4a52a3 Thomas Thrainer
       -- if not found by uuid, we need to look it up by name
182 da4a52a3 Thomas Thrainer
       Ok inst -> Ok inst
183 da4a52a3 Thomas Thrainer
       Bad _ -> let by_name = M.mapKeys
184 da4a52a3 Thomas Thrainer
                              (instName . (M.!) instances) instances
185 da4a52a3 Thomas Thrainer
                in getItem "Instance" name by_name
186 eaa64cd8 Iustin Pop
187 da4a52a3 Thomas Thrainer
-- | Looks up a node group by name or uuid.
188 5183e8be Iustin Pop
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
189 4cd428db Iustin Pop
getGroup cfg name =
190 4cd428db Iustin Pop
  let groups = fromContainer (configNodegroups cfg)
191 4cd428db Iustin Pop
  in case getItem "NodeGroup" name groups of
192 4cd428db Iustin Pop
       -- if not found by uuid, we need to look it up by name, slow
193 4cd428db Iustin Pop
       Ok grp -> Ok grp
194 4cd428db Iustin Pop
       Bad _ -> let by_name = M.mapKeys
195 5b11f8db Iustin Pop
                              (groupName . (M.!) groups) groups
196 4cd428db Iustin Pop
                in getItem "NodeGroup" name by_name
197 4cd428db Iustin Pop
198 da45c352 Iustin Pop
-- | Computes a node group's node params.
199 da45c352 Iustin Pop
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
200 da45c352 Iustin Pop
getGroupNdParams cfg ng =
201 da45c352 Iustin Pop
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
202 da45c352 Iustin Pop
203 e5cb098c Agata Murawska
-- | Computes a node group's ipolicy.
204 e5cb098c Agata Murawska
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
205 e5cb098c Agata Murawska
getGroupIpolicy cfg ng =
206 e5cb098c Agata Murawska
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
207 e5cb098c Agata Murawska
208 90d033ef Iustin Pop
-- | Computes a group\'s (merged) disk params.
209 90d033ef Iustin Pop
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
210 90d033ef Iustin Pop
getGroupDiskParams cfg ng =
211 edc1acde Iustin Pop
  GenericContainer $
212 90d033ef Iustin Pop
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
213 90d033ef Iustin Pop
           (fromContainer $ groupDiskparams ng) []
214 90d033ef Iustin Pop
215 e5cb098c Agata Murawska
-- | Get nodes of a given node group.
216 e5cb098c Agata Murawska
getGroupNodes :: ConfigData -> String -> [Node]
217 e5cb098c Agata Murawska
getGroupNodes cfg gname =
218 e5cb098c Agata Murawska
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
219 e5cb098c Agata Murawska
  filter ((==gname) . nodeGroup) all_nodes
220 e5cb098c Agata Murawska
221 e5cb098c Agata Murawska
-- | Get (primary, secondary) instances of a given node group.
222 e5cb098c Agata Murawska
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
223 e5cb098c Agata Murawska
getGroupInstances cfg gname =
224 da4a52a3 Thomas Thrainer
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
225 e5cb098c Agata Murawska
      ginsts = map (getNodeInstances cfg) gnodes in
226 e5cb098c Agata Murawska
  (concatMap fst ginsts, concatMap snd ginsts)
227 e5cb098c Agata Murawska
228 05092772 Helga Velroyen
-- | Looks up a network. If looking up by uuid fails, we look up
229 05092772 Helga Velroyen
-- by name.
230 05092772 Helga Velroyen
getNetwork :: ConfigData -> String -> ErrorResult Network
231 05092772 Helga Velroyen
getNetwork cfg name =
232 05092772 Helga Velroyen
  let networks = fromContainer (configNetworks cfg)
233 05092772 Helga Velroyen
  in case getItem "Network" name networks of
234 05092772 Helga Velroyen
       Ok net -> Ok net
235 05092772 Helga Velroyen
       Bad _ -> let by_name = M.mapKeys
236 05092772 Helga Velroyen
                              (fromNonEmpty . networkName . (M.!) networks)
237 05092772 Helga Velroyen
                              networks
238 05092772 Helga Velroyen
                in getItem "Network" name by_name
239 05092772 Helga Velroyen
240 eaa64cd8 Iustin Pop
-- | Looks up an instance's primary node.
241 5183e8be Iustin Pop
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
242 eaa64cd8 Iustin Pop
getInstPrimaryNode cfg name =
243 2cdaf225 Iustin Pop
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
244 eaa64cd8 Iustin Pop
245 9491766c Hrvoje Ribicic
-- | Retrieves all nodes hosting a DRBD disk
246 9491766c Hrvoje Ribicic
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
247 9491766c Hrvoje Ribicic
getDrbdDiskNodes cfg disk =
248 9491766c Hrvoje Ribicic
  let retrieved = case diskLogicalId disk of
249 9491766c Hrvoje Ribicic
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
250 9491766c Hrvoje Ribicic
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
251 9491766c Hrvoje Ribicic
                    _                            -> []
252 9491766c Hrvoje Ribicic
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
253 9491766c Hrvoje Ribicic
254 9491766c Hrvoje Ribicic
-- | Retrieves all the nodes of the instance.
255 9491766c Hrvoje Ribicic
--
256 9491766c Hrvoje Ribicic
-- As instances not using DRBD can be sent as a parameter as well,
257 9491766c Hrvoje Ribicic
-- the primary node has to be appended to the results.
258 9491766c Hrvoje Ribicic
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
259 9491766c Hrvoje Ribicic
getInstAllNodes cfg name = do
260 9491766c Hrvoje Ribicic
  inst <- getInstance cfg name
261 9491766c Hrvoje Ribicic
  let diskNodes = concatMap (getDrbdDiskNodes cfg) $ instDisks inst
262 9491766c Hrvoje Ribicic
  pNode <- getInstPrimaryNode cfg name
263 9491766c Hrvoje Ribicic
  return . nub $ pNode:diskNodes
264 9491766c Hrvoje Ribicic
265 d81ec8b7 Iustin Pop
-- | Filters DRBD minors for a given node.
266 d81ec8b7 Iustin Pop
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
267 d81ec8b7 Iustin Pop
getDrbdMinorsForNode node disk =
268 d81ec8b7 Iustin Pop
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
269 d81ec8b7 Iustin Pop
      this_minors =
270 d81ec8b7 Iustin Pop
        case diskLogicalId disk of
271 d81ec8b7 Iustin Pop
          LIDDrbd8 nodeA nodeB _ minorA minorB _
272 d81ec8b7 Iustin Pop
            | nodeA == node -> [(minorA, nodeB)]
273 d81ec8b7 Iustin Pop
            | nodeB == node -> [(minorB, nodeA)]
274 d81ec8b7 Iustin Pop
          _ -> []
275 d81ec8b7 Iustin Pop
  in this_minors ++ child_minors
276 d81ec8b7 Iustin Pop
277 d81ec8b7 Iustin Pop
-- | String for primary role.
278 d81ec8b7 Iustin Pop
rolePrimary :: String
279 d81ec8b7 Iustin Pop
rolePrimary = "primary"
280 d81ec8b7 Iustin Pop
281 d81ec8b7 Iustin Pop
-- | String for secondary role.
282 d81ec8b7 Iustin Pop
roleSecondary :: String
283 d81ec8b7 Iustin Pop
roleSecondary = "secondary"
284 d81ec8b7 Iustin Pop
285 d81ec8b7 Iustin Pop
-- | Gets the list of DRBD minors for an instance that are related to
286 d81ec8b7 Iustin Pop
-- a given node.
287 d81ec8b7 Iustin Pop
getInstMinorsForNode :: String -> Instance
288 d81ec8b7 Iustin Pop
                     -> [(String, Int, String, String, String, String)]
289 d81ec8b7 Iustin Pop
getInstMinorsForNode node inst =
290 d81ec8b7 Iustin Pop
  let role = if node == instPrimaryNode inst
291 d81ec8b7 Iustin Pop
               then rolePrimary
292 d81ec8b7 Iustin Pop
               else roleSecondary
293 d81ec8b7 Iustin Pop
      iname = instName inst
294 d81ec8b7 Iustin Pop
  -- FIXME: the disk/ build there is hack-ish; unify this in a
295 d81ec8b7 Iustin Pop
  -- separate place, or reuse the iv_name (but that is deprecated on
296 d81ec8b7 Iustin Pop
  -- the Python side)
297 d81ec8b7 Iustin Pop
  in concatMap (\(idx, dsk) ->
298 d81ec8b7 Iustin Pop
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
299 d81ec8b7 Iustin Pop
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
300 d81ec8b7 Iustin Pop
     zip [(0::Int)..] . instDisks $ inst
301 d81ec8b7 Iustin Pop
302 eaa64cd8 Iustin Pop
-- | Builds link -> ip -> instname map.
303 eaa64cd8 Iustin Pop
--
304 eaa64cd8 Iustin Pop
-- TODO: improve this by splitting it into multiple independent functions:
305 eaa64cd8 Iustin Pop
--
306 eaa64cd8 Iustin Pop
-- * abstract the \"fetch instance with filled params\" functionality
307 eaa64cd8 Iustin Pop
--
308 eaa64cd8 Iustin Pop
-- * abstsract the [instance] -> [(nic, instance_name)] part
309 eaa64cd8 Iustin Pop
--
310 eaa64cd8 Iustin Pop
-- * etc.
311 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
312 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap cfg =
313 eaa64cd8 Iustin Pop
  let cluster = configCluster cfg
314 84835174 Iustin Pop
      instances = M.elems . fromContainer . configInstances $ cfg
315 84835174 Iustin Pop
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
316 eaa64cd8 Iustin Pop
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
317 eaa64cd8 Iustin Pop
             instances
318 eaa64cd8 Iustin Pop
  in foldl' (\accum (iname, nic) ->
319 eaa64cd8 Iustin Pop
               let pparams = nicNicparams nic
320 b09cce64 Iustin Pop
                   fparams = fillNicParams defparams pparams
321 eaa64cd8 Iustin Pop
                   link = nicpLink fparams
322 eaa64cd8 Iustin Pop
               in case nicIp nic of
323 eaa64cd8 Iustin Pop
                    Nothing -> accum
324 5b11f8db Iustin Pop
                    Just ip -> let oldipmap = M.findWithDefault M.empty
325 eaa64cd8 Iustin Pop
                                              link accum
326 eaa64cd8 Iustin Pop
                                   newipmap = M.insert ip iname oldipmap
327 eaa64cd8 Iustin Pop
                               in M.insert link newipmap accum
328 eaa64cd8 Iustin Pop
            ) M.empty nics
329 da45c352 Iustin Pop
330 da45c352 Iustin Pop
331 da45c352 Iustin Pop
-- | Returns a node's group, with optional failure if we can't find it
332 da45c352 Iustin Pop
-- (configuration corrupt).
333 da45c352 Iustin Pop
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
334 da45c352 Iustin Pop
getGroupOfNode cfg node =
335 da45c352 Iustin Pop
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
336 da45c352 Iustin Pop
337 da45c352 Iustin Pop
-- | Returns a node's ndparams, filled.
338 da45c352 Iustin Pop
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
339 da45c352 Iustin Pop
getNodeNdParams cfg node = do
340 da45c352 Iustin Pop
  group <- getGroupOfNode cfg node
341 da45c352 Iustin Pop
  let gparams = getGroupNdParams cfg group
342 da45c352 Iustin Pop
  return $ fillNDParams gparams (nodeNdparams node)
343 da45c352 Iustin Pop
344 da45c352 Iustin Pop
instance NdParamObject Node where
345 da45c352 Iustin Pop
  getNdParamsOf = getNodeNdParams
346 da45c352 Iustin Pop
347 da45c352 Iustin Pop
instance NdParamObject NodeGroup where
348 da45c352 Iustin Pop
  getNdParamsOf cfg = Just . getGroupNdParams cfg
349 da45c352 Iustin Pop
350 da45c352 Iustin Pop
instance NdParamObject Cluster where
351 da45c352 Iustin Pop
  getNdParamsOf _ = Just . clusterNdparams