Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Text.hs @ 000ca91a

History | View | Annotate | Download (13.3 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
  , 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
87
              if Node.isMaster node then 'M' else 'N')
88
           (Group.uuid grp)
89
           (Node.spindleCount node)
90
    where grp = Container.find (Node.group node) gl
91

    
92
-- | Generate node file data from node objects.
93
serializeNodes :: Group.List -> Node.List -> String
94
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
95

    
96
-- | Serialize a single instance.
97
serializeInstance :: Node.List         -- ^ The node list (needed for
98
                                       -- node names)
99
                  -> Instance.Instance -- ^ The instance to be serialised
100
                  -> String
101
serializeInstance nl inst =
102
  let iname = Instance.name inst
103
      pnode = Container.nameOf nl (Instance.pNode inst)
104
      sidx = Instance.sNode inst
105
      snode = (if sidx == Node.noSecondary
106
                 then ""
107
                 else Container.nameOf nl sidx)
108
  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d"
109
       iname (Instance.mem inst) (Instance.dsk inst)
110
       (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
111
       (if Instance.autoBalance inst then "Y" else "N")
112
       pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
113
       (intercalate "," (Instance.allTags inst)) (Instance.spindleUse inst)
114

    
115
-- | Generate instance file data from instance objects.
116
serializeInstances :: Node.List -> Instance.List -> String
117
serializeInstances nl =
118
  unlines . map (serializeInstance nl) . Container.elems
119

    
120
-- | Generate a spec data from a given ISpec object.
121
serializeISpec :: ISpec -> String
122
serializeISpec ispec =
123
  -- this needs to be kept in sync with the object definition
124
  let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec
125
      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c,
126
                 show su]
127
  in intercalate "," strings
128

    
129
-- | Generate disk template data.
130
serializeDiskTemplates :: [DiskTemplate] -> String
131
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
132

    
133
-- | Generate policy data from a given policy object.
134
serializeIPolicy :: String -> IPolicy -> String
135
serializeIPolicy owner ipol =
136
  let IPolicy minmax stdspec dts vcpu_ratio spindle_ratio = ipol
137
      MinMaxISpecs minspec maxspec = minmax
138
      strings = [ owner
139
                , serializeISpec stdspec
140
                , serializeISpec minspec
141
                , serializeISpec maxspec
142
                , serializeDiskTemplates dts
143
                , show vcpu_ratio
144
                , show spindle_ratio
145
                ]
146
  in intercalate "|" strings
147

    
148
-- | Generates the entire ipolicy section from the cluster and group
149
-- objects.
150
serializeAllIPolicies :: IPolicy -> Group.List -> String
151
serializeAllIPolicies cpol gl =
152
  let groups = Container.elems gl
153
      allpolicies = ("", cpol) :
154
                    map (\g -> (Group.name g, Group.iPolicy g)) groups
155
      strings = map (uncurry serializeIPolicy) allpolicies
156
  in unlines strings
157

    
158
-- | Generate complete cluster data from node and instance lists.
159
serializeCluster :: ClusterData -> String
160
serializeCluster (ClusterData gl nl il ctags cpol) =
161
  let gdata = serializeGroups gl
162
      ndata = serializeNodes gl nl
163
      idata = serializeInstances nl il
164
      pdata = serializeAllIPolicies cpol gl
165
  -- note: not using 'unlines' as that adds too many newlines
166
  in intercalate "\n" [gdata, ndata, idata, unlines ctags, pdata]
167

    
168
-- * Parsing functions
169

    
170
-- | Load a group from a field list.
171
loadGroup :: (Monad m) => [String]
172
          -> m (String, Group.Group) -- ^ The result, a tuple of group
173
                                     -- UUID and group object
174
loadGroup [name, gid, apol, tags] = do
175
  xapol <- allocPolicyFromRaw apol
176
  let xtags = commaSplit tags
177
  return (gid, Group.create name gid xapol defIPolicy xtags)
178

    
179
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
180

    
181
-- | Load a node from a field list.
182
loadNode :: (Monad m) =>
183
            NameAssoc             -- ^ Association list with current groups
184
         -> [String]              -- ^ Input data as a list of fields
185
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
186
                                  -- and node object
187
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] = do
188
  gdx <- lookupGroup ktg name gu
189
  new_node <-
190
      if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then
191
          return $ Node.create name 0 0 0 0 0 0 True 0 gdx
192
      else do
193
        vtm <- tryRead name tm
194
        vnm <- tryRead name nm
195
        vfm <- tryRead name fm
196
        vtd <- tryRead name td
197
        vfd <- tryRead name fd
198
        vtc <- tryRead name tc
199
        vspindles <- tryRead name spindles
200
        return . flip Node.setMaster (fo == "M") $
201
          Node.create name vtm vnm vfm vtd vfd vtc False vspindles gdx
202
  return (name, new_node)
203

    
204
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
205
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
206

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

    
209
-- | Load an instance from a field list.
210
loadInst :: NameAssoc -- ^ Association list with the current nodes
211
         -> [String]  -- ^ Input data as a list of fields
212
         -> Result (String, Instance.Instance) -- ^ A tuple of
213
                                               -- instance name and
214
                                               -- the instance object
215
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
216
             , dt, tags, su ] = do
217
  pidx <- lookupNode ktn name pnode
218
  sidx <- if null snode
219
            then return Node.noSecondary
220
            else lookupNode ktn name snode
221
  vmem <- tryRead name mem
222
  vdsk <- tryRead name dsk
223
  vvcpus <- tryRead name vcpus
224
  vstatus <- instanceStatusFromRaw status
225
  auto_balance <- case auto_bal of
226
                    "Y" -> return True
227
                    "N" -> return False
228
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
229
                         "' for instance " ++ name
230
  disk_template <- annotateResult ("Instance " ++ name)
231
                   (diskTemplateFromRaw dt)
232
  spindle_use <- tryRead name su
233
  when (sidx == pidx) . fail $ "Instance " ++ name ++
234
           " has same primary and secondary node - " ++ pnode
235
  let vtags = commaSplit tags
236
      newinst = Instance.create name vmem vdsk [vdsk] vvcpus vstatus vtags
237
                auto_balance pidx sidx disk_template spindle_use
238
  return (name, newinst)
239

    
240
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
241
             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
242
                                           auto_bal, pnode, snode, dt, tags,
243
                                           "1" ]
244
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
245

    
246
-- | Loads a spec from a field list.
247
loadISpec :: String -> [String] -> Result ISpec
248
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
249
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
250
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
251
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
252
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
253
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
254
  xsu    <- tryRead (owner ++ "/spindleuse") su
255
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
256
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
257

    
258
-- | Loads an ipolicy from a field list.
259
loadIPolicy :: [String] -> Result (String, IPolicy)
260
loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates,
261
             vcpu_ratio, spindle_ratio] = do
262
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
263
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
264
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
265
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
266
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
267
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
268
  return (owner,
269
          IPolicy (MinMaxISpecs xminspec xmaxspec) xstdspec
270
                xdts xvcpu_ratio xspindle_ratio)
271
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
272

    
273
loadOnePolicy :: (IPolicy, Group.List) -> String
274
              -> Result (IPolicy, Group.List)
275
loadOnePolicy (cpol, gl) line = do
276
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
277
  case owner of
278
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
279
    _ -> do
280
      grp <- Container.findByName gl owner
281
      let grp' = grp { Group.iPolicy = ipol }
282
          gl' = Container.add (Group.idx grp') grp' gl
283
      return (cpol, gl')
284

    
285
-- | Loads all policies from the policy section
286
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
287
loadAllIPolicies gl =
288
  foldM loadOnePolicy (defIPolicy, gl)
289

    
290
-- | Convert newline and delimiter-separated text.
291
--
292
-- This function converts a text in tabular format as generated by
293
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
294
-- a supplied conversion function.
295
loadTabular :: (Monad m, Element a) =>
296
               [String] -- ^ Input data, as a list of lines
297
            -> ([String] -> m (String, a)) -- ^ Conversion function
298
            -> m ( NameAssoc
299
                 , Container.Container a ) -- ^ A tuple of an
300
                                           -- association list (name
301
                                           -- to object) and a set as
302
                                           -- used in
303
                                           -- "Ganeti.HTools.Container"
304

    
305
loadTabular lines_data convert_fn = do
306
  let rows = map (sepSplit '|') lines_data
307
  kerows <- mapM convert_fn rows
308
  return $ assignIndices kerows
309

    
310
-- | Load the cluser data from disk.
311
--
312
-- This is an alias to 'readFile' just for consistency with the other
313
-- modules.
314
readData :: String    -- ^ Path to the text file
315
         -> IO String -- ^ Contents of the file
316
readData = readFile
317

    
318
-- | Builds the cluster data from text input.
319
parseData :: String -- ^ Text data
320
          -> Result ClusterData
321
parseData fdata = do
322
  let flines = lines fdata
323
  (glines, nlines, ilines, ctags, pollines) <-
324
      case sepSplit "" flines of
325
        [a, b, c, d, e] -> Ok (a, b, c, d, e)
326
        [a, b, c, d] -> Ok (a, b, c, d, [])
327
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
328
                           \ instead of 4 or 5" (length xs)
329
  {- group file: name uuid alloc_policy -}
330
  (ktg, gl) <- loadTabular glines loadGroup
331
  {- node file: name t_mem n_mem f_mem t_disk f_disk t_cpu offline grp_uuid
332
                spindles -}
333
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
334
  {- instance file: name mem disk vcpus status auto_bal pnode snode
335
                    disk_template tags spindle_use -}
336
  (_, il) <- loadTabular ilines (loadInst ktn)
337
  {- the tags are simply line-based, no processing needed -}
338
  {- process policies -}
339
  (cpol, gl') <- loadAllIPolicies gl pollines
340
  return (ClusterData gl' nl il ctags cpol)
341

    
342
-- | Top level function for data loading.
343
loadData :: String -- ^ Path to the text file
344
         -> IO (Result ClusterData)
345
loadData = fmap parseData . readData