Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Config.hs @ cefd4a4a

History | View | Annotate | Download (10.6 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 eaa64cd8 Iustin Pop
    , getNode
37 eaa64cd8 Iustin Pop
    , getInstance
38 4cd428db Iustin Pop
    , getGroup
39 da45c352 Iustin Pop
    , getGroupNdParams
40 e5cb098c Agata Murawska
    , getGroupIpolicy
41 90d033ef Iustin Pop
    , getGroupDiskParams
42 e5cb098c Agata Murawska
    , getGroupNodes
43 e5cb098c Agata Murawska
    , getGroupInstances
44 da45c352 Iustin Pop
    , getGroupOfNode
45 eaa64cd8 Iustin Pop
    , getInstPrimaryNode
46 d81ec8b7 Iustin Pop
    , getInstMinorsForNode
47 eaa64cd8 Iustin Pop
    , buildLinkIpInstnameMap
48 7b2ead5a Iustin Pop
    , instNodes
49 eaa64cd8 Iustin Pop
    ) where
50 eaa64cd8 Iustin Pop
51 2cdaf225 Iustin Pop
import Control.Monad (liftM)
52 eaa64cd8 Iustin Pop
import Data.List (foldl')
53 eaa64cd8 Iustin Pop
import qualified Data.Map as M
54 7b2ead5a Iustin Pop
import qualified Data.Set as S
55 eaa64cd8 Iustin Pop
import qualified Text.JSON as J
56 eaa64cd8 Iustin Pop
57 eaa64cd8 Iustin Pop
import Ganeti.BasicTypes
58 eaa64cd8 Iustin Pop
import qualified Ganeti.Constants as C
59 5183e8be Iustin Pop
import Ganeti.Errors
60 5183e8be Iustin Pop
import Ganeti.JSON
61 eaa64cd8 Iustin Pop
import Ganeti.Objects
62 22381768 Iustin Pop
import Ganeti.Types
63 eaa64cd8 Iustin Pop
64 eaa64cd8 Iustin Pop
-- | Type alias for the link and ip map.
65 eaa64cd8 Iustin Pop
type LinkIpMap = M.Map String (M.Map String String)
66 eaa64cd8 Iustin Pop
67 da45c352 Iustin Pop
-- | Type class denoting objects which have node parameters.
68 da45c352 Iustin Pop
class NdParamObject a where
69 da45c352 Iustin Pop
  getNdParamsOf :: ConfigData -> a -> Maybe FilledNDParams
70 da45c352 Iustin Pop
71 eaa64cd8 Iustin Pop
-- | Reads the config file.
72 eaa64cd8 Iustin Pop
readConfig :: FilePath -> IO String
73 eaa64cd8 Iustin Pop
readConfig = readFile
74 eaa64cd8 Iustin Pop
75 eaa64cd8 Iustin Pop
-- | Parses the configuration file.
76 eaa64cd8 Iustin Pop
parseConfig :: String -> Result ConfigData
77 eaa64cd8 Iustin Pop
parseConfig = fromJResult "parsing configuration" . J.decodeStrict
78 eaa64cd8 Iustin Pop
79 eaa64cd8 Iustin Pop
-- | Wrapper over 'readConfig' and 'parseConfig'.
80 eaa64cd8 Iustin Pop
loadConfig :: FilePath -> IO (Result ConfigData)
81 eaa64cd8 Iustin Pop
loadConfig = fmap parseConfig . readConfig
82 eaa64cd8 Iustin Pop
83 eaa64cd8 Iustin Pop
-- * Query functions
84 eaa64cd8 Iustin Pop
85 7b2ead5a Iustin Pop
-- | Computes the nodes covered by a disk.
86 7b2ead5a Iustin Pop
computeDiskNodes :: Disk -> S.Set String
87 7b2ead5a Iustin Pop
computeDiskNodes dsk =
88 7b2ead5a Iustin Pop
  case diskLogicalId dsk of
89 7b2ead5a Iustin Pop
    LIDDrbd8 nodeA nodeB _ _ _ _ -> S.fromList [nodeA, nodeB]
90 7b2ead5a Iustin Pop
    _ -> S.empty
91 7b2ead5a Iustin Pop
92 7b2ead5a Iustin Pop
-- | Computes all disk-related nodes of an instance. For non-DRBD,
93 7b2ead5a Iustin Pop
-- this will be empty, for DRBD it will contain both the primary and
94 7b2ead5a Iustin Pop
-- the secondaries.
95 7b2ead5a Iustin Pop
instDiskNodes :: Instance -> S.Set String
96 7b2ead5a Iustin Pop
instDiskNodes = S.unions . map computeDiskNodes . instDisks
97 7b2ead5a Iustin Pop
98 7b2ead5a Iustin Pop
-- | Computes all nodes of an instance.
99 7b2ead5a Iustin Pop
instNodes :: Instance -> S.Set String
100 7b2ead5a Iustin Pop
instNodes inst = instPrimaryNode inst `S.insert` instDiskNodes inst
101 7b2ead5a Iustin Pop
102 7b2ead5a Iustin Pop
-- | Computes the secondary nodes of an instance. Since this is valid
103 7b2ead5a Iustin Pop
-- only for DRBD, we call directly 'instDiskNodes', skipping over the
104 7b2ead5a Iustin Pop
-- extra primary insert.
105 7b2ead5a Iustin Pop
instSecondaryNodes :: Instance -> S.Set String
106 7b2ead5a Iustin Pop
instSecondaryNodes inst =
107 7b2ead5a Iustin Pop
  instPrimaryNode inst `S.delete` instDiskNodes inst
108 7b2ead5a Iustin Pop
109 eaa64cd8 Iustin Pop
-- | Get instances of a given node.
110 eaa64cd8 Iustin Pop
getNodeInstances :: ConfigData -> String -> ([Instance], [Instance])
111 eaa64cd8 Iustin Pop
getNodeInstances cfg nname =
112 84835174 Iustin Pop
    let all_inst = M.elems . fromContainer . configInstances $ cfg
113 eaa64cd8 Iustin Pop
        pri_inst = filter ((== nname) . instPrimaryNode) all_inst
114 7b2ead5a Iustin Pop
        sec_inst = filter ((nname `S.member`) . instSecondaryNodes) all_inst
115 eaa64cd8 Iustin Pop
    in (pri_inst, sec_inst)
116 eaa64cd8 Iustin Pop
117 da45c352 Iustin Pop
-- | Computes the role of a node.
118 da45c352 Iustin Pop
getNodeRole :: ConfigData -> Node -> NodeRole
119 da45c352 Iustin Pop
getNodeRole cfg node
120 5b11f8db Iustin Pop
  | nodeName node == clusterMasterNode (configCluster cfg) = NRMaster
121 da45c352 Iustin Pop
  | nodeMasterCandidate node = NRCandidate
122 da45c352 Iustin Pop
  | nodeDrained node = NRDrained
123 da45c352 Iustin Pop
  | nodeOffline node = NROffline
124 da45c352 Iustin Pop
  | otherwise = NRRegular
125 da45c352 Iustin Pop
126 eaa64cd8 Iustin Pop
-- | Returns the default cluster link.
127 eaa64cd8 Iustin Pop
getDefaultNicLink :: ConfigData -> String
128 eaa64cd8 Iustin Pop
getDefaultNicLink =
129 84835174 Iustin Pop
  nicpLink . (M.! C.ppDefault) . fromContainer .
130 84835174 Iustin Pop
  clusterNicparams . configCluster
131 eaa64cd8 Iustin Pop
132 0ec87781 Iustin Pop
-- | Returns the default cluster hypervisor.
133 0ec87781 Iustin Pop
getDefaultHypervisor :: ConfigData -> Hypervisor
134 0ec87781 Iustin Pop
getDefaultHypervisor cfg =
135 0ec87781 Iustin Pop
  case clusterEnabledHypervisors $ configCluster cfg of
136 0ec87781 Iustin Pop
    -- FIXME: this case shouldn't happen (configuration broken), but
137 0ec87781 Iustin Pop
    -- for now we handle it here because we're not authoritative for
138 0ec87781 Iustin Pop
    -- the config
139 0ec87781 Iustin Pop
    []  -> XenPvm
140 0ec87781 Iustin Pop
    x:_ -> x
141 0ec87781 Iustin Pop
142 eaa64cd8 Iustin Pop
-- | Returns instances of a given link.
143 eaa64cd8 Iustin Pop
getInstancesIpByLink :: LinkIpMap -> String -> [String]
144 eaa64cd8 Iustin Pop
getInstancesIpByLink linkipmap link =
145 eaa64cd8 Iustin Pop
  M.keys $ M.findWithDefault M.empty link linkipmap
146 eaa64cd8 Iustin Pop
147 0fc8e521 Iustin Pop
-- | Generic lookup function that converts from a possible abbreviated
148 0fc8e521 Iustin Pop
-- name to a full name.
149 5183e8be Iustin Pop
getItem :: String -> String -> M.Map String a -> ErrorResult a
150 0fc8e521 Iustin Pop
getItem kind name allitems = do
151 0fc8e521 Iustin Pop
  let lresult = lookupName (M.keys allitems) name
152 5183e8be Iustin Pop
      err msg = Bad $ OpPrereqError (kind ++ " name " ++ name ++ " " ++ msg)
153 5183e8be Iustin Pop
                        ECodeNoEnt
154 0fc8e521 Iustin Pop
  fullname <- case lrMatchPriority lresult of
155 0fc8e521 Iustin Pop
                PartialMatch -> Ok $ lrContent lresult
156 0fc8e521 Iustin Pop
                ExactMatch -> Ok $ lrContent lresult
157 0fc8e521 Iustin Pop
                MultipleMatch -> err "has multiple matches"
158 0fc8e521 Iustin Pop
                FailMatch -> err "not found"
159 0fc8e521 Iustin Pop
  maybe (err "not found after successfull match?!") Ok $
160 0fc8e521 Iustin Pop
        M.lookup fullname allitems
161 0fc8e521 Iustin Pop
162 eaa64cd8 Iustin Pop
-- | Looks up a node.
163 5183e8be Iustin Pop
getNode :: ConfigData -> String -> ErrorResult Node
164 84835174 Iustin Pop
getNode cfg name = getItem "Node" name (fromContainer $ configNodes cfg)
165 eaa64cd8 Iustin Pop
166 eaa64cd8 Iustin Pop
-- | Looks up an instance.
167 5183e8be Iustin Pop
getInstance :: ConfigData -> String -> ErrorResult Instance
168 84835174 Iustin Pop
getInstance cfg name =
169 84835174 Iustin Pop
  getItem "Instance" name (fromContainer $ configInstances cfg)
170 eaa64cd8 Iustin Pop
171 4cd428db Iustin Pop
-- | Looks up a node group. This is more tricky than for
172 4cd428db Iustin Pop
-- node/instances since the groups map is indexed by uuid, not name.
173 5183e8be Iustin Pop
getGroup :: ConfigData -> String -> ErrorResult NodeGroup
174 4cd428db Iustin Pop
getGroup cfg name =
175 4cd428db Iustin Pop
  let groups = fromContainer (configNodegroups cfg)
176 4cd428db Iustin Pop
  in case getItem "NodeGroup" name groups of
177 4cd428db Iustin Pop
       -- if not found by uuid, we need to look it up by name, slow
178 4cd428db Iustin Pop
       Ok grp -> Ok grp
179 4cd428db Iustin Pop
       Bad _ -> let by_name = M.mapKeys
180 5b11f8db Iustin Pop
                              (groupName . (M.!) groups) groups
181 4cd428db Iustin Pop
                in getItem "NodeGroup" name by_name
182 4cd428db Iustin Pop
183 da45c352 Iustin Pop
-- | Computes a node group's node params.
184 da45c352 Iustin Pop
getGroupNdParams :: ConfigData -> NodeGroup -> FilledNDParams
185 da45c352 Iustin Pop
getGroupNdParams cfg ng =
186 da45c352 Iustin Pop
  fillNDParams (clusterNdparams $ configCluster cfg) (groupNdparams ng)
187 da45c352 Iustin Pop
188 e5cb098c Agata Murawska
-- | Computes a node group's ipolicy.
189 e5cb098c Agata Murawska
getGroupIpolicy :: ConfigData -> NodeGroup -> FilledIPolicy
190 e5cb098c Agata Murawska
getGroupIpolicy cfg ng =
191 e5cb098c Agata Murawska
  fillIPolicy (clusterIpolicy $ configCluster cfg) (groupIpolicy ng)
192 e5cb098c Agata Murawska
193 90d033ef Iustin Pop
-- | Computes a group\'s (merged) disk params.
194 90d033ef Iustin Pop
getGroupDiskParams :: ConfigData -> NodeGroup -> DiskParams
195 90d033ef Iustin Pop
getGroupDiskParams cfg ng =
196 edc1acde Iustin Pop
  GenericContainer $
197 90d033ef Iustin Pop
  fillDict (fromContainer . clusterDiskparams $ configCluster cfg)
198 90d033ef Iustin Pop
           (fromContainer $ groupDiskparams ng) []
199 90d033ef Iustin Pop
200 e5cb098c Agata Murawska
-- | Get nodes of a given node group.
201 e5cb098c Agata Murawska
getGroupNodes :: ConfigData -> String -> [Node]
202 e5cb098c Agata Murawska
getGroupNodes cfg gname =
203 e5cb098c Agata Murawska
  let all_nodes = M.elems . fromContainer . configNodes $ cfg in
204 e5cb098c Agata Murawska
  filter ((==gname) . nodeGroup) all_nodes
205 e5cb098c Agata Murawska
206 e5cb098c Agata Murawska
-- | Get (primary, secondary) instances of a given node group.
207 e5cb098c Agata Murawska
getGroupInstances :: ConfigData -> String -> ([Instance], [Instance])
208 e5cb098c Agata Murawska
getGroupInstances cfg gname =
209 e5cb098c Agata Murawska
  let gnodes = map nodeName (getGroupNodes cfg gname)
210 e5cb098c Agata Murawska
      ginsts = map (getNodeInstances cfg) gnodes in
211 e5cb098c Agata Murawska
  (concatMap fst ginsts, concatMap snd ginsts)
212 e5cb098c Agata Murawska
213 eaa64cd8 Iustin Pop
-- | Looks up an instance's primary node.
214 5183e8be Iustin Pop
getInstPrimaryNode :: ConfigData -> String -> ErrorResult Node
215 eaa64cd8 Iustin Pop
getInstPrimaryNode cfg name =
216 2cdaf225 Iustin Pop
  liftM instPrimaryNode (getInstance cfg name) >>= getNode cfg
217 eaa64cd8 Iustin Pop
218 d81ec8b7 Iustin Pop
-- | Filters DRBD minors for a given node.
219 d81ec8b7 Iustin Pop
getDrbdMinorsForNode :: String -> Disk -> [(Int, String)]
220 d81ec8b7 Iustin Pop
getDrbdMinorsForNode node disk =
221 d81ec8b7 Iustin Pop
  let child_minors = concatMap (getDrbdMinorsForNode node) (diskChildren disk)
222 d81ec8b7 Iustin Pop
      this_minors =
223 d81ec8b7 Iustin Pop
        case diskLogicalId disk of
224 d81ec8b7 Iustin Pop
          LIDDrbd8 nodeA nodeB _ minorA minorB _
225 d81ec8b7 Iustin Pop
            | nodeA == node -> [(minorA, nodeB)]
226 d81ec8b7 Iustin Pop
            | nodeB == node -> [(minorB, nodeA)]
227 d81ec8b7 Iustin Pop
          _ -> []
228 d81ec8b7 Iustin Pop
  in this_minors ++ child_minors
229 d81ec8b7 Iustin Pop
230 d81ec8b7 Iustin Pop
-- | String for primary role.
231 d81ec8b7 Iustin Pop
rolePrimary :: String
232 d81ec8b7 Iustin Pop
rolePrimary = "primary"
233 d81ec8b7 Iustin Pop
234 d81ec8b7 Iustin Pop
-- | String for secondary role.
235 d81ec8b7 Iustin Pop
roleSecondary :: String
236 d81ec8b7 Iustin Pop
roleSecondary = "secondary"
237 d81ec8b7 Iustin Pop
238 d81ec8b7 Iustin Pop
-- | Gets the list of DRBD minors for an instance that are related to
239 d81ec8b7 Iustin Pop
-- a given node.
240 d81ec8b7 Iustin Pop
getInstMinorsForNode :: String -> Instance
241 d81ec8b7 Iustin Pop
                     -> [(String, Int, String, String, String, String)]
242 d81ec8b7 Iustin Pop
getInstMinorsForNode node inst =
243 d81ec8b7 Iustin Pop
  let role = if node == instPrimaryNode inst
244 d81ec8b7 Iustin Pop
               then rolePrimary
245 d81ec8b7 Iustin Pop
               else roleSecondary
246 d81ec8b7 Iustin Pop
      iname = instName inst
247 d81ec8b7 Iustin Pop
  -- FIXME: the disk/ build there is hack-ish; unify this in a
248 d81ec8b7 Iustin Pop
  -- separate place, or reuse the iv_name (but that is deprecated on
249 d81ec8b7 Iustin Pop
  -- the Python side)
250 d81ec8b7 Iustin Pop
  in concatMap (\(idx, dsk) ->
251 d81ec8b7 Iustin Pop
            [(node, minor, iname, "disk/" ++ show idx, role, peer)
252 d81ec8b7 Iustin Pop
               | (minor, peer) <- getDrbdMinorsForNode node dsk]) .
253 d81ec8b7 Iustin Pop
     zip [(0::Int)..] . instDisks $ inst
254 d81ec8b7 Iustin Pop
255 eaa64cd8 Iustin Pop
-- | Builds link -> ip -> instname map.
256 eaa64cd8 Iustin Pop
--
257 eaa64cd8 Iustin Pop
-- TODO: improve this by splitting it into multiple independent functions:
258 eaa64cd8 Iustin Pop
--
259 eaa64cd8 Iustin Pop
-- * abstract the \"fetch instance with filled params\" functionality
260 eaa64cd8 Iustin Pop
--
261 eaa64cd8 Iustin Pop
-- * abstsract the [instance] -> [(nic, instance_name)] part
262 eaa64cd8 Iustin Pop
--
263 eaa64cd8 Iustin Pop
-- * etc.
264 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap :: ConfigData -> LinkIpMap
265 eaa64cd8 Iustin Pop
buildLinkIpInstnameMap cfg =
266 eaa64cd8 Iustin Pop
  let cluster = configCluster cfg
267 84835174 Iustin Pop
      instances = M.elems . fromContainer . configInstances $ cfg
268 84835174 Iustin Pop
      defparams = (M.!) (fromContainer $ clusterNicparams cluster) C.ppDefault
269 eaa64cd8 Iustin Pop
      nics = concatMap (\i -> [(instName i, nic) | nic <- instNics i])
270 eaa64cd8 Iustin Pop
             instances
271 eaa64cd8 Iustin Pop
  in foldl' (\accum (iname, nic) ->
272 eaa64cd8 Iustin Pop
               let pparams = nicNicparams nic
273 b09cce64 Iustin Pop
                   fparams = fillNicParams defparams pparams
274 eaa64cd8 Iustin Pop
                   link = nicpLink fparams
275 eaa64cd8 Iustin Pop
               in case nicIp nic of
276 eaa64cd8 Iustin Pop
                    Nothing -> accum
277 5b11f8db Iustin Pop
                    Just ip -> let oldipmap = M.findWithDefault M.empty
278 eaa64cd8 Iustin Pop
                                              link accum
279 eaa64cd8 Iustin Pop
                                   newipmap = M.insert ip iname oldipmap
280 eaa64cd8 Iustin Pop
                               in M.insert link newipmap accum
281 eaa64cd8 Iustin Pop
            ) M.empty nics
282 da45c352 Iustin Pop
283 da45c352 Iustin Pop
284 da45c352 Iustin Pop
-- | Returns a node's group, with optional failure if we can't find it
285 da45c352 Iustin Pop
-- (configuration corrupt).
286 da45c352 Iustin Pop
getGroupOfNode :: ConfigData -> Node -> Maybe NodeGroup
287 da45c352 Iustin Pop
getGroupOfNode cfg node =
288 da45c352 Iustin Pop
  M.lookup (nodeGroup node) (fromContainer . configNodegroups $ cfg)
289 da45c352 Iustin Pop
290 da45c352 Iustin Pop
-- | Returns a node's ndparams, filled.
291 da45c352 Iustin Pop
getNodeNdParams :: ConfigData -> Node -> Maybe FilledNDParams
292 da45c352 Iustin Pop
getNodeNdParams cfg node = do
293 da45c352 Iustin Pop
  group <- getGroupOfNode cfg node
294 da45c352 Iustin Pop
  let gparams = getGroupNdParams cfg group
295 da45c352 Iustin Pop
  return $ fillNDParams gparams (nodeNdparams node)
296 da45c352 Iustin Pop
297 da45c352 Iustin Pop
instance NdParamObject Node where
298 da45c352 Iustin Pop
  getNdParamsOf = getNodeNdParams
299 da45c352 Iustin Pop
300 da45c352 Iustin Pop
instance NdParamObject NodeGroup where
301 da45c352 Iustin Pop
  getNdParamsOf cfg = Just . getGroupNdParams cfg
302 da45c352 Iustin Pop
303 da45c352 Iustin Pop
instance NdParamObject Cluster where
304 da45c352 Iustin Pop
  getNdParamsOf _ = Just . clusterNdparams