Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ d6a7518a

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