Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ a6a6a1b5

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