Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ 05092772

History | View | Annotate | Download (12.5 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
    , getNodeInstances
31
    , getNodeRole
32
    , getNodeNdParams
33
    , getDefaultNicLink
34
    , getDefaultHypervisor
35
    , getInstancesIpByLink
36
    , getNode
37
    , getInstance
38
    , getGroup
39
    , getGroupNdParams
40
    , getGroupIpolicy
41
    , getGroupDiskParams
42
    , getGroupNodes
43
    , getGroupInstances
44
    , getGroupOfNode
45
    , getGroupConnections
46
    , getInstPrimaryNode
47
    , getInstMinorsForNode
48
    , getNetwork
49
    , buildLinkIpInstnameMap
50
    , instNodes
51
    ) where
52

    
53
import Control.Monad (liftM)
54
import Data.List (foldl')
55
import Data.Maybe (fromMaybe, mapMaybe)
56
import qualified Data.Map as M
57
import qualified Data.Set as S
58
import qualified Text.JSON as J
59

    
60
import Ganeti.BasicTypes
61
import qualified Ganeti.Constants as C
62
import Ganeti.Errors
63
import Ganeti.JSON
64
import Ganeti.Objects
65
import Ganeti.Types
66

    
67
-- | Type alias for the link and ip map.
68
type LinkIpMap = M.Map String (M.Map String String)
69

    
70
-- | Type class denoting objects which have node parameters.
71
class NdParamObject a where
72
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
73

    
74
-- | Reads the config file.
75
readConfig :: FilePath -> IO String
76
readConfig = readFile
77

    
78
-- | Parses the configuration file.
79
parseConfig :: String -> Result ConfigData
80
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
81

    
82
-- | Wrapper over 'readConfig' and 'parseConfig'.
83
loadConfig :: FilePath -> IO (Result ConfigData)
84
loadConfig = fmap parseConfig . readConfig
85

    
86
-- * Query functions
87

    
88
-- | Computes the nodes covered by a disk.
89
computeDiskNodes :: Disk -> S.Set String
90
computeDiskNodes dsk =
91
  case diskLogicalId dsk of
92
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
93
    _ -> S.empty
94

    
95
-- | Computes all disk-related nodes of an instance. For non-DRBD,
96
-- this will be empty, for DRBD it will contain both the primary and
97
-- the secondaries.
98
instDiskNodes :: Instance -> S.Set String
99
instDiskNodes = S.unions . map computeDiskNodes . instDisks
100

    
101
-- | Computes all nodes of an instance.
102
instNodes :: Instance -> S.Set String
103
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
104

    
105
-- | Computes the secondary nodes of an instance. Since this is valid
106
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
107
-- extra primary insert.
108
instSecondaryNodes :: Instance -> S.Set String
109
instSecondaryNodes inst =
110
  instPrimaryNode inst `S.delete` instDiskNodes inst
111

    
112
-- | Get instances of a given node.
113
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
114
getNodeInstances cfg nname =
115
    let all_inst = M.elems . fromContainer . configInstances $ cfg
116
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
117
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
118
    in (pri_inst, sec_inst)
119

    
120
-- | Computes the role of a node.
121
getNodeRole :: ConfigData -> Node -> NodeRole
122
getNodeRole cfg node
123
  | nodeName node == clusterMasterNode (configCluster cfg) = NRMaster
124
  | nodeMasterCandidate node = NRCandidate
125
  | nodeDrained node = NRDrained
126
  | nodeOffline node = NROffline
127
  | otherwise = NRRegular
128

    
129
-- | Returns the default cluster link.
130
getDefaultNicLink :: ConfigData -> String
131
getDefaultNicLink =
132
  nicpLink . (M.! C.ppDefault) . fromContainer .
133
  clusterNicparams . configCluster
134

    
135
-- | Returns the default cluster hypervisor.
136
getDefaultHypervisor :: ConfigData -> Hypervisor
137
getDefaultHypervisor cfg =
138
  case clusterEnabledHypervisors $ configCluster cfg of
139
    -- FIXME: this case shouldn't happen (configuration broken), but
140
    -- for now we handle it here because we're not authoritative for
141
    -- the config
142
    []  -> XenPvm
143
    x:_ -> x
144

    
145
-- | Returns instances of a given link.
146
getInstancesIpByLink :: LinkIpMap -> String -> [String]
147
getInstancesIpByLink linkipmap link =
148
  M.keys $ M.findWithDefault M.empty link linkipmap
149

    
150
-- | Generic lookup function that converts from a possible abbreviated
151
-- name to a full name.
152
getItem :: String -> String -> M.Map String a -> ErrorResult a
153
getItem kind name allitems = do
154
  let lresult = lookupName (M.keys allitems) name
155
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
156
                        ECodeNoEnt
157
  fullname <- case lrMatchPriority lresult of
158
                PartialMatch -> Ok $ lrContent lresult
159
                ExactMatch -> Ok $ lrContent lresult
160
                MultipleMatch -> err "has multiple matches"
161
                FailMatch -> err "not found"
162
  maybe (err "not found after successfull match?!") Ok $
163
        M.lookup fullname allitems
164

    
165
-- | Looks up a node.
166
getNode :: ConfigData -> String -> ErrorResult Node
167
getNode cfg name = getItem "Node" name (fromContainer $ configNodes cfg)
168

    
169
-- | Looks up an instance.
170
getInstance :: ConfigData -> String -> ErrorResult Instance
171
getInstance cfg name =
172
  getItem "Instance" name (fromContainer $ configInstances cfg)
173

    
174
-- | Looks up a node group. This is more tricky than for
175
-- node/instances since the groups map is indexed by uuid, not name.
176
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
177
getGroup cfg name =
178
  let groups = fromContainer (configNodegroups cfg)
179
  in case getItem "NodeGroup" name groups of
180
       -- if not found by uuid, we need to look it up by name, slow
181
       Ok grp -> Ok grp
182
       Bad _ -> let by_name = M.mapKeys
183
                              (groupName . (M.!) groups) groups
184
                in getItem "NodeGroup" name by_name
185

    
186
-- | Computes a node group's node params.
187
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
188
getGroupNdParams cfg ng =
189
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
190

    
191
-- | Computes a node group's ipolicy.
192
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
193
getGroupIpolicy cfg ng =
194
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
195

    
196
-- | Computes a group\'s (merged) disk params.
197
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
198
getGroupDiskParams cfg ng =
199
  GenericContainer $
200
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
201
           (fromContainer $ groupDiskparams ng) []
202

    
203
-- | Get nodes of a given node group.
204
getGroupNodes :: ConfigData -> String -> [Node]
205
getGroupNodes cfg gname =
206
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
207
  filter ((==gname) . nodeGroup) all_nodes
208

    
209
-- | Get (primary, secondary) instances of a given node group.
210
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
211
getGroupInstances cfg gname =
212
  let gnodes = map nodeName (getGroupNodes cfg gname)
213
      ginsts = map (getNodeInstances cfg) gnodes in
214
  (concatMap fst ginsts, concatMap snd ginsts)
215

    
216
-- | Looks up a network. If looking up by uuid fails, we look up
217
-- by name.
218
getNetwork :: ConfigData -> String -> ErrorResult Network
219
getNetwork cfg name =
220
  let networks = fromContainer (configNetworks cfg)
221
  in case getItem "Network" name networks of
222
       Ok net -> Ok net
223
       Bad _ -> let by_name = M.mapKeys
224
                              (fromNonEmpty . networkName . (M.!) networks)
225
                              networks
226
                in getItem "Network" name by_name
227

    
228
-- | Given a network's UUID, this function lists all connections from
229
-- the network to nodegroups including the respective mode and links.
230
getGroupConnections :: ConfigData -> String -> [(String, String, String)]
231
getGroupConnections cfg network_uuid =
232
  mapMaybe (getGroupConnection network_uuid)
233
  ((M.elems . fromContainer . configNodegroups) cfg)
234

    
235
-- | Given a network's UUID and a node group, this function assembles
236
-- a tuple of the group's name, the mode and the link by which the
237
-- network is connected to the group. Returns 'Nothing' if the network
238
-- is not connected to the group.
239
getGroupConnection :: String -> NodeGroup -> Maybe (String, String, String)
240
getGroupConnection network_uuid group =
241
  let networks = fromContainer . groupNetworks $ group
242
  in case M.lookup network_uuid networks of
243
    Nothing -> Nothing
244
    Just network ->
245
      Just (groupName group, getNicMode network, getNicLink network)
246

    
247
-- | Retrieves the network's mode and formats it human-readable,
248
-- also in case it is not available.
249
getNicMode :: PartialNicParams -> String
250
getNicMode nic_params =
251
  maybe "-" nICModeToRaw $ nicpModeP nic_params
252

    
253
-- | Retrieves the network's link and formats it human-readable, also in
254
-- case it it not available.
255
getNicLink :: PartialNicParams -> String
256
getNicLink nic_params = fromMaybe "-" (nicpLinkP nic_params)
257

    
258
-- | Looks up an instance's primary node.
259
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
260
getInstPrimaryNode cfg name =
261
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
262

    
263
-- | Filters DRBD minors for a given node.
264
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
265
getDrbdMinorsForNode node disk =
266
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
267
      this_minors =
268
        case diskLogicalId disk of
269
          LIDDrbd8 nodeA nodeB _ minorA minorB _
270
            | nodeA == node -> [(minorA, nodeB)]
271
            | nodeB == node -> [(minorB, nodeA)]
272
          _ -> []
273
  in this_minors ++ child_minors
274

    
275
-- | String for primary role.
276
rolePrimary :: String
277
rolePrimary = "primary"
278

    
279
-- | String for secondary role.
280
roleSecondary :: String
281
roleSecondary = "secondary"
282

    
283
-- | Gets the list of DRBD minors for an instance that are related to
284
-- a given node.
285
getInstMinorsForNode :: String -> Instance
286
                     -> [(String, Int, String, String, String, String)]
287
getInstMinorsForNode node inst =
288
  let role = if node == instPrimaryNode inst
289
               then rolePrimary
290
               else roleSecondary
291
      iname = instName inst
292
  -- FIXME: the disk/ build there is hack-ish; unify this in a
293
  -- separate place, or reuse the iv_name (but that is deprecated on
294
  -- the Python side)
295
  in concatMap (\(idx, dsk) ->
296
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
297
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
298
     zip [(0::Int)..] . instDisks $ inst
299

    
300
-- | Builds link -> ip -> instname map.
301
--
302
-- TODO: improve this by splitting it into multiple independent functions:
303
--
304
-- * abstract the \"fetch instance with filled params\" functionality
305
--
306
-- * abstsract the [instance] -> [(nic, instance_name)] part
307
--
308
-- * etc.
309
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
310
buildLinkIpInstnameMap cfg =
311
  let cluster = configCluster cfg
312
      instances = M.elems . fromContainer . configInstances $ cfg
313
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
314
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
315
             instances
316
  in foldl' (\accum (iname, nic) ->
317
               let pparams = nicNicparams nic
318
                   fparams = fillNicParams defparams pparams
319
                   link = nicpLink fparams
320
               in case nicIp nic of
321
                    Nothing -> accum
322
                    Just ip -> let oldipmap = M.findWithDefault M.empty
323
                                              link accum
324
                                   newipmap = M.insert ip iname oldipmap
325
                               in M.insert link newipmap accum
326
            ) M.empty nics
327

    
328

    
329
-- | Returns a node's group, with optional failure if we can't find it
330
-- (configuration corrupt).
331
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
332
getGroupOfNode cfg node =
333
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
334

    
335
-- | Returns a node's ndparams, filled.
336
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
337
getNodeNdParams cfg node = do
338
  group <- getGroupOfNode cfg node
339
  let gparams = getGroupNdParams cfg group
340
  return $ fillNDParams gparams (nodeNdparams node)
341

    
342
instance NdParamObject Node where
343
  getNdParamsOf = getNodeNdParams
344

    
345
instance NdParamObject NodeGroup where
346
  getNdParamsOf cfg = Just . getGroupNdParams cfg
347

    
348
instance NdParamObject Cluster where
349
  getNdParamsOf _ = Just . clusterNdparams