root / htools / Ganeti / HTools / Backend / Text.hs @ 29a30533
History | View | Annotate | Download (13.1 kB)
1 |
{-| Parsing data from text-files. |
---|---|
2 |
|
3 |
This module holds the code for loading the cluster state from text |
4 |
files, as produced by @gnt-node@ and @gnt-instance@ @list@ command. |
5 |
|
6 |
-} |
7 |
|
8 |
{- |
9 |
|
10 |
Copyright (C) 2009, 2010, 2011, 2012 Google Inc. |
11 |
|
12 |
This program is free software; you can redistribute it and/or modify |
13 |
it under the terms of the GNU General Public License as published by |
14 |
the Free Software Foundation; either version 2 of the License, or |
15 |
(at your option) any later version. |
16 |
|
17 |
This program is distributed in the hope that it will be useful, but |
18 |
WITHOUT ANY WARRANTY; without even the implied warranty of |
19 |
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
20 |
General Public License for more details. |
21 |
|
22 |
You should have received a copy of the GNU General Public License |
23 |
along with this program; if not, write to the Free Software |
24 |
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
25 |
02110-1301, USA. |
26 |
|
27 |
-} |
28 |
|
29 |
module Ganeti.HTools.Backend.Text |
30 |
( loadData |
31 |
, parseData |
32 |
, loadInst |
33 |
, loadNode |
34 |
, loadISpec |
35 |
, loadIPolicy |
36 |
, serializeInstances |
37 |
, serializeNode |
38 |
, serializeNodes |
39 |
, serializeGroup |
40 |
, serializeISpec |
41 |
, serializeIPolicy |
42 |
, serializeCluster |
43 |
) where |
44 |
|
45 |
import Control.Monad |
46 |
import Data.List |
47 |
|
48 |
import Text.Printf (printf) |
49 |
|
50 |
import Ganeti.BasicTypes |
51 |
import Ganeti.Utils |
52 |
import Ganeti.HTools.Loader |
53 |
import Ganeti.HTools.Types |
54 |
import qualified Ganeti.HTools.Container as Container |
55 |
import qualified Ganeti.HTools.Group as Group |
56 |
import qualified Ganeti.HTools.Node as Node |
57 |
import qualified Ganeti.HTools.Instance as Instance |
58 |
|
59 |
-- * Helper functions |
60 |
|
61 |
-- | Simple wrapper over sepSplit |
62 |
commaSplit :: String -> [String] |
63 |
commaSplit = sepSplit ',' |
64 |
|
65 |
-- * Serialisation functions |
66 |
|
67 |
-- | Serialize a single group. |
68 |
serializeGroup :: Group.Group -> String |
69 |
serializeGroup grp = |
70 |
printf "%s|%s|%s|%s" (Group.name grp) (Group.uuid grp) |
71 |
(allocPolicyToRaw (Group.allocPolicy grp)) |
72 |
(intercalate "," (Group.allTags grp)) |
73 |
|
74 |
-- | Generate group file data from a group list. |
75 |
serializeGroups :: Group.List -> String |
76 |
serializeGroups = unlines . map serializeGroup . Container.elems |
77 |
|
78 |
-- | Serialize a single node. |
79 |
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid) |
80 |
-> Node.Node -- ^ The node to be serialised |
81 |
-> String |
82 |
serializeNode gl node = |
83 |
printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d" (Node.name node) |
84 |
(Node.tMem node) (Node.nMem node) (Node.fMem node) |
85 |
(Node.tDsk node) (Node.fDsk node) (Node.tCpu node) |
86 |
(if Node.offline node then 'Y' else 'N') |
87 |
(Group.uuid grp) |
88 |
(Node.spindleCount node) |
89 |
where grp = Container.find (Node.group node) gl |
90 |
|
91 |
-- | Generate node file data from node objects. |
92 |
serializeNodes :: Group.List -> Node.List -> String |
93 |
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems |
94 |
|
95 |
-- | Serialize a single instance. |
96 |
serializeInstance :: Node.List -- ^ The node list (needed for |
97 |
-- node names) |
98 |
-> Instance.Instance -- ^ The instance to be serialised |
99 |
-> String |
100 |
serializeInstance nl inst = |
101 |
let iname = Instance.name inst |
102 |
pnode = Container.nameOf nl (Instance.pNode inst) |
103 |
sidx = Instance.sNode inst |
104 |
snode = (if sidx == Node.noSecondary |
105 |
then "" |
106 |
else Container.nameOf nl sidx) |
107 |
in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d" |
108 |
iname (Instance.mem inst) (Instance.dsk inst) |
109 |
(Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst)) |
110 |
(if Instance.autoBalance inst then "Y" else "N") |
111 |
pnode snode (diskTemplateToRaw (Instance.diskTemplate inst)) |
112 |
(intercalate "," (Instance.allTags inst)) (Instance.spindleUse inst) |
113 |
|
114 |
-- | Generate instance file data from instance objects. |
115 |
serializeInstances :: Node.List -> Instance.List -> String |
116 |
serializeInstances nl = |
117 |
unlines . map (serializeInstance nl) . Container.elems |
118 |
|
119 |
-- | Generate a spec data from a given ISpec object. |
120 |
serializeISpec :: ISpec -> String |
121 |
serializeISpec ispec = |
122 |
-- this needs to be kept in sync with the object definition |
123 |
let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec |
124 |
strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c, |
125 |
show su] |
126 |
in intercalate "," strings |
127 |
|
128 |
-- | Generate disk template data. |
129 |
serializeDiskTemplates :: [DiskTemplate] -> String |
130 |
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw |
131 |
|
132 |
-- | Generate policy data from a given policy object. |
133 |
serializeIPolicy :: String -> IPolicy -> String |
134 |
serializeIPolicy owner ipol = |
135 |
let IPolicy stdspec minspec maxspec dts vcpu_ratio spindle_ratio = ipol |
136 |
strings = [ owner |
137 |
, serializeISpec stdspec |
138 |
, serializeISpec minspec |
139 |
, serializeISpec maxspec |
140 |
, serializeDiskTemplates dts |
141 |
, show vcpu_ratio |
142 |
, show spindle_ratio |
143 |
] |
144 |
in intercalate "|" strings |
145 |
|
146 |
-- | Generates the entire ipolicy section from the cluster and group |
147 |
-- objects. |
148 |
serializeAllIPolicies :: IPolicy -> Group.List -> String |
149 |
serializeAllIPolicies cpol gl = |
150 |
let groups = Container.elems gl |
151 |
allpolicies = ("", cpol) : |
152 |
map (\g -> (Group.name g, Group.iPolicy g)) groups |
153 |
strings = map (uncurry serializeIPolicy) allpolicies |
154 |
in unlines strings |
155 |
|
156 |
-- | Generate complete cluster data from node and instance lists. |
157 |
serializeCluster :: ClusterData -> String |
158 |
serializeCluster (ClusterData gl nl il ctags cpol) = |
159 |
let gdata = serializeGroups gl |
160 |
ndata = serializeNodes gl nl |
161 |
idata = serializeInstances nl il |
162 |
pdata = serializeAllIPolicies cpol gl |
163 |
-- note: not using 'unlines' as that adds too many newlines |
164 |
in intercalate "\n" [gdata, ndata, idata, unlines ctags, pdata] |
165 |
|
166 |
-- * Parsing functions |
167 |
|
168 |
-- | Load a group from a field list. |
169 |
loadGroup :: (Monad m) => [String] |
170 |
-> m (String, Group.Group) -- ^ The result, a tuple of group |
171 |
-- UUID and group object |
172 |
loadGroup [name, gid, apol, tags] = do |
173 |
xapol <- allocPolicyFromRaw apol |
174 |
let xtags = commaSplit tags |
175 |
return (gid, Group.create name gid xapol defIPolicy xtags) |
176 |
|
177 |
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'" |
178 |
|
179 |
-- | Load a node from a field list. |
180 |
loadNode :: (Monad m) => |
181 |
NameAssoc -- ^ Association list with current groups |
182 |
-> [String] -- ^ Input data as a list of fields |
183 |
-> m (String, Node.Node) -- ^ The result, a tuple o node name |
184 |
-- and node object |
185 |
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] = do |
186 |
gdx <- lookupGroup ktg name gu |
187 |
new_node <- |
188 |
if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then |
189 |
return $ Node.create name 0 0 0 0 0 0 True 0 gdx |
190 |
else do |
191 |
vtm <- tryRead name tm |
192 |
vnm <- tryRead name nm |
193 |
vfm <- tryRead name fm |
194 |
vtd <- tryRead name td |
195 |
vfd <- tryRead name fd |
196 |
vtc <- tryRead name tc |
197 |
vspindles <- tryRead name spindles |
198 |
return $ Node.create name vtm vnm vfm vtd vfd vtc False vspindles gdx |
199 |
return (name, new_node) |
200 |
|
201 |
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = |
202 |
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"] |
203 |
|
204 |
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'" |
205 |
|
206 |
-- | Load an instance from a field list. |
207 |
loadInst :: NameAssoc -- ^ Association list with the current nodes |
208 |
-> [String] -- ^ Input data as a list of fields |
209 |
-> Result (String, Instance.Instance) -- ^ A tuple of |
210 |
-- instance name and |
211 |
-- the instance object |
212 |
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode |
213 |
, dt, tags, su ] = do |
214 |
pidx <- lookupNode ktn name pnode |
215 |
sidx <- if null snode |
216 |
then return Node.noSecondary |
217 |
else lookupNode ktn name snode |
218 |
vmem <- tryRead name mem |
219 |
vdsk <- tryRead name dsk |
220 |
vvcpus <- tryRead name vcpus |
221 |
vstatus <- instanceStatusFromRaw status |
222 |
auto_balance <- case auto_bal of |
223 |
"Y" -> return True |
224 |
"N" -> return False |
225 |
_ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++ |
226 |
"' for instance " ++ name |
227 |
disk_template <- annotateResult ("Instance " ++ name) |
228 |
(diskTemplateFromRaw dt) |
229 |
spindle_use <- tryRead name su |
230 |
when (sidx == pidx) . fail $ "Instance " ++ name ++ |
231 |
" has same primary and secondary node - " ++ pnode |
232 |
let vtags = commaSplit tags |
233 |
newinst = Instance.create name vmem vdsk vvcpus vstatus vtags |
234 |
auto_balance pidx sidx disk_template spindle_use |
235 |
return (name, newinst) |
236 |
|
237 |
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode |
238 |
, dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status, |
239 |
auto_bal, pnode, snode, dt, tags, |
240 |
"1" ] |
241 |
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'" |
242 |
|
243 |
-- | Loads a spec from a field list. |
244 |
loadISpec :: String -> [String] -> Result ISpec |
245 |
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do |
246 |
xmem_s <- tryRead (owner ++ "/memsize") mem_s |
247 |
xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c |
248 |
xdsk_s <- tryRead (owner ++ "/disksize") dsk_s |
249 |
xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c |
250 |
xnic_c <- tryRead (owner ++ "/niccount") nic_c |
251 |
xsu <- tryRead (owner ++ "/spindleuse") su |
252 |
return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu |
253 |
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s |
254 |
|
255 |
-- | Loads an ipolicy from a field list. |
256 |
loadIPolicy :: [String] -> Result (String, IPolicy) |
257 |
loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates, |
258 |
vcpu_ratio, spindle_ratio] = do |
259 |
xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec) |
260 |
xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec) |
261 |
xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec) |
262 |
xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates |
263 |
xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio |
264 |
xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio |
265 |
return (owner, |
266 |
IPolicy xstdspec xminspec xmaxspec xdts xvcpu_ratio xspindle_ratio) |
267 |
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'" |
268 |
|
269 |
loadOnePolicy :: (IPolicy, Group.List) -> String |
270 |
-> Result (IPolicy, Group.List) |
271 |
loadOnePolicy (cpol, gl) line = do |
272 |
(owner, ipol) <- loadIPolicy (sepSplit '|' line) |
273 |
case owner of |
274 |
"" -> return (ipol, gl) -- this is a cluster policy (no owner) |
275 |
_ -> do |
276 |
grp <- Container.findByName gl owner |
277 |
let grp' = grp { Group.iPolicy = ipol } |
278 |
gl' = Container.add (Group.idx grp') grp' gl |
279 |
return (cpol, gl') |
280 |
|
281 |
-- | Loads all policies from the policy section |
282 |
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List) |
283 |
loadAllIPolicies gl = |
284 |
foldM loadOnePolicy (defIPolicy, gl) |
285 |
|
286 |
-- | Convert newline and delimiter-separated text. |
287 |
-- |
288 |
-- This function converts a text in tabular format as generated by |
289 |
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using |
290 |
-- a supplied conversion function. |
291 |
loadTabular :: (Monad m, Element a) => |
292 |
[String] -- ^ Input data, as a list of lines |
293 |
-> ([String] -> m (String, a)) -- ^ Conversion function |
294 |
-> m ( NameAssoc |
295 |
, Container.Container a ) -- ^ A tuple of an |
296 |
-- association list (name |
297 |
-- to object) and a set as |
298 |
-- used in |
299 |
-- "Ganeti.HTools.Container" |
300 |
|
301 |
loadTabular lines_data convert_fn = do |
302 |
let rows = map (sepSplit '|') lines_data |
303 |
kerows <- mapM convert_fn rows |
304 |
return $ assignIndices kerows |
305 |
|
306 |
-- | Load the cluser data from disk. |
307 |
-- |
308 |
-- This is an alias to 'readFile' just for consistency with the other |
309 |
-- modules. |
310 |
readData :: String -- ^ Path to the text file |
311 |
-> IO String -- ^ Contents of the file |
312 |
readData = readFile |
313 |
|
314 |
-- | Builds the cluster data from text input. |
315 |
parseData :: String -- ^ Text data |
316 |
-> Result ClusterData |
317 |
parseData fdata = do |
318 |
let flines = lines fdata |
319 |
(glines, nlines, ilines, ctags, pollines) <- |
320 |
case sepSplit "" flines of |
321 |
[a, b, c, d, e] -> Ok (a, b, c, d, e) |
322 |
[a, b, c, d] -> Ok (a, b, c, d, []) |
323 |
xs -> Bad $ printf "Invalid format of the input file: %d sections\ |
324 |
\ instead of 4 or 5" (length xs) |
325 |
{- group file: name uuid alloc_policy -} |
326 |
(ktg, gl) <- loadTabular glines loadGroup |
327 |
{- node file: name t_mem n_mem f_mem t_disk f_disk t_cpu offline grp_uuid |
328 |
spindles -} |
329 |
(ktn, nl) <- loadTabular nlines (loadNode ktg) |
330 |
{- instance file: name mem disk vcpus status auto_bal pnode snode |
331 |
disk_template tags spindle_use -} |
332 |
(_, il) <- loadTabular ilines (loadInst ktn) |
333 |
{- the tags are simply line-based, no processing needed -} |
334 |
{- process policies -} |
335 |
(cpol, gl') <- loadAllIPolicies gl pollines |
336 |
return (ClusterData gl' nl il ctags cpol) |
337 |
|
338 |
-- | Top level function for data loading. |
339 |
loadData :: String -- ^ Path to the text file |
340 |
-> IO (Result ClusterData) |
341 |
loadData = fmap parseData . readData |