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