Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Config.hs @ ecebe9f6

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