Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Text.hs @ 2724417c

History | View | Annotate | Download (16.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, 2013 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
  , loadMultipleMinMaxISpecs
36
  , loadIPolicy
37
  , serializeInstance
38
  , serializeInstances
39
  , serializeNode
40
  , serializeNodes
41
  , serializeGroup
42
  , serializeISpec
43
  , serializeMultipleMinMaxISpecs
44
  , serializeIPolicy
45
  , serializeCluster
46
  ) where
47

    
48
import Control.Monad
49
import Data.List
50

    
51
import Text.Printf (printf)
52

    
53
import Ganeti.BasicTypes
54
import Ganeti.Utils
55
import Ganeti.HTools.Loader
56
import Ganeti.HTools.Types
57
import qualified Ganeti.HTools.Container as Container
58
import qualified Ganeti.HTools.Group as Group
59
import qualified Ganeti.HTools.Node as Node
60
import qualified Ganeti.HTools.Instance as Instance
61

    
62
-- * Helper functions
63

    
64
-- | Simple wrapper over sepSplit
65
commaSplit :: String -> [String]
66
commaSplit = sepSplit ','
67

    
68
-- * Serialisation functions
69

    
70
-- | Serialize a single group.
71
serializeGroup :: Group.Group -> String
72
serializeGroup grp =
73
  printf "%s|%s|%s|%s|%s" (Group.name grp) (Group.uuid grp)
74
           (allocPolicyToRaw (Group.allocPolicy grp))
75
           (intercalate "," (Group.allTags grp))
76
           (intercalate "," (Group.networks grp))
77

    
78
-- | Generate group file data from a group list.
79
serializeGroups :: Group.List -> String
80
serializeGroups = unlines . map serializeGroup . Container.elems
81

    
82
-- | Serialize a single node.
83
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
84
              -> Node.Node  -- ^ The node to be serialised
85
              -> String
86
serializeNode gl node =
87
  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d|%s|%s" (Node.name node)
88
           (Node.tMem node) (Node.nMem node) (Node.fMem node)
89
           (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
90
           (if Node.offline node then 'Y' else
91
              if Node.isMaster node then 'M' else 'N')
92
           (Group.uuid grp)
93
           (Node.spindleCount node)
94
           (intercalate "," (Node.nTags node))
95
           (if Node.exclStorage node then "Y" else "N")
96
    where grp = Container.find (Node.group node) gl
97

    
98
-- | Generate node file data from node objects.
99
serializeNodes :: Group.List -> Node.List -> String
100
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
101

    
102
-- | Serialize a single instance.
103
serializeInstance :: Node.List         -- ^ The node list (needed for
104
                                       -- node names)
105
                  -> Instance.Instance -- ^ The instance to be serialised
106
                  -> String
107
serializeInstance nl inst =
108
  let iname = Instance.name inst
109
      pnode = Container.nameOf nl (Instance.pNode inst)
110
      sidx = Instance.sNode inst
111
      snode = (if sidx == Node.noSecondary
112
                 then ""
113
                 else Container.nameOf nl sidx)
114
  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d|%s"
115
       iname (Instance.mem inst) (Instance.dsk inst)
116
       (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
117
       (if Instance.autoBalance inst then "Y" else "N")
118
       pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
119
       (intercalate "," (Instance.allTags inst)) (Instance.spindleUse inst)
120
       -- disk spindles are summed together, as it's done for disk size
121
       (case Instance.getTotalSpindles inst of
122
          Nothing -> "-"
123
          Just x -> show x)
124

    
125
-- | Generate instance file data from instance objects.
126
serializeInstances :: Node.List -> Instance.List -> String
127
serializeInstances nl =
128
  unlines . map (serializeInstance nl) . Container.elems
129

    
130
-- | Separator between ISpecs (in MinMaxISpecs).
131
iSpecsSeparator :: Char
132
iSpecsSeparator = ';'
133

    
134
-- | Generate a spec data from a given ISpec object.
135
serializeISpec :: ISpec -> String
136
serializeISpec ispec =
137
  -- this needs to be kept in sync with the object definition
138
  let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec
139
      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c,
140
                 show su]
141
  in intercalate "," strings
142

    
143
-- | Generate disk template data.
144
serializeDiskTemplates :: [DiskTemplate] -> String
145
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
146

    
147
-- | Generate min/max instance specs data.
148
serializeMultipleMinMaxISpecs :: [MinMaxISpecs] -> String
149
serializeMultipleMinMaxISpecs minmaxes =
150
  intercalate [iSpecsSeparator] $ foldr serialpair [] minmaxes
151
  where serialpair (MinMaxISpecs minspec maxspec) acc =
152
          serializeISpec minspec : serializeISpec maxspec : acc
153

    
154
-- | Generate policy data from a given policy object.
155
serializeIPolicy :: String -> IPolicy -> String
156
serializeIPolicy owner ipol =
157
  let IPolicy minmax stdspec dts vcpu_ratio spindle_ratio = ipol
158
      strings = [ owner
159
                , serializeISpec stdspec
160
                , serializeMultipleMinMaxISpecs minmax
161
                , serializeDiskTemplates dts
162
                , show vcpu_ratio
163
                , show spindle_ratio
164
                ]
165
  in intercalate "|" strings
166

    
167
-- | Generates the entire ipolicy section from the cluster and group
168
-- objects.
169
serializeAllIPolicies :: IPolicy -> Group.List -> String
170
serializeAllIPolicies cpol gl =
171
  let groups = Container.elems gl
172
      allpolicies = ("", cpol) :
173
                    map (\g -> (Group.name g, Group.iPolicy g)) groups
174
      strings = map (uncurry serializeIPolicy) allpolicies
175
  in unlines strings
176

    
177
-- | Generate complete cluster data from node and instance lists.
178
serializeCluster :: ClusterData -> String
179
serializeCluster (ClusterData gl nl il ctags cpol) =
180
  let gdata = serializeGroups gl
181
      ndata = serializeNodes gl nl
182
      idata = serializeInstances nl il
183
      pdata = serializeAllIPolicies cpol gl
184
  -- note: not using 'unlines' as that adds too many newlines
185
  in intercalate "\n" [gdata, ndata, idata, unlines ctags, pdata]
186

    
187
-- * Parsing functions
188

    
189
-- | Load a group from a field list.
190
loadGroup :: (Monad m) => [String]
191
          -> m (String, Group.Group) -- ^ The result, a tuple of group
192
                                     -- UUID and group object
193
loadGroup [name, gid, apol, tags, nets] = do
194
  xapol <- allocPolicyFromRaw apol
195
  let xtags = commaSplit tags
196
  let xnets = commaSplit nets
197
  return (gid, Group.create name gid xapol xnets defIPolicy xtags)
198
loadGroup [name, gid, apol, tags] = loadGroup [name, gid, apol, tags, ""]
199
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
200

    
201
-- | Load a node from a field list.
202
loadNode :: (Monad m) =>
203
            NameAssoc             -- ^ Association list with current groups
204
         -> [String]              -- ^ Input data as a list of fields
205
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
206
                                  -- and node object
207
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
208
              excl_stor] = do
209
  gdx <- lookupGroup ktg name gu
210
  new_node <-
211
      if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then
212
          return $ Node.create name 0 0 0 0 0 0 True 0 gdx False
213
      else do
214
        let vtags = commaSplit tags
215
        vtm <- tryRead name tm
216
        vnm <- tryRead name nm
217
        vfm <- tryRead name fm
218
        vtd <- tryRead name td
219
        vfd <- tryRead name fd
220
        vtc <- tryRead name tc
221
        vspindles <- tryRead name spindles
222
        vexcl_stor <- case excl_stor of
223
                        "Y" -> return True
224
                        "N" -> return False
225
                        _ -> fail $
226
                             "Invalid exclusive_storage value for node '" ++
227
                             name ++ "': " ++ excl_stor
228
        return . flip Node.setMaster (fo == "M") . flip Node.setNodeTags vtags $
229
          Node.create name vtm vnm vfm vtd vfd vtc False vspindles gdx
230
          vexcl_stor
231
  return (name, new_node)
232

    
233
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
234
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
235

    
236
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] =
237
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, ""]
238

    
239
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags] =
240
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags, "N"]
241

    
242
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
243

    
244
-- | Load an instance from a field list.
245
loadInst :: NameAssoc -- ^ Association list with the current nodes
246
         -> [String]  -- ^ Input data as a list of fields
247
         -> Result (String, Instance.Instance) -- ^ A tuple of
248
                                               -- instance name and
249
                                               -- the instance object
250
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
251
             , dt, tags, su, spindles ] = do
252
  pidx <- lookupNode ktn name pnode
253
  sidx <- if null snode
254
            then return Node.noSecondary
255
            else lookupNode ktn name snode
256
  vmem <- tryRead name mem
257
  dsize <- tryRead name dsk
258
  vvcpus <- tryRead name vcpus
259
  vstatus <- instanceStatusFromRaw status
260
  auto_balance <- case auto_bal of
261
                    "Y" -> return True
262
                    "N" -> return False
263
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
264
                         "' for instance " ++ name
265
  disk_template <- annotateResult ("Instance " ++ name)
266
                   (diskTemplateFromRaw dt)
267
  spindle_use <- tryRead name su
268
  vspindles <- case spindles of
269
                 "-" -> return Nothing
270
                 _ -> liftM Just (tryRead name spindles)
271
  let disk = Instance.Disk dsize vspindles
272
  let vtags = commaSplit tags
273
      newinst = Instance.create name vmem dsize [disk] vvcpus vstatus vtags
274
                auto_balance pidx sidx disk_template spindle_use []
275
  when (Instance.hasSecondary newinst && sidx == pidx) . fail $
276
    "Instance " ++ name ++ " has same primary and secondary node - " ++ pnode
277
  return (name, newinst)
278

    
279
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
280
             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
281
                                           auto_bal, pnode, snode, dt, tags,
282
                                           "1" ]
283

    
284
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
285
             , dt, tags, su ] =
286
  loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode, dt
287
               , tags, su, "-" ]
288

    
289
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
290

    
291
-- | Loads a spec from a field list.
292
loadISpec :: String -> [String] -> Result ISpec
293
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
294
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
295
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
296
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
297
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
298
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
299
  xsu    <- tryRead (owner ++ "/spindleuse") su
300
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
301
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
302

    
303
-- | Load a single min/max ISpec pair
304
loadMinMaxISpecs :: String -> String -> String -> Result MinMaxISpecs
305
loadMinMaxISpecs owner minspec maxspec = do
306
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
307
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
308
  return $ MinMaxISpecs xminspec xmaxspec
309

    
310
-- | Break a list of ispecs strings into a list of (min/max) ispecs pairs
311
breakISpecsPairs :: String -> [String] -> Result [(String, String)]
312
breakISpecsPairs _ [] =
313
  return []
314
breakISpecsPairs owner (x:y:xs) = do
315
  rest <- breakISpecsPairs owner xs
316
  return $ (x, y) : rest
317
breakISpecsPairs owner _ =
318
  fail $ "Odd number of min/max specs for " ++ owner
319

    
320
-- | Load a list of min/max ispecs pairs
321
loadMultipleMinMaxISpecs :: String -> [String] -> Result [MinMaxISpecs]
322
loadMultipleMinMaxISpecs owner ispecs = do
323
  pairs <- breakISpecsPairs owner ispecs
324
  mapM (uncurry $ loadMinMaxISpecs owner) pairs
325

    
326
-- | Loads an ipolicy from a field list.
327
loadIPolicy :: [String] -> Result (String, IPolicy)
328
loadIPolicy [owner, stdspec, minmaxspecs, dtemplates,
329
             vcpu_ratio, spindle_ratio] = do
330
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
331
  xminmaxspecs <- loadMultipleMinMaxISpecs owner $
332
                  sepSplit iSpecsSeparator minmaxspecs
333
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
334
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
335
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
336
  return (owner,
337
          IPolicy xminmaxspecs xstdspec
338
                xdts xvcpu_ratio xspindle_ratio)
339
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
340

    
341
loadOnePolicy :: (IPolicy, Group.List) -> String
342
              -> Result (IPolicy, Group.List)
343
loadOnePolicy (cpol, gl) line = do
344
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
345
  case owner of
346
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
347
    _ -> do
348
      grp <- Container.findByName gl owner
349
      let grp' = grp { Group.iPolicy = ipol }
350
          gl' = Container.add (Group.idx grp') grp' gl
351
      return (cpol, gl')
352

    
353
-- | Loads all policies from the policy section
354
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
355
loadAllIPolicies gl =
356
  foldM loadOnePolicy (defIPolicy, gl)
357

    
358
-- | Convert newline and delimiter-separated text.
359
--
360
-- This function converts a text in tabular format as generated by
361
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
362
-- a supplied conversion function.
363
loadTabular :: (Monad m, Element a) =>
364
               [String] -- ^ Input data, as a list of lines
365
            -> ([String] -> m (String, a)) -- ^ Conversion function
366
            -> m ( NameAssoc
367
                 , Container.Container a ) -- ^ A tuple of an
368
                                           -- association list (name
369
                                           -- to object) and a set as
370
                                           -- used in
371
                                           -- "Ganeti.HTools.Container"
372

    
373
loadTabular lines_data convert_fn = do
374
  let rows = map (sepSplit '|') lines_data
375
  kerows <- mapM convert_fn rows
376
  return $ assignIndices kerows
377

    
378
-- | Load the cluser data from disk.
379
--
380
-- This is an alias to 'readFile' just for consistency with the other
381
-- modules.
382
readData :: String    -- ^ Path to the text file
383
         -> IO String -- ^ Contents of the file
384
readData = readFile
385

    
386
-- | Builds the cluster data from text input.
387
parseData :: String -- ^ Text data
388
          -> Result ClusterData
389
parseData fdata = do
390
  let flines = lines fdata
391
  (glines, nlines, ilines, ctags, pollines) <-
392
      case sepSplit "" flines of
393
        [a, b, c, d, e] -> Ok (a, b, c, d, e)
394
        [a, b, c, d] -> Ok (a, b, c, d, [])
395
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
396
                           \ instead of 4 or 5" (length xs)
397
  {- group file: name uuid alloc_policy -}
398
  (ktg, gl) <- loadTabular glines loadGroup
399
  {- node file: name t_mem n_mem f_mem t_disk f_disk t_cpu offline grp_uuid
400
                spindles tags -}
401
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
402
  {- instance file: name mem disk vcpus status auto_bal pnode snode
403
                    disk_template tags spindle_use -}
404
  (_, il) <- loadTabular ilines (loadInst ktn)
405
  {- the tags are simply line-based, no processing needed -}
406
  {- process policies -}
407
  (cpol, gl') <- loadAllIPolicies gl pollines
408
  return (ClusterData gl' nl il ctags cpol)
409

    
410
-- | Top level function for data loading.
411
loadData :: String -- ^ Path to the text file
412
         -> IO (Result ClusterData)
413
loadData = fmap parseData . readData