Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Text.hs @ c324da14

History | View | Annotate | Download (15.6 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"
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

    
121
-- | Generate instance file data from instance objects.
122
serializeInstances :: Node.List -> Instance.List -> String
123
serializeInstances nl =
124
  unlines . map (serializeInstance nl) . Container.elems
125

    
126
-- | Separator between ISpecs (in MinMaxISpecs).
127
iSpecsSeparator :: Char
128
iSpecsSeparator = ';'
129

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

    
139
-- | Generate disk template data.
140
serializeDiskTemplates :: [DiskTemplate] -> String
141
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
142

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

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

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

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

    
183
-- * Parsing functions
184

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

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

    
229
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
230
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
231

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

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

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

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

    
271
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
272
             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
273
                                           auto_bal, pnode, snode, dt, tags,
274
                                           "1" ]
275
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
276

    
277
-- | Loads a spec from a field list.
278
loadISpec :: String -> [String] -> Result ISpec
279
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
280
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
281
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
282
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
283
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
284
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
285
  xsu    <- tryRead (owner ++ "/spindleuse") su
286
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
287
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
288

    
289
-- | Load a single min/max ISpec pair
290
loadMinMaxISpecs :: String -> String -> String -> Result MinMaxISpecs
291
loadMinMaxISpecs owner minspec maxspec = do
292
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
293
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
294
  return $ MinMaxISpecs xminspec xmaxspec
295

    
296
-- | Break a list of ispecs strings into a list of (min/max) ispecs pairs
297
breakISpecsPairs :: String -> [String] -> Result [(String, String)]
298
breakISpecsPairs _ [] =
299
  return []
300
breakISpecsPairs owner (x:y:xs) = do
301
  rest <- breakISpecsPairs owner xs
302
  return $ (x, y) : rest
303
breakISpecsPairs owner _ =
304
  fail $ "Odd number of min/max specs for " ++ owner
305

    
306
-- | Load a list of min/max ispecs pairs
307
loadMultipleMinMaxISpecs :: String -> [String] -> Result [MinMaxISpecs]
308
loadMultipleMinMaxISpecs owner ispecs = do
309
  pairs <- breakISpecsPairs owner ispecs
310
  mapM (uncurry $ loadMinMaxISpecs owner) pairs
311

    
312
-- | Loads an ipolicy from a field list.
313
loadIPolicy :: [String] -> Result (String, IPolicy)
314
loadIPolicy [owner, stdspec, minmaxspecs, dtemplates,
315
             vcpu_ratio, spindle_ratio] = do
316
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
317
  xminmaxspecs <- loadMultipleMinMaxISpecs owner $
318
                  sepSplit iSpecsSeparator minmaxspecs
319
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
320
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
321
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
322
  return (owner,
323
          IPolicy xminmaxspecs xstdspec
324
                xdts xvcpu_ratio xspindle_ratio)
325
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
326

    
327
loadOnePolicy :: (IPolicy, Group.List) -> String
328
              -> Result (IPolicy, Group.List)
329
loadOnePolicy (cpol, gl) line = do
330
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
331
  case owner of
332
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
333
    _ -> do
334
      grp <- Container.findByName gl owner
335
      let grp' = grp { Group.iPolicy = ipol }
336
          gl' = Container.add (Group.idx grp') grp' gl
337
      return (cpol, gl')
338

    
339
-- | Loads all policies from the policy section
340
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
341
loadAllIPolicies gl =
342
  foldM loadOnePolicy (defIPolicy, gl)
343

    
344
-- | Convert newline and delimiter-separated text.
345
--
346
-- This function converts a text in tabular format as generated by
347
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
348
-- a supplied conversion function.
349
loadTabular :: (Monad m, Element a) =>
350
               [String] -- ^ Input data, as a list of lines
351
            -> ([String] -> m (String, a)) -- ^ Conversion function
352
            -> m ( NameAssoc
353
                 , Container.Container a ) -- ^ A tuple of an
354
                                           -- association list (name
355
                                           -- to object) and a set as
356
                                           -- used in
357
                                           -- "Ganeti.HTools.Container"
358

    
359
loadTabular lines_data convert_fn = do
360
  let rows = map (sepSplit '|') lines_data
361
  kerows <- mapM convert_fn rows
362
  return $ assignIndices kerows
363

    
364
-- | Load the cluser data from disk.
365
--
366
-- This is an alias to 'readFile' just for consistency with the other
367
-- modules.
368
readData :: String    -- ^ Path to the text file
369
         -> IO String -- ^ Contents of the file
370
readData = readFile
371

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

    
396
-- | Top level function for data loading.
397
loadData :: String -- ^ Path to the text file
398
         -> IO (Result ClusterData)
399
loadData = fmap parseData . readData