Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Text.hs @ 7dd14211

History | View | Annotate | Download (8.7 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 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
    (
31
      loadData
32
    , parseData
33
    , loadInst
34
    , loadNode
35
    , serializeInstances
36
    , serializeNode
37
    , serializeNodes
38
    , serializeCluster
39
    ) where
40

    
41
import Control.Monad
42
import Data.List
43

    
44
import Text.Printf (printf)
45

    
46
import Ganeti.HTools.Utils
47
import Ganeti.HTools.Loader
48
import Ganeti.HTools.Types
49
import qualified Ganeti.HTools.Container as Container
50
import qualified Ganeti.HTools.Group as Group
51
import qualified Ganeti.HTools.Node as Node
52
import qualified Ganeti.HTools.Instance as Instance
53

    
54
-- * Serialisation functions
55

    
56
-- | Serialize a single group.
57
serializeGroup :: Group.Group -> String
58
serializeGroup grp =
59
    printf "%s|%s|%s" (Group.name grp) (Group.uuid grp)
60
               (allocPolicyToRaw (Group.allocPolicy grp))
61

    
62
-- | Generate group file data from a group list.
63
serializeGroups :: Group.List -> String
64
serializeGroups = unlines . map serializeGroup . Container.elems
65

    
66
-- | Serialize a single node.
67
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
68
              -> Node.Node  -- ^ The node to be serialised
69
              -> String
70
serializeNode gl node =
71
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
72
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
73
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
74
               (if Node.offline node then 'Y' else 'N')
75
               (Group.uuid grp)
76
    where grp = Container.find (Node.group node) gl
77

    
78
-- | Generate node file data from node objects.
79
serializeNodes :: Group.List -> Node.List -> String
80
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
81

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

    
103
-- | Generate instance file data from instance objects.
104
serializeInstances :: Node.List -> Instance.List -> String
105
serializeInstances nl =
106
    unlines . map (serializeInstance nl) . Container.elems
107

    
108
-- | Generate complete cluster data from node and instance lists.
109
serializeCluster :: ClusterData -> String
110
serializeCluster (ClusterData gl nl il ctags) =
111
  let gdata = serializeGroups gl
112
      ndata = serializeNodes gl nl
113
      idata = serializeInstances nl il
114
  -- note: not using 'unlines' as that adds too many newlines
115
  in intercalate "\n" [gdata, ndata, idata, unlines ctags]
116

    
117
-- * Parsing functions
118

    
119
-- | Load a group from a field list.
120
loadGroup :: (Monad m) => [String]
121
          -> m (String, Group.Group) -- ^ The result, a tuple of group
122
                                     -- UUID and group object
123
loadGroup [name, gid, apol] = do
124
  xapol <- allocPolicyFromRaw apol
125
  return (gid, Group.create name gid xapol)
126

    
127
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
128

    
129
-- | Load a node from a field list.
130
loadNode :: (Monad m) =>
131
            NameAssoc             -- ^ Association list with current groups
132
         -> [String]              -- ^ Input data as a list of fields
133
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
134
                                  -- and node object
135
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
136
  gdx <- lookupGroup ktg name gu
137
  new_node <-
138
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
139
          return $ Node.create name 0 0 0 0 0 0 True gdx
140
      else do
141
        vtm <- tryRead name tm
142
        vnm <- tryRead name nm
143
        vfm <- tryRead name fm
144
        vtd <- tryRead name td
145
        vfd <- tryRead name fd
146
        vtc <- tryRead name tc
147
        return $ Node.create name vtm vnm vfm vtd vfd vtc False gdx
148
  return (name, new_node)
149
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
150

    
151
-- | Load an instance from a field list.
152
loadInst :: NameAssoc -- ^ Association list with the current nodes
153
         -> [String]  -- ^ Input data as a list of fields
154
         -> Result (String, Instance.Instance) -- ^ A tuple of
155
                                               -- instance name and
156
                                               -- the instance object
157
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
158
             , dt, tags ] = do
159
  pidx <- lookupNode ktn name pnode
160
  sidx <- (if null snode then return Node.noSecondary
161
           else lookupNode ktn name snode)
162
  vmem <- tryRead name mem
163
  vdsk <- tryRead name dsk
164
  vvcpus <- tryRead name vcpus
165
  vstatus <- instanceStatusFromRaw status
166
  auto_balance <- case auto_bal of
167
                    "Y" -> return True
168
                    "N" -> return False
169
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
170
                         "' for instance " ++ name
171
  disk_template <- annotateResult ("Instance " ++ name)
172
                   (diskTemplateFromRaw dt)
173
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
174
           " has same primary and secondary node - " ++ pnode
175
  let vtags = sepSplit ',' tags
176
      newinst = Instance.create name vmem vdsk vvcpus vstatus vtags
177
                auto_balance pidx sidx disk_template
178
  return (name, newinst)
179
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
180

    
181
-- | Convert newline and delimiter-separated text.
182
--
183
-- This function converts a text in tabular format as generated by
184
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
185
-- a supplied conversion function.
186
loadTabular :: (Monad m, Element a) =>
187
               [String] -- ^ Input data, as a list of lines
188
            -> ([String] -> m (String, a)) -- ^ Conversion function
189
            -> m ( NameAssoc
190
                 , Container.Container a ) -- ^ A tuple of an
191
                                           -- association list (name
192
                                           -- to object) and a set as
193
                                           -- used in
194
                                           -- "Ganeti.HTools.Container"
195

    
196
loadTabular lines_data convert_fn = do
197
  let rows = map (sepSplit '|') lines_data
198
  kerows <- mapM convert_fn rows
199
  return $ assignIndices kerows
200

    
201
-- | Load the cluser data from disk.
202
--
203
-- This is an alias to 'readFile' just for consistency with the other
204
-- modules.
205
readData :: String    -- ^ Path to the text file
206
         -> IO String -- ^ Contents of the file
207
readData = readFile
208

    
209
-- | Builds the cluster data from text input.
210
parseData :: String -- ^ Text data
211
          -> Result ClusterData
212
parseData fdata = do
213
  let flines = lines fdata
214
  (glines, nlines, ilines, ctags) <-
215
      case sepSplit "" flines of
216
        [a, b, c, d] -> Ok (a, b, c, d)
217
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
218
                           \ instead of 4" (length xs)
219
  {- group file: name uuid -}
220
  (ktg, gl) <- loadTabular glines loadGroup
221
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
222
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
223
  {- instance file: name mem disk status pnode snode -}
224
  (_, il) <- loadTabular ilines (loadInst ktn)
225
  {- the tags are simply line-based, no processing needed -}
226
  return (ClusterData gl nl il ctags)
227

    
228
-- | Top level function for data loading.
229
loadData :: String -- ^ Path to the text file
230
         -> IO (Result ClusterData)
231
loadData = fmap parseData . readData