Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Config.hs @ 368e95fd

History | View | Annotate | Download (11.6 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
    , getInstPrimaryNode
46
    , getInstMinorsForNode
47
    , getNetwork
48
    , buildLinkIpInstnameMap
49
    , instNodes
50
    ) where
51

    
52
import Control.Monad (liftM)
53
import Data.List (foldl')
54
import qualified Data.Map as M
55
import qualified Data.Set as S
56
import qualified Text.JSON as J
57

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

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

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

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

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

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

    
84
-- * Query functions
85

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

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

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

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

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

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

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

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

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

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

    
164
-- | Looks up a node by name or uuid.
165
getNode :: ConfigData -> String -> ErrorResult Node
166
getNode cfg name =
167
  let nodes = fromContainer (configNodes cfg)
168
  in case getItem "Node" name nodes of
169
       -- if not found by uuid, we need to look it up by name
170
       Ok node -> Ok node
171
       Bad _ -> let by_name = M.mapKeys
172
                              (nodeName . (M.!) nodes) nodes
173
                in getItem "Node" name by_name
174

    
175
-- | Looks up an instance by name or uuid.
176
getInstance :: ConfigData -> String -> ErrorResult Instance
177
getInstance cfg name =
178
  let instances = fromContainer (configInstances cfg)
179
  in case getItem "Instance" name instances of
180
       -- if not found by uuid, we need to look it up by name
181
       Ok inst -> Ok inst
182
       Bad _ -> let by_name = M.mapKeys
183
                              (instName . (M.!) instances) instances
184
                in getItem "Instance" name by_name
185

    
186
-- | Looks up a node group by name or uuid.
187
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
188
getGroup cfg name =
189
  let groups = fromContainer (configNodegroups cfg)
190
  in case getItem "NodeGroup" name groups of
191
       -- if not found by uuid, we need to look it up by name, slow
192
       Ok grp -> Ok grp
193
       Bad _ -> let by_name = M.mapKeys
194
                              (groupName . (M.!) groups) groups
195
                in getItem "NodeGroup" name by_name
196

    
197
-- | Computes a node group's node params.
198
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
199
getGroupNdParams cfg ng =
200
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
201

    
202
-- | Computes a node group's ipolicy.
203
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
204
getGroupIpolicy cfg ng =
205
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
206

    
207
-- | Computes a group\'s (merged) disk params.
208
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
209
getGroupDiskParams cfg ng =
210
  GenericContainer $
211
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
212
           (fromContainer $ groupDiskparams ng) []
213

    
214
-- | Get nodes of a given node group.
215
getGroupNodes :: ConfigData -> String -> [Node]
216
getGroupNodes cfg gname =
217
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
218
  filter ((==gname) . nodeGroup) all_nodes
219

    
220
-- | Get (primary, secondary) instances of a given node group.
221
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
222
getGroupInstances cfg gname =
223
  let gnodes = map nodeUuid (getGroupNodes cfg gname)
224
      ginsts = map (getNodeInstances cfg) gnodes in
225
  (concatMap fst ginsts, concatMap snd ginsts)
226

    
227
-- | Looks up a network. If looking up by uuid fails, we look up
228
-- by name.
229
getNetwork :: ConfigData -> String -> ErrorResult Network
230
getNetwork cfg name =
231
  let networks = fromContainer (configNetworks cfg)
232
  in case getItem "Network" name networks of
233
       Ok net -> Ok net
234
       Bad _ -> let by_name = M.mapKeys
235
                              (fromNonEmpty . networkName . (M.!) networks)
236
                              networks
237
                in getItem "Network" name by_name
238

    
239
-- | Looks up an instance's primary node.
240
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
241
getInstPrimaryNode cfg name =
242
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
243

    
244
-- | Filters DRBD minors for a given node.
245
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
246
getDrbdMinorsForNode node disk =
247
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
248
      this_minors =
249
        case diskLogicalId disk of
250
          LIDDrbd8 nodeA nodeB _ minorA minorB _
251
            | nodeA == node -> [(minorA, nodeB)]
252
            | nodeB == node -> [(minorB, nodeA)]
253
          _ -> []
254
  in this_minors ++ child_minors
255

    
256
-- | String for primary role.
257
rolePrimary :: String
258
rolePrimary = "primary"
259

    
260
-- | String for secondary role.
261
roleSecondary :: String
262
roleSecondary = "secondary"
263

    
264
-- | Gets the list of DRBD minors for an instance that are related to
265
-- a given node.
266
getInstMinorsForNode :: String -> Instance
267
                     -> [(String, Int, String, String, String, String)]
268
getInstMinorsForNode node inst =
269
  let role = if node == instPrimaryNode inst
270
               then rolePrimary
271
               else roleSecondary
272
      iname = instName inst
273
  -- FIXME: the disk/ build there is hack-ish; unify this in a
274
  -- separate place, or reuse the iv_name (but that is deprecated on
275
  -- the Python side)
276
  in concatMap (\(idx, dsk) ->
277
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
278
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
279
     zip [(0::Int)..] . instDisks $ inst
280

    
281
-- | Builds link -> ip -> instname map.
282
--
283
-- TODO: improve this by splitting it into multiple independent functions:
284
--
285
-- * abstract the \"fetch instance with filled params\" functionality
286
--
287
-- * abstsract the [instance] -> [(nic, instance_name)] part
288
--
289
-- * etc.
290
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
291
buildLinkIpInstnameMap cfg =
292
  let cluster = configCluster cfg
293
      instances = M.elems . fromContainer . configInstances $ cfg
294
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
295
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
296
             instances
297
  in foldl' (\accum (iname, nic) ->
298
               let pparams = nicNicparams nic
299
                   fparams = fillNicParams defparams pparams
300
                   link = nicpLink fparams
301
               in case nicIp nic of
302
                    Nothing -> accum
303
                    Just ip -> let oldipmap = M.findWithDefault M.empty
304
                                              link accum
305
                                   newipmap = M.insert ip iname oldipmap
306
                               in M.insert link newipmap accum
307
            ) M.empty nics
308

    
309

    
310
-- | Returns a node's group, with optional failure if we can't find it
311
-- (configuration corrupt).
312
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
313
getGroupOfNode cfg node =
314
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
315

    
316
-- | Returns a node's ndparams, filled.
317
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
318
getNodeNdParams cfg node = do
319
  group <- getGroupOfNode cfg node
320
  let gparams = getGroupNdParams cfg group
321
  return $ fillNDParams gparams (nodeNdparams node)
322

    
323
instance NdParamObject Node where
324
  getNdParamsOf = getNodeNdParams
325

    
326
instance NdParamObject NodeGroup where
327
  getNdParamsOf cfg = Just . getGroupNdParams cfg
328

    
329
instance NdParamObject Cluster where
330
  getNdParamsOf _ = Just . clusterNdparams