Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Text.hs @ 6b6e335b

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.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.HTools.Utils
51
import Ganeti.HTools.Loader
52
import Ganeti.HTools.Types
53
import qualified Ganeti.HTools.Container as Container
54
import qualified Ganeti.HTools.Group as Group
55
import qualified Ganeti.HTools.Node as Node
56
import qualified Ganeti.HTools.Instance as Instance
57

    
58
-- * Helper functions
59

    
60
-- | Simple wrapper over sepSplit
61
commaSplit :: String -> [String]
62
commaSplit = sepSplit ','
63

    
64
-- * Serialisation functions
65

    
66
-- | Serialize a single group.
67
serializeGroup :: Group.Group -> String
68
serializeGroup grp =
69
  printf "%s|%s|%s|%s" (Group.name grp) (Group.uuid grp)
70
           (allocPolicyToRaw (Group.allocPolicy grp))
71
           (intercalate "," (Group.allTags grp))
72

    
73
-- | Generate group file data from a group list.
74
serializeGroups :: Group.List -> String
75
serializeGroups = unlines . map serializeGroup . Container.elems
76

    
77
-- | Serialize a single node.
78
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
79
              -> Node.Node  -- ^ The node to be serialised
80
              -> String
81
serializeNode gl node =
82
  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d" (Node.name node)
83
           (Node.tMem node) (Node.nMem node) (Node.fMem node)
84
           (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
85
           (if Node.offline node then 'Y' else 'N')
86
           (Group.uuid grp)
87
           (Node.spindleCount node)
88
    where grp = Container.find (Node.group node) gl
89

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

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

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

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

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

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

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

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

    
165
-- * Parsing functions
166

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

    
176
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
177

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

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

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

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

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

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

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

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

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

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

    
300
loadTabular lines_data convert_fn = do
301
  let rows = map (sepSplit '|') lines_data
302
  kerows <- mapM convert_fn rows
303
  return $ assignIndices kerows
304

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

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

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