Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Text.hs @ c22d4dd4

History | View | Annotate | Download (12.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 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" (Group.name grp) (Group.uuid grp)
70
           (allocPolicyToRaw (Group.allocPolicy grp))
71

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

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

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

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

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

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

    
124
-- | Generate disk template data.
125
serializeDiskTemplates :: [DiskTemplate] -> String
126
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
127

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

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

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

    
162
-- * Parsing functions
163

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

    
172
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
173

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

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

    
227
-- | Loads a spec from a field list.
228
loadISpec :: String -> [String] -> Result ISpec
229
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c] = do
230
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
231
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
232
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
233
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
234
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
235
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c
236
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
237

    
238
-- | Loads an ipolicy from a field list.
239
loadIPolicy :: [String] -> Result (String, IPolicy)
240
loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates,
241
             vcpu_ratio, spindle_ratio] = do
242
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
243
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
244
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
245
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
246
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
247
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
248
  return $ (owner, IPolicy xstdspec xminspec xmaxspec xdts
249
            xvcpu_ratio xspindle_ratio)
250
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
251

    
252
loadOnePolicy :: (IPolicy, Group.List) -> String
253
              -> Result (IPolicy, Group.List)
254
loadOnePolicy (cpol, gl) line = do
255
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
256
  case owner of
257
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
258
    _ -> do
259
      grp <- Container.findByName gl owner
260
      let grp' = grp { Group.iPolicy = ipol }
261
          gl' = Container.add (Group.idx grp') grp' gl
262
      return (cpol, gl')
263

    
264
-- | Loads all policies from the policy section
265
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
266
loadAllIPolicies gl =
267
  foldM loadOnePolicy (defIPolicy, gl)
268

    
269
-- | Convert newline and delimiter-separated text.
270
--
271
-- This function converts a text in tabular format as generated by
272
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
273
-- a supplied conversion function.
274
loadTabular :: (Monad m, Element a) =>
275
               [String] -- ^ Input data, as a list of lines
276
            -> ([String] -> m (String, a)) -- ^ Conversion function
277
            -> m ( NameAssoc
278
                 , Container.Container a ) -- ^ A tuple of an
279
                                           -- association list (name
280
                                           -- to object) and a set as
281
                                           -- used in
282
                                           -- "Ganeti.HTools.Container"
283

    
284
loadTabular lines_data convert_fn = do
285
  let rows = map (sepSplit '|') lines_data
286
  kerows <- mapM convert_fn rows
287
  return $ assignIndices kerows
288

    
289
-- | Load the cluser data from disk.
290
--
291
-- This is an alias to 'readFile' just for consistency with the other
292
-- modules.
293
readData :: String    -- ^ Path to the text file
294
         -> IO String -- ^ Contents of the file
295
readData = readFile
296

    
297
-- | Builds the cluster data from text input.
298
parseData :: String -- ^ Text data
299
          -> Result ClusterData
300
parseData fdata = do
301
  let flines = lines fdata
302
  (glines, nlines, ilines, ctags, pollines) <-
303
      case sepSplit "" flines of
304
        [a, b, c, d, e] -> Ok (a, b, c, d, e)
305
        [a, b, c, d] -> Ok (a, b, c, d, [])
306
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
307
                           \ instead of 4 or 5" (length xs)
308
  {- group file: name uuid -}
309
  (ktg, gl) <- loadTabular glines loadGroup
310
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
311
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
312
  {- instance file: name mem disk status pnode snode -}
313
  (_, il) <- loadTabular ilines (loadInst ktn)
314
  {- the tags are simply line-based, no processing needed -}
315
  {- process policies -}
316
  (cpol, gl') <- loadAllIPolicies gl pollines
317
  return (ClusterData gl' nl il ctags cpol)
318

    
319
-- | Top level function for data loading.
320
loadData :: String -- ^ Path to the text file
321
         -> IO (Result ClusterData)
322
loadData = fmap parseData . readData