Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (13.2 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 '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 minmax stdspec dts vcpu_ratio spindle_ratio = ipol
136
      MinMaxISpecs minspec maxspec = minmax
137
      strings = [ owner
138
                , serializeISpec stdspec
139
                , serializeISpec minspec
140
                , serializeISpec maxspec
141
                , serializeDiskTemplates dts
142
                , show vcpu_ratio
143
                , show spindle_ratio
144
                ]
145
  in intercalate "|" strings
146

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

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

    
167
-- * Parsing functions
168

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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