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