Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (8.6 kB)

1 525bfb36 Iustin Pop
{-| Parsing data from text-files.
2 040afc35 Iustin Pop
3 040afc35 Iustin Pop
This module holds the code for loading the cluster state from text
4 525bfb36 Iustin Pop
files, as produced by @gnt-node@ and @gnt-instance@ @list@ command.
5 040afc35 Iustin Pop
6 040afc35 Iustin Pop
-}
7 040afc35 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 d5072e4c Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
14 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e2fa2baf Iustin Pop
(at your option) any later version.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e2fa2baf Iustin Pop
General Public License for more details.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
23 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
24 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e2fa2baf Iustin Pop
02110-1301, USA.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
-}
28 e2fa2baf Iustin Pop
29 040afc35 Iustin Pop
module Ganeti.HTools.Text
30 ebf38064 Iustin Pop
  ( loadData
31 ebf38064 Iustin Pop
  , parseData
32 ebf38064 Iustin Pop
  , loadInst
33 ebf38064 Iustin Pop
  , loadNode
34 ebf38064 Iustin Pop
  , serializeInstances
35 ebf38064 Iustin Pop
  , serializeNode
36 ebf38064 Iustin Pop
  , serializeNodes
37 ebf38064 Iustin Pop
  , serializeCluster
38 ebf38064 Iustin Pop
  ) where
39 040afc35 Iustin Pop
40 040afc35 Iustin Pop
import Control.Monad
41 3bf75b7d Iustin Pop
import Data.List
42 3bf75b7d Iustin Pop
43 3bf75b7d Iustin Pop
import Text.Printf (printf)
44 040afc35 Iustin Pop
45 040afc35 Iustin Pop
import Ganeti.HTools.Utils
46 040afc35 Iustin Pop
import Ganeti.HTools.Loader
47 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
48 3bf75b7d Iustin Pop
import qualified Ganeti.HTools.Container as Container
49 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
50 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
51 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
52 040afc35 Iustin Pop
53 525bfb36 Iustin Pop
-- * Serialisation functions
54 525bfb36 Iustin Pop
55 525bfb36 Iustin Pop
-- | Serialize a single group.
56 e4d8071d Iustin Pop
serializeGroup :: Group.Group -> String
57 e4d8071d Iustin Pop
serializeGroup grp =
58 ebf38064 Iustin Pop
  printf "%s|%s|%s" (Group.name grp) (Group.uuid grp)
59 ebf38064 Iustin Pop
           (allocPolicyToRaw (Group.allocPolicy grp))
60 e4d8071d Iustin Pop
61 525bfb36 Iustin Pop
-- | Generate group file data from a group list.
62 e4d8071d Iustin Pop
serializeGroups :: Group.List -> String
63 e4d8071d Iustin Pop
serializeGroups = unlines . map serializeGroup . Container.elems
64 e4d8071d Iustin Pop
65 525bfb36 Iustin Pop
-- | Serialize a single node.
66 525bfb36 Iustin Pop
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
67 525bfb36 Iustin Pop
              -> Node.Node  -- ^ The node to be serialised
68 525bfb36 Iustin Pop
              -> String
69 10ef6b4e Iustin Pop
serializeNode gl node =
70 ebf38064 Iustin Pop
  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
71 ebf38064 Iustin Pop
           (Node.tMem node) (Node.nMem node) (Node.fMem node)
72 ebf38064 Iustin Pop
           (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
73 ebf38064 Iustin Pop
           (if Node.offline node then 'Y' else 'N')
74 ebf38064 Iustin Pop
           (Group.uuid grp)
75 10ef6b4e Iustin Pop
    where grp = Container.find (Node.group node) gl
76 3bf75b7d Iustin Pop
77 525bfb36 Iustin Pop
-- | Generate node file data from node objects.
78 10ef6b4e Iustin Pop
serializeNodes :: Group.List -> Node.List -> String
79 10ef6b4e Iustin Pop
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
80 3bf75b7d Iustin Pop
81 525bfb36 Iustin Pop
-- | Serialize a single instance.
82 525bfb36 Iustin Pop
serializeInstance :: Node.List         -- ^ The node list (needed for
83 525bfb36 Iustin Pop
                                       -- node names)
84 525bfb36 Iustin Pop
                  -> Instance.Instance -- ^ The instance to be serialised
85 525bfb36 Iustin Pop
                  -> String
86 3bf75b7d Iustin Pop
serializeInstance nl inst =
87 ebf38064 Iustin Pop
  let iname = Instance.name inst
88 ebf38064 Iustin Pop
      pnode = Container.nameOf nl (Instance.pNode inst)
89 ebf38064 Iustin Pop
      sidx = Instance.sNode inst
90 ebf38064 Iustin Pop
      snode = (if sidx == Node.noSecondary
91 ebf38064 Iustin Pop
                 then ""
92 ebf38064 Iustin Pop
                 else Container.nameOf nl sidx)
93 ebf38064 Iustin Pop
  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s"
94 ebf38064 Iustin Pop
       iname (Instance.mem inst) (Instance.dsk inst)
95 ebf38064 Iustin Pop
       (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
96 ebf38064 Iustin Pop
       (if Instance.autoBalance inst then "Y" else "N")
97 ebf38064 Iustin Pop
       pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
98 ebf38064 Iustin Pop
       (intercalate "," (Instance.tags inst))
99 3bf75b7d Iustin Pop
100 525bfb36 Iustin Pop
-- | Generate instance file data from instance objects.
101 3bf75b7d Iustin Pop
serializeInstances :: Node.List -> Instance.List -> String
102 3bf75b7d Iustin Pop
serializeInstances nl =
103 ebf38064 Iustin Pop
  unlines . map (serializeInstance nl) . Container.elems
104 3bf75b7d Iustin Pop
105 525bfb36 Iustin Pop
-- | Generate complete cluster data from node and instance lists.
106 c0e31451 Iustin Pop
serializeCluster :: ClusterData -> String
107 c0e31451 Iustin Pop
serializeCluster (ClusterData gl nl il ctags) =
108 e4d8071d Iustin Pop
  let gdata = serializeGroups gl
109 e4d8071d Iustin Pop
      ndata = serializeNodes gl nl
110 4a273e97 Iustin Pop
      idata = serializeInstances nl il
111 716c6be5 Iustin Pop
  -- note: not using 'unlines' as that adds too many newlines
112 716c6be5 Iustin Pop
  in intercalate "\n" [gdata, ndata, idata, unlines ctags]
113 4a273e97 Iustin Pop
114 525bfb36 Iustin Pop
-- * Parsing functions
115 525bfb36 Iustin Pop
116 a679e9dc Iustin Pop
-- | Load a group from a field list.
117 525bfb36 Iustin Pop
loadGroup :: (Monad m) => [String]
118 525bfb36 Iustin Pop
          -> m (String, Group.Group) -- ^ The result, a tuple of group
119 525bfb36 Iustin Pop
                                     -- UUID and group object
120 f4c7d37a Iustin Pop
loadGroup [name, gid, apol] = do
121 5f828ce4 Agata Murawska
  xapol <- allocPolicyFromRaw apol
122 d5072e4c Iustin Pop
  return (gid, Group.create name gid xapol)
123 a679e9dc Iustin Pop
124 a679e9dc Iustin Pop
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
125 a679e9dc Iustin Pop
126 9188aeef Iustin Pop
-- | Load a node from a field list.
127 525bfb36 Iustin Pop
loadNode :: (Monad m) =>
128 525bfb36 Iustin Pop
            NameAssoc             -- ^ Association list with current groups
129 525bfb36 Iustin Pop
         -> [String]              -- ^ Input data as a list of fields
130 525bfb36 Iustin Pop
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
131 525bfb36 Iustin Pop
                                  -- and node object
132 10ef6b4e Iustin Pop
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
133 10ef6b4e Iustin Pop
  gdx <- lookupGroup ktg name gu
134 040afc35 Iustin Pop
  new_node <-
135 1a82215d Iustin Pop
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
136 10ef6b4e Iustin Pop
          return $ Node.create name 0 0 0 0 0 0 True gdx
137 040afc35 Iustin Pop
      else do
138 040afc35 Iustin Pop
        vtm <- tryRead name tm
139 040afc35 Iustin Pop
        vnm <- tryRead name nm
140 040afc35 Iustin Pop
        vfm <- tryRead name fm
141 040afc35 Iustin Pop
        vtd <- tryRead name td
142 040afc35 Iustin Pop
        vfd <- tryRead name fd
143 1a82215d Iustin Pop
        vtc <- tryRead name tc
144 10ef6b4e Iustin Pop
        return $ Node.create name vtm vnm vfm vtd vfd vtc False gdx
145 040afc35 Iustin Pop
  return (name, new_node)
146 10ef6b4e Iustin Pop
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
147 040afc35 Iustin Pop
148 9188aeef Iustin Pop
-- | Load an instance from a field list.
149 6429e8d8 Iustin Pop
loadInst :: NameAssoc -- ^ Association list with the current nodes
150 6429e8d8 Iustin Pop
         -> [String]  -- ^ Input data as a list of fields
151 6429e8d8 Iustin Pop
         -> Result (String, Instance.Instance) -- ^ A tuple of
152 6429e8d8 Iustin Pop
                                               -- instance name and
153 6429e8d8 Iustin Pop
                                               -- the instance object
154 6429e8d8 Iustin Pop
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
155 6429e8d8 Iustin Pop
             , dt, tags ] = do
156 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
157 3603605a Iustin Pop
  sidx <- if null snode
158 3603605a Iustin Pop
            then return Node.noSecondary
159 3603605a Iustin Pop
            else lookupNode ktn name snode
160 040afc35 Iustin Pop
  vmem <- tryRead name mem
161 040afc35 Iustin Pop
  vdsk <- tryRead name dsk
162 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
163 7dd14211 Agata Murawska
  vstatus <- instanceStatusFromRaw status
164 bc782180 Iustin Pop
  auto_balance <- case auto_bal of
165 bc782180 Iustin Pop
                    "Y" -> return True
166 bc782180 Iustin Pop
                    "N" -> return False
167 bc782180 Iustin Pop
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
168 bc782180 Iustin Pop
                         "' for instance " ++ name
169 2c9336a4 Iustin Pop
  disk_template <- annotateResult ("Instance " ++ name)
170 5f828ce4 Agata Murawska
                   (diskTemplateFromRaw dt)
171 040afc35 Iustin Pop
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
172 040afc35 Iustin Pop
           " has same primary and secondary node - " ++ pnode
173 17e7af2b Iustin Pop
  let vtags = sepSplit ',' tags
174 7dd14211 Agata Murawska
      newinst = Instance.create name vmem vdsk vvcpus vstatus vtags
175 6429e8d8 Iustin Pop
                auto_balance pidx sidx disk_template
176 040afc35 Iustin Pop
  return (name, newinst)
177 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
178 040afc35 Iustin Pop
179 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
180 9188aeef Iustin Pop
--
181 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
182 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
183 9188aeef Iustin Pop
-- a supplied conversion function.
184 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
185 525bfb36 Iustin Pop
               [String] -- ^ Input data, as a list of lines
186 525bfb36 Iustin Pop
            -> ([String] -> m (String, a)) -- ^ Conversion function
187 525bfb36 Iustin Pop
            -> m ( NameAssoc
188 525bfb36 Iustin Pop
                 , Container.Container a ) -- ^ A tuple of an
189 525bfb36 Iustin Pop
                                           -- association list (name
190 525bfb36 Iustin Pop
                                           -- to object) and a set as
191 525bfb36 Iustin Pop
                                           -- used in
192 525bfb36 Iustin Pop
                                           -- "Ganeti.HTools.Container"
193 525bfb36 Iustin Pop
194 f5197d89 Iustin Pop
loadTabular lines_data convert_fn = do
195 f5197d89 Iustin Pop
  let rows = map (sepSplit '|') lines_data
196 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
197 497e30a1 Iustin Pop
  return $ assignIndices kerows
198 040afc35 Iustin Pop
199 dadfc261 Iustin Pop
-- | Load the cluser data from disk.
200 525bfb36 Iustin Pop
--
201 525bfb36 Iustin Pop
-- This is an alias to 'readFile' just for consistency with the other
202 525bfb36 Iustin Pop
-- modules.
203 525bfb36 Iustin Pop
readData :: String    -- ^ Path to the text file
204 525bfb36 Iustin Pop
         -> IO String -- ^ Contents of the file
205 dadfc261 Iustin Pop
readData = readFile
206 dadfc261 Iustin Pop
207 16c2369c Iustin Pop
-- | Builds the cluster data from text input.
208 dadfc261 Iustin Pop
parseData :: String -- ^ Text data
209 f4f6eb0b Iustin Pop
          -> Result ClusterData
210 dadfc261 Iustin Pop
parseData fdata = do
211 16c2369c Iustin Pop
  let flines = lines fdata
212 afcd5a0b Iustin Pop
  (glines, nlines, ilines, ctags) <-
213 a604456d Iustin Pop
      case sepSplit "" flines of
214 afcd5a0b Iustin Pop
        [a, b, c, d] -> Ok (a, b, c, d)
215 a604456d Iustin Pop
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
216 afcd5a0b Iustin Pop
                           \ instead of 4" (length xs)
217 a679e9dc Iustin Pop
  {- group file: name uuid -}
218 10ef6b4e Iustin Pop
  (ktg, gl) <- loadTabular glines loadGroup
219 dadfc261 Iustin Pop
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
220 a604456d Iustin Pop
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
221 dadfc261 Iustin Pop
  {- instance file: name mem disk status pnode snode -}
222 a604456d Iustin Pop
  (_, il) <- loadTabular ilines (loadInst ktn)
223 afcd5a0b Iustin Pop
  {- the tags are simply line-based, no processing needed -}
224 f4f6eb0b Iustin Pop
  return (ClusterData gl nl il ctags)
225 dadfc261 Iustin Pop
226 525bfb36 Iustin Pop
-- | Top level function for data loading.
227 dadfc261 Iustin Pop
loadData :: String -- ^ Path to the text file
228 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
229 2a8e2dc9 Iustin Pop
loadData = fmap parseData . readData