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