Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ 1c474f2b

History | View | Annotate | Download (16.2 kB)

1
{-| Implementation of the Ganeti configuration database.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2011, 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.Config
27
    ( LinkIpMap
28
    , NdParamObject(..)
29
    , loadConfig
30
    , saveConfig
31
    , getNodeInstances
32
    , getNodeRole
33
    , getNodeNdParams
34
    , getDefaultNicLink
35
    , getDefaultHypervisor
36
    , getInstancesIpByLink
37
    , getMasterCandidates
38
    , getOnlineNodes
39
    , getNode
40
    , getInstance
41
    , getDisk
42
    , getGroup
43
    , getGroupNdParams
44
    , getGroupIpolicy
45
    , getGroupDiskParams
46
    , getGroupNodes
47
    , getGroupInstances
48
    , getGroupOfNode
49
    , getInstPrimaryNode
50
    , getInstMinorsForNode
51
    , getInstAllNodes
52
    , getInstDisks
53
    , getInstDisksByName
54
    , getFilledInstHvParams
55
    , getFilledInstBeParams
56
    , getFilledInstOsParams
57
    , getNetwork
58
    , buildLinkIpInstnameMap
59
    , instNodes
60
    ) where
61

    
62
import Control.Monad (liftM)
63
import qualified Data.Foldable as F
64
import Data.List (foldl', nub)
65
import qualified Data.Map as M
66
import qualified Data.Set as S
67
import qualified Text.JSON as J
68
import System.IO
69

    
70
import Ganeti.BasicTypes
71
import qualified Ganeti.Constants as C
72
import Ganeti.Errors
73
import Ganeti.JSON
74
import Ganeti.Objects
75
import Ganeti.Types
76

    
77
-- | Type alias for the link and ip map.
78
type LinkIpMap = M.Map String (M.Map String String)
79

    
80
-- | Type class denoting objects which have node parameters.
81
class NdParamObject a where
82
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
83

    
84
-- | Reads the config file.
85
readConfig :: FilePath -> IO (Result String)
86
readConfig = runResultT . liftIO . readFile
87

    
88
-- | Parses the configuration file.
89
parseConfig :: String -> Result ConfigData
90
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
91

    
92
-- | Encodes the configuration file.
93
encodeConfig :: ConfigData -> String
94
encodeConfig = J.encodeStrict
95

    
96
-- | Wrapper over 'readConfig' and 'parseConfig'.
97
loadConfig :: FilePath -> IO (Result ConfigData)
98
loadConfig = fmap (>>= parseConfig) . readConfig
99

    
100
-- | Wrapper over 'hPutStr' and 'encodeConfig'.
101
saveConfig :: Handle -> ConfigData -> IO ()
102
saveConfig fh = hPutStr fh . encodeConfig
103

    
104
-- * Query functions
105

    
106
-- | Computes the nodes covered by a disk.
107
computeDiskNodes :: Disk -> S.Set String
108
computeDiskNodes dsk =
109
  case diskLogicalId dsk of
110
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
111
    _ -> S.empty
112

    
113
-- | Computes all disk-related nodes of an instance. For non-DRBD,
114
-- this will be empty, for DRBD it will contain both the primary and
115
-- the secondaries.
116
instDiskNodes :: ConfigData -> Instance -> S.Set String
117
instDiskNodes cfg inst =
118
  case getInstDisks cfg inst of
119
    Ok disks -> S.unions $ map computeDiskNodes disks
120
    Bad _ -> S.empty
121

    
122
-- | Computes all nodes of an instance.
123
instNodes :: ConfigData -> Instance -> S.Set String
124
instNodes cfg inst = instPrimaryNode inst `S.insert` instDiskNodes cfg inst
125

    
126
-- | Computes the secondary nodes of an instance. Since this is valid
127
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
128
-- extra primary insert.
129
instSecondaryNodes :: ConfigData -> Instance -> S.Set String
130
instSecondaryNodes cfg inst =
131
  instPrimaryNode inst `S.delete` instDiskNodes cfg inst
132

    
133
-- | Get instances of a given node.
134
-- The node is specified through its UUID.
135
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
136
getNodeInstances cfg nname =
137
    let all_inst = M.elems . fromContainer . configInstances $ cfg
138
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
139
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes cfg) all_inst
140
    in (pri_inst, sec_inst)
141

    
142
-- | Computes the role of a node.
143
getNodeRole :: ConfigData -> Node -> NodeRole
144
getNodeRole cfg node
145
  | nodeUuid node == clusterMasterNode (configCluster cfg) = NRMaster
146
  | nodeMasterCandidate node = NRCandidate
147
  | nodeDrained node = NRDrained
148
  | nodeOffline node = NROffline
149
  | otherwise = NRRegular
150

    
151
-- | Get the list of master candidates.
152
getMasterCandidates :: ConfigData -> [Node]
153
getMasterCandidates cfg = 
154
  filter ((==) NRCandidate . getNodeRole cfg) . F.toList . configNodes $ cfg
155

    
156
-- | Get the list of online nodes.
157
getOnlineNodes :: ConfigData -> [Node]
158
getOnlineNodes = filter (not . nodeOffline) . F.toList . configNodes
159

    
160
-- | Returns the default cluster link.
161
getDefaultNicLink :: ConfigData -> String
162
getDefaultNicLink =
163
  nicpLink . (M.! C.ppDefault) . fromContainer .
164
  clusterNicparams . configCluster
165

    
166
-- | Returns the default cluster hypervisor.
167
getDefaultHypervisor :: ConfigData -> Hypervisor
168
getDefaultHypervisor cfg =
169
  case clusterEnabledHypervisors $ configCluster cfg of
170
    -- FIXME: this case shouldn't happen (configuration broken), but
171
    -- for now we handle it here because we're not authoritative for
172
    -- the config
173
    []  -> XenPvm
174
    x:_ -> x
175

    
176
-- | Returns instances of a given link.
177
getInstancesIpByLink :: LinkIpMap -> String -> [String]
178
getInstancesIpByLink linkipmap link =
179
  M.keys $ M.findWithDefault M.empty link linkipmap
180

    
181
-- | Generic lookup function that converts from a possible abbreviated
182
-- name to a full name.
183
getItem :: String -> String -> M.Map String a -> ErrorResult a
184
getItem kind name allitems = do
185
  let lresult = lookupName (M.keys allitems) name
186
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
187
                        ECodeNoEnt
188
  fullname <- case lrMatchPriority lresult of
189
                PartialMatch -> Ok $ lrContent lresult
190
                ExactMatch -> Ok $ lrContent lresult
191
                MultipleMatch -> err "has multiple matches"
192
                FailMatch -> err "not found"
193
  maybe (err "not found after successfull match?!") Ok $
194
        M.lookup fullname allitems
195

    
196
-- | Looks up a node by name or uuid.
197
getNode :: ConfigData -> String -> ErrorResult Node
198
getNode cfg name =
199
  let nodes = fromContainer (configNodes cfg)
200
  in case getItem "Node" name nodes of
201
       -- if not found by uuid, we need to look it up by name
202
       Ok node -> Ok node
203
       Bad _ -> let by_name = M.mapKeys
204
                              (nodeName . (M.!) nodes) nodes
205
                in getItem "Node" name by_name
206

    
207
-- | Looks up an instance by name or uuid.
208
getInstance :: ConfigData -> String -> ErrorResult Instance
209
getInstance cfg name =
210
  let instances = fromContainer (configInstances cfg)
211
  in case getItem "Instance" name instances of
212
       -- if not found by uuid, we need to look it up by name
213
       Ok inst -> Ok inst
214
       Bad _ -> let by_name = M.mapKeys
215
                              (instName . (M.!) instances) instances
216
                in getItem "Instance" name by_name
217

    
218
-- | Looks up a disk by uuid.
219
getDisk :: ConfigData -> String -> ErrorResult Disk
220
getDisk cfg name =
221
  let disks = fromContainer (configDisks cfg)
222
  in getItem "Disk" name disks
223

    
224
-- | Looks up a node group by name or uuid.
225
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
226
getGroup cfg name =
227
  let groups = fromContainer (configNodegroups cfg)
228
  in case getItem "NodeGroup" name groups of
229
       -- if not found by uuid, we need to look it up by name, slow
230
       Ok grp -> Ok grp
231
       Bad _ -> let by_name = M.mapKeys
232
                              (groupName . (M.!) groups) groups
233
                in getItem "NodeGroup" name by_name
234

    
235
-- | Computes a node group's node params.
236
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
237
getGroupNdParams cfg ng =
238
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
239

    
240
-- | Computes a node group's ipolicy.
241
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
242
getGroupIpolicy cfg ng =
243
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
244

    
245
-- | Computes a group\'s (merged) disk params.
246
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
247
getGroupDiskParams cfg ng =
248
  GenericContainer $
249
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
250
           (fromContainer $ groupDiskparams ng) []
251

    
252
-- | Get nodes of a given node group.
253
getGroupNodes :: ConfigData -> String -> [Node]
254
getGroupNodes cfg gname =
255
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
256
  filter ((==gname) . nodeGroup) all_nodes
257

    
258
-- | Get (primary, secondary) instances of a given node group.
259
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
260
getGroupInstances cfg gname =
261
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
262
      ginsts = map (getNodeInstances cfg) gnodes in
263
  (concatMap fst ginsts, concatMap snd ginsts)
264

    
265
-- | Looks up a network. If looking up by uuid fails, we look up
266
-- by name.
267
getNetwork :: ConfigData -> String -> ErrorResult Network
268
getNetwork cfg name =
269
  let networks = fromContainer (configNetworks cfg)
270
  in case getItem "Network" name networks of
271
       Ok net -> Ok net
272
       Bad _ -> let by_name = M.mapKeys
273
                              (fromNonEmpty . networkName . (M.!) networks)
274
                              networks
275
                in getItem "Network" name by_name
276

    
277
-- | Retrieves the instance hypervisor params, missing values filled with
278
-- cluster defaults.
279
getFilledInstHvParams :: [String] -> ConfigData -> Instance -> HvParams
280
getFilledInstHvParams globals cfg inst =
281
  -- First get the defaults of the parent
282
  let hvName = hypervisorToRaw . instHypervisor $ inst
283
      hvParamMap = fromContainer . clusterHvparams $ configCluster cfg
284
      parentHvParams = maybe M.empty fromContainer $ M.lookup hvName hvParamMap
285
  -- Then the os defaults for the given hypervisor
286
      osName = instOs inst
287
      osParamMap = fromContainer . clusterOsHvp $ configCluster cfg
288
      osHvParamMap = maybe M.empty fromContainer $ M.lookup osName osParamMap
289
      osHvParams = maybe M.empty fromContainer $ M.lookup hvName osHvParamMap
290
  -- Then the child
291
      childHvParams = fromContainer . instHvparams $ inst
292
  -- Helper function
293
      fillFn con val = fillDict con val globals
294
  in GenericContainer $ fillFn (fillFn parentHvParams osHvParams) childHvParams
295

    
296
-- | Retrieves the instance backend params, missing values filled with cluster
297
-- defaults.
298
getFilledInstBeParams :: ConfigData -> Instance -> ErrorResult FilledBeParams
299
getFilledInstBeParams cfg inst = do
300
  let beParamMap = fromContainer . clusterBeparams . configCluster $ cfg
301
  parentParams <- getItem "FilledBeParams" C.ppDefault beParamMap
302
  return $ fillBeParams parentParams (instBeparams inst)
303

    
304
-- | Retrieves the instance os params, missing values filled with cluster
305
-- defaults. This does NOT include private and secret parameters.
306
getFilledInstOsParams :: ConfigData -> Instance -> OsParams
307
getFilledInstOsParams cfg inst =
308
  let osLookupName = takeWhile (/= '+') (instOs inst)
309
      osParamMap = fromContainer . clusterOsparams $ configCluster cfg
310
      childOsParams = instOsparams inst
311
  in case getItem "OsParams" osLookupName osParamMap of
312
       Ok parentOsParams -> GenericContainer $
313
                              fillDict (fromContainer parentOsParams)
314
                                       (fromContainer childOsParams) []
315
       Bad _             -> childOsParams
316

    
317
-- | Looks up an instance's primary node.
318
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
319
getInstPrimaryNode cfg name =
320
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
321

    
322
-- | Retrieves all nodes hosting a DRBD disk
323
getDrbdDiskNodes :: ConfigData -> Disk -> [Node]
324
getDrbdDiskNodes cfg disk =
325
  let retrieved = case diskLogicalId disk of
326
                    LIDDrbd8 nodeA nodeB _ _ _ _ ->
327
                      justOk [getNode cfg nodeA, getNode cfg nodeB]
328
                    _                            -> []
329
  in retrieved ++ concatMap (getDrbdDiskNodes cfg) (diskChildren disk)
330

    
331
-- | Retrieves all the nodes of the instance.
332
--
333
-- As instances not using DRBD can be sent as a parameter as well,
334
-- the primary node has to be appended to the results.
335
getInstAllNodes :: ConfigData -> String -> ErrorResult [Node]
336
getInstAllNodes cfg name = do
337
  inst_disks <- getInstDisksByName cfg name
338
  let diskNodes = concatMap (getDrbdDiskNodes cfg) inst_disks
339
  pNode <- getInstPrimaryNode cfg name
340
  return . nub $ pNode:diskNodes
341

    
342
-- | Get disks for a given instance object.
343
getInstDisks :: ConfigData -> Instance -> ErrorResult [Disk]
344
getInstDisks cfg =
345
  mapM (getDisk cfg) . instDisks
346

    
347
-- | Get disks for a given instance.
348
-- The instance is specified by name or uuid.
349
getInstDisksByName :: ConfigData -> String -> ErrorResult [Disk]
350
getInstDisksByName cfg iname =
351
  getInstance cfg iname >>= getInstDisks cfg
352

    
353
-- | Filters DRBD minors for a given node.
354
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
355
getDrbdMinorsForNode node disk =
356
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
357
      this_minors =
358
        case diskLogicalId disk of
359
          LIDDrbd8 nodeA nodeB _ minorA minorB _
360
            | nodeA == node -> [(minorA, nodeB)]
361
            | nodeB == node -> [(minorB, nodeA)]
362
          _ -> []
363
  in this_minors ++ child_minors
364

    
365
-- | String for primary role.
366
rolePrimary :: String
367
rolePrimary = "primary"
368

    
369
-- | String for secondary role.
370
roleSecondary :: String
371
roleSecondary = "secondary"
372

    
373
-- | Gets the list of DRBD minors for an instance that are related to
374
-- a given node.
375
getInstMinorsForNode :: ConfigData -> String -> Instance
376
                     -> [(String, Int, String, String, String, String)]
377
getInstMinorsForNode cfg node inst =
378
  let role = if node == instPrimaryNode inst
379
               then rolePrimary
380
               else roleSecondary
381
      iname = instName inst
382
      inst_disks = case getInstDisks cfg inst of
383
                     Ok disks -> disks
384
                     Bad _ -> []
385
  -- FIXME: the disk/ build there is hack-ish; unify this in a
386
  -- separate place, or reuse the iv_name (but that is deprecated on
387
  -- the Python side)
388
  in concatMap (\(idx, dsk) ->
389
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
390
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
391
     zip [(0::Int)..] $ inst_disks
392

    
393
-- | Builds link -> ip -> instname map.
394
--
395
-- TODO: improve this by splitting it into multiple independent functions:
396
--
397
-- * abstract the \"fetch instance with filled params\" functionality
398
--
399
-- * abstsract the [instance] -> [(nic, instance_name)] part
400
--
401
-- * etc.
402
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
403
buildLinkIpInstnameMap cfg =
404
  let cluster = configCluster cfg
405
      instances = M.elems . fromContainer . configInstances $ cfg
406
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
407
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
408
             instances
409
  in foldl' (\accum (iname, nic) ->
410
               let pparams = nicNicparams nic
411
                   fparams = fillNicParams defparams pparams
412
                   link = nicpLink fparams
413
               in case nicIp nic of
414
                    Nothing -> accum
415
                    Just ip -> let oldipmap = M.findWithDefault M.empty
416
                                              link accum
417
                                   newipmap = M.insert ip iname oldipmap
418
                               in M.insert link newipmap accum
419
            ) M.empty nics
420

    
421

    
422
-- | Returns a node's group, with optional failure if we can't find it
423
-- (configuration corrupt).
424
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
425
getGroupOfNode cfg node =
426
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
427

    
428
-- | Returns a node's ndparams, filled.
429
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
430
getNodeNdParams cfg node = do
431
  group <- getGroupOfNode cfg node
432
  let gparams = getGroupNdParams cfg group
433
  return $ fillNDParams gparams (nodeNdparams node)
434

    
435
instance NdParamObject Node where
436
  getNdParamsOf = getNodeNdParams
437

    
438
instance NdParamObject NodeGroup where
439
  getNdParamsOf cfg = Just . getGroupNdParams cfg
440

    
441
instance NdParamObject Cluster where
442
  getNdParamsOf _ = Just . clusterNdparams