Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ b9202225

History | View | Annotate | Download (14.8 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 f5a67757 Klaus Aehlig
    , getMasterCandidates
37 eaa64cd8 Iustin Pop
    , getNode
38 eaa64cd8 Iustin Pop
    , getInstance
39 4cd428db Iustin Pop
    , getGroup
40 da45c352 Iustin Pop
    , getGroupNdParams
41 e5cb098c Agata Murawska
    , getGroupIpolicy
42 90d033ef Iustin Pop
    , getGroupDiskParams
43 e5cb098c Agata Murawska
    , getGroupNodes
44 e5cb098c Agata Murawska
    , getGroupInstances
45 da45c352 Iustin Pop
    , getGroupOfNode
46 eaa64cd8 Iustin Pop
    , getInstPrimaryNode
47 d81ec8b7 Iustin Pop
    , getInstMinorsForNode
48 9491766c Hrvoje Ribicic
    , getInstAllNodes
49 4e6f1cde Hrvoje Ribicic
    , getFilledInstHvParams
50 4e6f1cde Hrvoje Ribicic
    , getFilledInstBeParams
51 4e6f1cde Hrvoje Ribicic
    , getFilledInstOsParams
52 05092772 Helga Velroyen
    , getNetwork
53 eaa64cd8 Iustin Pop
    , buildLinkIpInstnameMap
54 7b2ead5a Iustin Pop
    , instNodes
55 eaa64cd8 Iustin Pop
    ) where
56 eaa64cd8 Iustin Pop
57 2cdaf225 Iustin Pop
import Control.Monad (liftM)
58 9491766c Hrvoje Ribicic
import Data.List (foldl', nub)
59 eaa64cd8 Iustin Pop
import qualified Data.Map as M
60 7b2ead5a Iustin Pop
import qualified Data.Set as S
61 eaa64cd8 Iustin Pop
import qualified Text.JSON as J
62 eaa64cd8 Iustin Pop
63 eaa64cd8 Iustin Pop
import Ganeti.BasicTypes
64 eaa64cd8 Iustin Pop
import qualified Ganeti.Constants as C
65 5183e8be Iustin Pop
import Ganeti.Errors
66 5183e8be Iustin Pop
import Ganeti.JSON
67 eaa64cd8 Iustin Pop
import Ganeti.Objects
68 22381768 Iustin Pop
import Ganeti.Types
69 eaa64cd8 Iustin Pop
70 eaa64cd8 Iustin Pop
-- | Type alias for the link and ip map.
71 eaa64cd8 Iustin Pop
type LinkIpMap = M.Map String (M.Map String String)
72 eaa64cd8 Iustin Pop
73 da45c352 Iustin Pop
-- | Type class denoting objects which have node parameters.
74 da45c352 Iustin Pop
class NdParamObject a where
75 da45c352 Iustin Pop
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
76 da45c352 Iustin Pop
77 eaa64cd8 Iustin Pop
-- | Reads the config file.
78 eaa64cd8 Iustin Pop
readConfig :: FilePath -> IO String
79 eaa64cd8 Iustin Pop
readConfig = readFile
80 eaa64cd8 Iustin Pop
81 eaa64cd8 Iustin Pop
-- | Parses the configuration file.
82 eaa64cd8 Iustin Pop
parseConfig :: String -> Result ConfigData
83 eaa64cd8 Iustin Pop
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
84 eaa64cd8 Iustin Pop
85 eaa64cd8 Iustin Pop
-- | Wrapper over 'readConfig' and 'parseConfig'.
86 eaa64cd8 Iustin Pop
loadConfig :: FilePath -> IO (Result ConfigData)
87 eaa64cd8 Iustin Pop
loadConfig = fmap parseConfig . readConfig
88 eaa64cd8 Iustin Pop
89 eaa64cd8 Iustin Pop
-- * Query functions
90 eaa64cd8 Iustin Pop
91 7b2ead5a Iustin Pop
-- | Computes the nodes covered by a disk.
92 7b2ead5a Iustin Pop
computeDiskNodes :: Disk -> S.Set String
93 7b2ead5a Iustin Pop
computeDiskNodes dsk =
94 7b2ead5a Iustin Pop
  case diskLogicalId dsk of
95 7b2ead5a Iustin Pop
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
96 7b2ead5a Iustin Pop
    _ -> S.empty
97 7b2ead5a Iustin Pop
98 7b2ead5a Iustin Pop
-- | Computes all disk-related nodes of an instance. For non-DRBD,
99 7b2ead5a Iustin Pop
-- this will be empty, for DRBD it will contain both the primary and
100 7b2ead5a Iustin Pop
-- the secondaries.
101 7b2ead5a Iustin Pop
instDiskNodes :: Instance -> S.Set String
102 7b2ead5a Iustin Pop
instDiskNodes = S.unions . map computeDiskNodes . instDisks
103 7b2ead5a Iustin Pop
104 7b2ead5a Iustin Pop
-- | Computes all nodes of an instance.
105 7b2ead5a Iustin Pop
instNodes :: Instance -> S.Set String
106 7b2ead5a Iustin Pop
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
107 7b2ead5a Iustin Pop
108 7b2ead5a Iustin Pop
-- | Computes the secondary nodes of an instance. Since this is valid
109 7b2ead5a Iustin Pop
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
110 7b2ead5a Iustin Pop
-- extra primary insert.
111 7b2ead5a Iustin Pop
instSecondaryNodes :: Instance -> S.Set String
112 7b2ead5a Iustin Pop
instSecondaryNodes inst =
113 7b2ead5a Iustin Pop
  instPrimaryNode inst `S.delete` instDiskNodes inst
114 7b2ead5a Iustin Pop
115 eaa64cd8 Iustin Pop
-- | Get instances of a given node.
116 1a4f3b38 Michele Tartara
-- The node is specified through its UUID.
117 eaa64cd8 Iustin Pop
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
118 eaa64cd8 Iustin Pop
getNodeInstances cfg nname =
119 84835174 Iustin Pop
    let all_inst = M.elems . fromContainer . configInstances $ cfg
120 eaa64cd8 Iustin Pop
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
121 7b2ead5a Iustin Pop
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
122 eaa64cd8 Iustin Pop
    in (pri_inst, sec_inst)
123 eaa64cd8 Iustin Pop
124 da45c352 Iustin Pop
-- | Computes the role of a node.
125 da45c352 Iustin Pop
getNodeRole :: ConfigData -> Node -> NodeRole
126 da45c352 Iustin Pop
getNodeRole cfg node
127 dfcebee3 Klaus Aehlig
  | nodeUuid node == clusterMasterNode (configCluster cfg) = NRMaster
128 da45c352 Iustin Pop
  | nodeMasterCandidate node = NRCandidate
129 da45c352 Iustin Pop
  | nodeDrained node = NRDrained
130 da45c352 Iustin Pop
  | nodeOffline node = NROffline
131 da45c352 Iustin Pop
  | otherwise = NRRegular
132 da45c352 Iustin Pop
133 f5a67757 Klaus Aehlig
-- | Get the list of master candidates.
134 f5a67757 Klaus Aehlig
getMasterCandidates :: ConfigData -> [Node]
135 f5a67757 Klaus Aehlig
getMasterCandidates cfg = 
136 f5a67757 Klaus Aehlig
  filter ((==) NRCandidate . getNodeRole cfg)
137 f5a67757 Klaus Aehlig
    (map snd . M.toList . fromContainer . configNodes $ cfg)
138 f5a67757 Klaus Aehlig
139 eaa64cd8 Iustin Pop
-- | Returns the default cluster link.
140 eaa64cd8 Iustin Pop
getDefaultNicLink :: ConfigData -> String
141 eaa64cd8 Iustin Pop
getDefaultNicLink =
142 84835174 Iustin Pop
  nicpLink . (M.! C.ppDefault) . fromContainer .
143 84835174 Iustin Pop
  clusterNicparams . configCluster
144 eaa64cd8 Iustin Pop
145 0ec87781 Iustin Pop
-- | Returns the default cluster hypervisor.
146 0ec87781 Iustin Pop
getDefaultHypervisor :: ConfigData -> Hypervisor
147 0ec87781 Iustin Pop
getDefaultHypervisor cfg =
148 0ec87781 Iustin Pop
  case clusterEnabledHypervisors $ configCluster cfg of
149 0ec87781 Iustin Pop
    -- FIXME: this case shouldn't happen (configuration broken), but
150 0ec87781 Iustin Pop
    -- for now we handle it here because we're not authoritative for
151 0ec87781 Iustin Pop
    -- the config
152 0ec87781 Iustin Pop
    []  -> XenPvm
153 0ec87781 Iustin Pop
    x:_ -> x
154 0ec87781 Iustin Pop
155 eaa64cd8 Iustin Pop
-- | Returns instances of a given link.
156 eaa64cd8 Iustin Pop
getInstancesIpByLink :: LinkIpMap -> String -> [String]
157 eaa64cd8 Iustin Pop
getInstancesIpByLink linkipmap link =
158 eaa64cd8 Iustin Pop
  M.keys $ M.findWithDefault M.empty link linkipmap
159 eaa64cd8 Iustin Pop
160 0fc8e521 Iustin Pop
-- | Generic lookup function that converts from a possible abbreviated
161 0fc8e521 Iustin Pop
-- name to a full name.
162 5183e8be Iustin Pop
getItem :: String -> String -> M.Map String a -> ErrorResult a
163 0fc8e521 Iustin Pop
getItem kind name allitems = do
164 0fc8e521 Iustin Pop
  let lresult = lookupName (M.keys allitems) name
165 5183e8be Iustin Pop
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
166 5183e8be Iustin Pop
                        ECodeNoEnt
167 0fc8e521 Iustin Pop
  fullname <- case lrMatchPriority lresult of
168 0fc8e521 Iustin Pop
                PartialMatch -> Ok $ lrContent lresult
169 0fc8e521 Iustin Pop
                ExactMatch -> Ok $ lrContent lresult
170 0fc8e521 Iustin Pop
                MultipleMatch -> err "has multiple matches"
171 0fc8e521 Iustin Pop
                FailMatch -> err "not found"
172 0fc8e521 Iustin Pop
  maybe (err "not found after successfull match?!") Ok $
173 0fc8e521 Iustin Pop
        M.lookup fullname allitems
174 0fc8e521 Iustin Pop
175 1c3231aa Thomas Thrainer
-- | Looks up a node by name or uuid.
176 5183e8be Iustin Pop
getNode :: ConfigData -> String -> ErrorResult Node
177 1c3231aa Thomas Thrainer
getNode cfg name =
178 1c3231aa Thomas Thrainer
  let nodes = fromContainer (configNodes cfg)
179 1c3231aa Thomas Thrainer
  in case getItem "Node" name nodes of
180 1c3231aa Thomas Thrainer
       -- if not found by uuid, we need to look it up by name
181 1c3231aa Thomas Thrainer
       Ok node -> Ok node
182 1c3231aa Thomas Thrainer
       Bad _ -> let by_name = M.mapKeys
183 1c3231aa Thomas Thrainer
                              (nodeName . (M.!) nodes) nodes
184 1c3231aa Thomas Thrainer
                in getItem "Node" name by_name
185 eaa64cd8 Iustin Pop
186 da4a52a3 Thomas Thrainer
-- | Looks up an instance by name or uuid.
187 5183e8be Iustin Pop
getInstance :: ConfigData -> String -> ErrorResult Instance
188 84835174 Iustin Pop
getInstance cfg name =
189 da4a52a3 Thomas Thrainer
  let instances = fromContainer (configInstances cfg)
190 da4a52a3 Thomas Thrainer
  in case getItem "Instance" name instances of
191 da4a52a3 Thomas Thrainer
       -- if not found by uuid, we need to look it up by name
192 da4a52a3 Thomas Thrainer
       Ok inst -> Ok inst
193 da4a52a3 Thomas Thrainer
       Bad _ -> let by_name = M.mapKeys
194 da4a52a3 Thomas Thrainer
                              (instName . (M.!) instances) instances
195 da4a52a3 Thomas Thrainer
                in getItem "Instance" name by_name
196 eaa64cd8 Iustin Pop
197 da4a52a3 Thomas Thrainer
-- | Looks up a node group by name or uuid.
198 5183e8be Iustin Pop
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
199 4cd428db Iustin Pop
getGroup cfg name =
200 4cd428db Iustin Pop
  let groups = fromContainer (configNodegroups cfg)
201 4cd428db Iustin Pop
  in case getItem "NodeGroup" name groups of
202 4cd428db Iustin Pop
       -- if not found by uuid, we need to look it up by name, slow
203 4cd428db Iustin Pop
       Ok grp -> Ok grp
204 4cd428db Iustin Pop
       Bad _ -> let by_name = M.mapKeys
205 5b11f8db Iustin Pop
                              (groupName . (M.!) groups) groups
206 4cd428db Iustin Pop
                in getItem "NodeGroup" name by_name
207 4cd428db Iustin Pop
208 da45c352 Iustin Pop
-- | Computes a node group's node params.
209 da45c352 Iustin Pop
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
210 da45c352 Iustin Pop
getGroupNdParams cfg ng =
211 da45c352 Iustin Pop
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
212 da45c352 Iustin Pop
213 e5cb098c Agata Murawska
-- | Computes a node group's ipolicy.
214 e5cb098c Agata Murawska
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
215 e5cb098c Agata Murawska
getGroupIpolicy cfg ng =
216 e5cb098c Agata Murawska
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
217 e5cb098c Agata Murawska
218 90d033ef Iustin Pop
-- | Computes a group\'s (merged) disk params.
219 90d033ef Iustin Pop
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
220 90d033ef Iustin Pop
getGroupDiskParams cfg ng =
221 edc1acde Iustin Pop
  GenericContainer $
222 90d033ef Iustin Pop
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
223 90d033ef Iustin Pop
           (fromContainer $ groupDiskparams ng) []
224 90d033ef Iustin Pop
225 e5cb098c Agata Murawska
-- | Get nodes of a given node group.
226 e5cb098c Agata Murawska
getGroupNodes :: ConfigData -> String -> [Node]
227 e5cb098c Agata Murawska
getGroupNodes cfg gname =
228 e5cb098c Agata Murawska
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
229 e5cb098c Agata Murawska
  filter ((==gname) . nodeGroup) all_nodes
230 e5cb098c Agata Murawska
231 e5cb098c Agata Murawska
-- | Get (primary, secondary) instances of a given node group.
232 e5cb098c Agata Murawska
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
233 e5cb098c Agata Murawska
getGroupInstances cfg gname =
234 da4a52a3 Thomas Thrainer
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
235 e5cb098c Agata Murawska
      ginsts = map (getNodeInstances cfg) gnodes in
236 e5cb098c Agata Murawska
  (concatMap fst ginsts, concatMap snd ginsts)
237 e5cb098c Agata Murawska
238 05092772 Helga Velroyen
-- | Looks up a network. If looking up by uuid fails, we look up
239 05092772 Helga Velroyen
-- by name.
240 05092772 Helga Velroyen
getNetwork :: ConfigData -> String -> ErrorResult Network
241 05092772 Helga Velroyen
getNetwork cfg name =
242 05092772 Helga Velroyen
  let networks = fromContainer (configNetworks cfg)
243 05092772 Helga Velroyen
  in case getItem "Network" name networks of
244 05092772 Helga Velroyen
       Ok net -> Ok net
245 05092772 Helga Velroyen
       Bad _ -> let by_name = M.mapKeys
246 05092772 Helga Velroyen
                              (fromNonEmpty . networkName . (M.!) networks)
247 05092772 Helga Velroyen
                              networks
248 05092772 Helga Velroyen
                in getItem "Network" name by_name
249 05092772 Helga Velroyen
250 4e6f1cde Hrvoje Ribicic
-- | Retrieves the instance hypervisor params, missing values filled with
251 4e6f1cde Hrvoje Ribicic
-- cluster defaults.
252 b9666288 Hrvoje Ribicic
getFilledInstHvParams :: [String] -> ConfigData -> Instance -> HvParams
253 b9666288 Hrvoje Ribicic
getFilledInstHvParams globals cfg inst =
254 4e6f1cde Hrvoje Ribicic
  -- First get the defaults of the parent
255 4e6f1cde Hrvoje Ribicic
  let hvName = hypervisorToRaw . instHypervisor $ inst
256 4e6f1cde Hrvoje Ribicic
      hvParamMap = fromContainer . clusterHvparams $ configCluster cfg
257 4e6f1cde Hrvoje Ribicic
      parentHvParams = maybe M.empty fromContainer $ M.lookup hvName hvParamMap
258 4e6f1cde Hrvoje Ribicic
  -- Then the os defaults for the given hypervisor
259 4e6f1cde Hrvoje Ribicic
      osName = instOs inst
260 4e6f1cde Hrvoje Ribicic
      osParamMap = fromContainer . clusterOsHvp $ configCluster cfg
261 4e6f1cde Hrvoje Ribicic
      osHvParamMap = maybe M.empty fromContainer $ M.lookup osName osParamMap
262 4e6f1cde Hrvoje Ribicic
      osHvParams = maybe M.empty fromContainer $ M.lookup hvName osHvParamMap
263 4e6f1cde Hrvoje Ribicic
  -- Then the child
264 4e6f1cde Hrvoje Ribicic
      childHvParams = fromContainer . instHvparams $ inst
265 4e6f1cde Hrvoje Ribicic
  -- Helper function
266 b9666288 Hrvoje Ribicic
      fillFn con val = fillDict con val globals
267 4e6f1cde Hrvoje Ribicic
  in GenericContainer $ fillFn (fillFn parentHvParams osHvParams) childHvParams
268 4e6f1cde Hrvoje Ribicic
269 4e6f1cde Hrvoje Ribicic
-- | Retrieves the instance backend params, missing values filled with cluster
270 4e6f1cde Hrvoje Ribicic
-- defaults.
271 4e6f1cde Hrvoje Ribicic
getFilledInstBeParams :: ConfigData -> Instance -> ErrorResult FilledBeParams
272 4e6f1cde Hrvoje Ribicic
getFilledInstBeParams cfg inst = do
273 4e6f1cde Hrvoje Ribicic
  let beParamMap = fromContainer . clusterBeparams . configCluster $ cfg
274 4e6f1cde Hrvoje Ribicic
  parentParams <- getItem "FilledBeParams" C.ppDefault beParamMap
275 4e6f1cde Hrvoje Ribicic
  return $ fillBeParams parentParams (instBeparams inst)
276 4e6f1cde Hrvoje Ribicic
277 4e6f1cde Hrvoje Ribicic
-- | Retrieves the instance os params, missing values filled with cluster
278 4e6f1cde Hrvoje Ribicic
-- defaults.
279 4e6f1cde Hrvoje Ribicic
getFilledInstOsParams :: ConfigData -> Instance -> OsParams
280 4e6f1cde Hrvoje Ribicic
getFilledInstOsParams cfg inst =
281 4e6f1cde Hrvoje Ribicic
  let osLookupName = takeWhile (/= '+') (instOs inst)
282 4e6f1cde Hrvoje Ribicic
      osParamMap = fromContainer . clusterOsparams $ configCluster cfg
283 4e6f1cde Hrvoje Ribicic
      childOsParams = instOsparams inst
284 4e6f1cde Hrvoje Ribicic
  in case getItem "OsParams" osLookupName osParamMap of
285 4e6f1cde Hrvoje Ribicic
       Ok parentOsParams -> GenericContainer $
286 4e6f1cde Hrvoje Ribicic
                              fillDict (fromContainer parentOsParams)
287 4e6f1cde Hrvoje Ribicic
                                       (fromContainer childOsParams) []
288 4e6f1cde Hrvoje Ribicic
       Bad _             -> childOsParams
289 4e6f1cde Hrvoje Ribicic
290 eaa64cd8 Iustin Pop
-- | Looks up an instance's primary node.
291 5183e8be Iustin Pop
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
292 eaa64cd8 Iustin Pop
getInstPrimaryNode cfg name =
293 2cdaf225 Iustin Pop
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
294 eaa64cd8 Iustin Pop
295 9491766c Hrvoje Ribicic
-- | Retrieves all nodes hosting a DRBD disk
296 9491766c Hrvoje Ribicic
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
297 9491766c Hrvoje Ribicic
getDrbdDiskNodes cfg disk =
298 9491766c Hrvoje Ribicic
  let retrieved = case diskLogicalId disk of
299 9491766c Hrvoje Ribicic
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
300 9491766c Hrvoje Ribicic
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
301 9491766c Hrvoje Ribicic
                    _                            -> []
302 9491766c Hrvoje Ribicic
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
303 9491766c Hrvoje Ribicic
304 9491766c Hrvoje Ribicic
-- | Retrieves all the nodes of the instance.
305 9491766c Hrvoje Ribicic
--
306 9491766c Hrvoje Ribicic
-- As instances not using DRBD can be sent as a parameter as well,
307 9491766c Hrvoje Ribicic
-- the primary node has to be appended to the results.
308 9491766c Hrvoje Ribicic
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
309 9491766c Hrvoje Ribicic
getInstAllNodes cfg name = do
310 9491766c Hrvoje Ribicic
  inst <- getInstance cfg name
311 9491766c Hrvoje Ribicic
  let diskNodes = concatMap (getDrbdDiskNodes cfg) $ instDisks inst
312 9491766c Hrvoje Ribicic
  pNode <- getInstPrimaryNode cfg name
313 9491766c Hrvoje Ribicic
  return . nub $ pNode:diskNodes
314 9491766c Hrvoje Ribicic
315 d81ec8b7 Iustin Pop
-- | Filters DRBD minors for a given node.
316 d81ec8b7 Iustin Pop
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
317 d81ec8b7 Iustin Pop
getDrbdMinorsForNode node disk =
318 d81ec8b7 Iustin Pop
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
319 d81ec8b7 Iustin Pop
      this_minors =
320 d81ec8b7 Iustin Pop
        case diskLogicalId disk of
321 d81ec8b7 Iustin Pop
          LIDDrbd8 nodeA nodeB _ minorA minorB _
322 d81ec8b7 Iustin Pop
            | nodeA == node -> [(minorA, nodeB)]
323 d81ec8b7 Iustin Pop
            | nodeB == node -> [(minorB, nodeA)]
324 d81ec8b7 Iustin Pop
          _ -> []
325 d81ec8b7 Iustin Pop
  in this_minors ++ child_minors
326 d81ec8b7 Iustin Pop
327 d81ec8b7 Iustin Pop
-- | String for primary role.
328 d81ec8b7 Iustin Pop
rolePrimary :: String
329 d81ec8b7 Iustin Pop
rolePrimary = "primary"
330 d81ec8b7 Iustin Pop
331 d81ec8b7 Iustin Pop
-- | String for secondary role.
332 d81ec8b7 Iustin Pop
roleSecondary :: String
333 d81ec8b7 Iustin Pop
roleSecondary = "secondary"
334 d81ec8b7 Iustin Pop
335 d81ec8b7 Iustin Pop
-- | Gets the list of DRBD minors for an instance that are related to
336 d81ec8b7 Iustin Pop
-- a given node.
337 d81ec8b7 Iustin Pop
getInstMinorsForNode :: String -> Instance
338 d81ec8b7 Iustin Pop
                     -> [(String, Int, String, String, String, String)]
339 d81ec8b7 Iustin Pop
getInstMinorsForNode node inst =
340 d81ec8b7 Iustin Pop
  let role = if node == instPrimaryNode inst
341 d81ec8b7 Iustin Pop
               then rolePrimary
342 d81ec8b7 Iustin Pop
               else roleSecondary
343 d81ec8b7 Iustin Pop
      iname = instName inst
344 d81ec8b7 Iustin Pop
  -- FIXME: the disk/ build there is hack-ish; unify this in a
345 d81ec8b7 Iustin Pop
  -- separate place, or reuse the iv_name (but that is deprecated on
346 d81ec8b7 Iustin Pop
  -- the Python side)
347 d81ec8b7 Iustin Pop
  in concatMap (\(idx, dsk) ->
348 d81ec8b7 Iustin Pop
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
349 d81ec8b7 Iustin Pop
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
350 d81ec8b7 Iustin Pop
     zip [(0::Int)..] . instDisks $ inst
351 d81ec8b7 Iustin Pop
352 eaa64cd8 Iustin Pop
-- | Builds link -> ip -> instname map.
353 eaa64cd8 Iustin Pop
--
354 eaa64cd8 Iustin Pop
-- TODO: improve this by splitting it into multiple independent functions:
355 eaa64cd8 Iustin Pop
--
356 eaa64cd8 Iustin Pop
-- * abstract the \"fetch instance with filled params\" functionality
357 eaa64cd8 Iustin Pop
--
358 eaa64cd8 Iustin Pop
-- * abstsract the [instance] -> [(nic, instance_name)] part
359 eaa64cd8 Iustin Pop
--
360 eaa64cd8 Iustin Pop
-- * etc.
361 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
362 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap cfg =
363 eaa64cd8 Iustin Pop
  let cluster = configCluster cfg
364 84835174 Iustin Pop
      instances = M.elems . fromContainer . configInstances $ cfg
365 84835174 Iustin Pop
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
366 eaa64cd8 Iustin Pop
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
367 eaa64cd8 Iustin Pop
             instances
368 eaa64cd8 Iustin Pop
  in foldl' (\accum (iname, nic) ->
369 eaa64cd8 Iustin Pop
               let pparams = nicNicparams nic
370 b09cce64 Iustin Pop
                   fparams = fillNicParams defparams pparams
371 eaa64cd8 Iustin Pop
                   link = nicpLink fparams
372 eaa64cd8 Iustin Pop
               in case nicIp nic of
373 eaa64cd8 Iustin Pop
                    Nothing -> accum
374 5b11f8db Iustin Pop
                    Just ip -> let oldipmap = M.findWithDefault M.empty
375 eaa64cd8 Iustin Pop
                                              link accum
376 eaa64cd8 Iustin Pop
                                   newipmap = M.insert ip iname oldipmap
377 eaa64cd8 Iustin Pop
                               in M.insert link newipmap accum
378 eaa64cd8 Iustin Pop
            ) M.empty nics
379 da45c352 Iustin Pop
380 da45c352 Iustin Pop
381 da45c352 Iustin Pop
-- | Returns a node's group, with optional failure if we can't find it
382 da45c352 Iustin Pop
-- (configuration corrupt).
383 da45c352 Iustin Pop
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
384 da45c352 Iustin Pop
getGroupOfNode cfg node =
385 da45c352 Iustin Pop
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
386 da45c352 Iustin Pop
387 da45c352 Iustin Pop
-- | Returns a node's ndparams, filled.
388 da45c352 Iustin Pop
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
389 da45c352 Iustin Pop
getNodeNdParams cfg node = do
390 da45c352 Iustin Pop
  group <- getGroupOfNode cfg node
391 da45c352 Iustin Pop
  let gparams = getGroupNdParams cfg group
392 da45c352 Iustin Pop
  return $ fillNDParams gparams (nodeNdparams node)
393 da45c352 Iustin Pop
394 da45c352 Iustin Pop
instance NdParamObject Node where
395 da45c352 Iustin Pop
  getNdParamsOf = getNodeNdParams
396 da45c352 Iustin Pop
397 da45c352 Iustin Pop
instance NdParamObject NodeGroup where
398 da45c352 Iustin Pop
  getNdParamsOf cfg = Just . getGroupNdParams cfg
399 da45c352 Iustin Pop
400 da45c352 Iustin Pop
instance NdParamObject Cluster where
401 da45c352 Iustin Pop
  getNdParamsOf _ = Just . clusterNdparams