Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Backend / Text.hs @ 29a30533

History | View | Annotate | Download (13.1 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 b37f4a76 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 879d9290 Iustin Pop
module Ganeti.HTools.Backend.Text
30 ebf38064 Iustin Pop
  ( loadData
31 ebf38064 Iustin Pop
  , parseData
32 ebf38064 Iustin Pop
  , loadInst
33 ebf38064 Iustin Pop
  , loadNode
34 bcd17bf0 Iustin Pop
  , loadISpec
35 bcd17bf0 Iustin Pop
  , loadIPolicy
36 ebf38064 Iustin Pop
  , serializeInstances
37 ebf38064 Iustin Pop
  , serializeNode
38 ebf38064 Iustin Pop
  , serializeNodes
39 bcd17bf0 Iustin Pop
  , serializeGroup
40 bcd17bf0 Iustin Pop
  , serializeISpec
41 bcd17bf0 Iustin Pop
  , serializeIPolicy
42 ebf38064 Iustin Pop
  , serializeCluster
43 ebf38064 Iustin Pop
  ) where
44 040afc35 Iustin Pop
45 040afc35 Iustin Pop
import Control.Monad
46 3bf75b7d Iustin Pop
import Data.List
47 3bf75b7d Iustin Pop
48 3bf75b7d Iustin Pop
import Text.Printf (printf)
49 040afc35 Iustin Pop
50 01e52493 Iustin Pop
import Ganeti.BasicTypes
51 26d62e4c Iustin Pop
import Ganeti.Utils
52 040afc35 Iustin Pop
import Ganeti.HTools.Loader
53 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
54 3bf75b7d Iustin Pop
import qualified Ganeti.HTools.Container as Container
55 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
56 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
57 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
58 040afc35 Iustin Pop
59 b37f4a76 Iustin Pop
-- * Helper functions
60 b37f4a76 Iustin Pop
61 b37f4a76 Iustin Pop
-- | Simple wrapper over sepSplit
62 b37f4a76 Iustin Pop
commaSplit :: String -> [String]
63 b37f4a76 Iustin Pop
commaSplit = sepSplit ','
64 b37f4a76 Iustin Pop
65 525bfb36 Iustin Pop
-- * Serialisation functions
66 525bfb36 Iustin Pop
67 525bfb36 Iustin Pop
-- | Serialize a single group.
68 e4d8071d Iustin Pop
serializeGroup :: Group.Group -> String
69 e4d8071d Iustin Pop
serializeGroup grp =
70 6b6e335b Dato Simó
  printf "%s|%s|%s|%s" (Group.name grp) (Group.uuid grp)
71 ebf38064 Iustin Pop
           (allocPolicyToRaw (Group.allocPolicy grp))
72 6b6e335b Dato Simó
           (intercalate "," (Group.allTags grp))
73 e4d8071d Iustin Pop
74 525bfb36 Iustin Pop
-- | Generate group file data from a group list.
75 e4d8071d Iustin Pop
serializeGroups :: Group.List -> String
76 e4d8071d Iustin Pop
serializeGroups = unlines . map serializeGroup . Container.elems
77 e4d8071d Iustin Pop
78 525bfb36 Iustin Pop
-- | Serialize a single node.
79 525bfb36 Iustin Pop
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
80 525bfb36 Iustin Pop
              -> Node.Node  -- ^ The node to be serialised
81 525bfb36 Iustin Pop
              -> String
82 10ef6b4e Iustin Pop
serializeNode gl node =
83 f951bd09 Iustin Pop
  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d" (Node.name node)
84 ebf38064 Iustin Pop
           (Node.tMem node) (Node.nMem node) (Node.fMem node)
85 ebf38064 Iustin Pop
           (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
86 ebf38064 Iustin Pop
           (if Node.offline node then 'Y' else 'N')
87 ebf38064 Iustin Pop
           (Group.uuid grp)
88 f951bd09 Iustin Pop
           (Node.spindleCount node)
89 10ef6b4e Iustin Pop
    where grp = Container.find (Node.group node) gl
90 3bf75b7d Iustin Pop
91 525bfb36 Iustin Pop
-- | Generate node file data from node objects.
92 10ef6b4e Iustin Pop
serializeNodes :: Group.List -> Node.List -> String
93 10ef6b4e Iustin Pop
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
94 3bf75b7d Iustin Pop
95 525bfb36 Iustin Pop
-- | Serialize a single instance.
96 525bfb36 Iustin Pop
serializeInstance :: Node.List         -- ^ The node list (needed for
97 525bfb36 Iustin Pop
                                       -- node names)
98 525bfb36 Iustin Pop
                  -> Instance.Instance -- ^ The instance to be serialised
99 525bfb36 Iustin Pop
                  -> String
100 3bf75b7d Iustin Pop
serializeInstance nl inst =
101 ebf38064 Iustin Pop
  let iname = Instance.name inst
102 ebf38064 Iustin Pop
      pnode = Container.nameOf nl (Instance.pNode inst)
103 ebf38064 Iustin Pop
      sidx = Instance.sNode inst
104 ebf38064 Iustin Pop
      snode = (if sidx == Node.noSecondary
105 ebf38064 Iustin Pop
                 then ""
106 ebf38064 Iustin Pop
                 else Container.nameOf nl sidx)
107 52cc1370 René Nussbaumer
  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d"
108 ebf38064 Iustin Pop
       iname (Instance.mem inst) (Instance.dsk inst)
109 ebf38064 Iustin Pop
       (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
110 ebf38064 Iustin Pop
       (if Instance.autoBalance inst then "Y" else "N")
111 ebf38064 Iustin Pop
       pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
112 2f907bad Dato Simó
       (intercalate "," (Instance.allTags inst)) (Instance.spindleUse inst)
113 3bf75b7d Iustin Pop
114 525bfb36 Iustin Pop
-- | Generate instance file data from instance objects.
115 3bf75b7d Iustin Pop
serializeInstances :: Node.List -> Instance.List -> String
116 3bf75b7d Iustin Pop
serializeInstances nl =
117 ebf38064 Iustin Pop
  unlines . map (serializeInstance nl) . Container.elems
118 3bf75b7d Iustin Pop
119 b37f4a76 Iustin Pop
-- | Generate a spec data from a given ISpec object.
120 b37f4a76 Iustin Pop
serializeISpec :: ISpec -> String
121 b37f4a76 Iustin Pop
serializeISpec ispec =
122 b37f4a76 Iustin Pop
  -- this needs to be kept in sync with the object definition
123 d953a965 René Nussbaumer
  let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec
124 d953a965 René Nussbaumer
      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c,
125 d953a965 René Nussbaumer
                 show su]
126 b37f4a76 Iustin Pop
  in intercalate "," strings
127 b37f4a76 Iustin Pop
128 b37f4a76 Iustin Pop
-- | Generate disk template data.
129 b37f4a76 Iustin Pop
serializeDiskTemplates :: [DiskTemplate] -> String
130 b37f4a76 Iustin Pop
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
131 b37f4a76 Iustin Pop
132 b37f4a76 Iustin Pop
-- | Generate policy data from a given policy object.
133 b37f4a76 Iustin Pop
serializeIPolicy :: String -> IPolicy -> String
134 b37f4a76 Iustin Pop
serializeIPolicy owner ipol =
135 c22d4dd4 Iustin Pop
  let IPolicy stdspec minspec maxspec dts vcpu_ratio spindle_ratio = ipol
136 b37f4a76 Iustin Pop
      strings = [ owner
137 b37f4a76 Iustin Pop
                , serializeISpec stdspec
138 b37f4a76 Iustin Pop
                , serializeISpec minspec
139 b37f4a76 Iustin Pop
                , serializeISpec maxspec
140 b37f4a76 Iustin Pop
                , serializeDiskTemplates dts
141 e8fa4ff6 Iustin Pop
                , show vcpu_ratio
142 c22d4dd4 Iustin Pop
                , show spindle_ratio
143 b37f4a76 Iustin Pop
                ]
144 b37f4a76 Iustin Pop
  in intercalate "|" strings
145 b37f4a76 Iustin Pop
146 b37f4a76 Iustin Pop
-- | Generates the entire ipolicy section from the cluster and group
147 b37f4a76 Iustin Pop
-- objects.
148 b37f4a76 Iustin Pop
serializeAllIPolicies :: IPolicy -> Group.List -> String
149 b37f4a76 Iustin Pop
serializeAllIPolicies cpol gl =
150 b37f4a76 Iustin Pop
  let groups = Container.elems gl
151 5b11f8db Iustin Pop
      allpolicies = ("", cpol) :
152 b37f4a76 Iustin Pop
                    map (\g -> (Group.name g, Group.iPolicy g)) groups
153 b37f4a76 Iustin Pop
      strings = map (uncurry serializeIPolicy) allpolicies
154 b37f4a76 Iustin Pop
  in unlines strings
155 b37f4a76 Iustin Pop
156 525bfb36 Iustin Pop
-- | Generate complete cluster data from node and instance lists.
157 c0e31451 Iustin Pop
serializeCluster :: ClusterData -> String
158 b37f4a76 Iustin Pop
serializeCluster (ClusterData gl nl il ctags cpol) =
159 e4d8071d Iustin Pop
  let gdata = serializeGroups gl
160 e4d8071d Iustin Pop
      ndata = serializeNodes gl nl
161 4a273e97 Iustin Pop
      idata = serializeInstances nl il
162 b37f4a76 Iustin Pop
      pdata = serializeAllIPolicies cpol gl
163 716c6be5 Iustin Pop
  -- note: not using 'unlines' as that adds too many newlines
164 b37f4a76 Iustin Pop
  in intercalate "\n" [gdata, ndata, idata, unlines ctags, pdata]
165 4a273e97 Iustin Pop
166 525bfb36 Iustin Pop
-- * Parsing functions
167 525bfb36 Iustin Pop
168 a679e9dc Iustin Pop
-- | Load a group from a field list.
169 525bfb36 Iustin Pop
loadGroup :: (Monad m) => [String]
170 525bfb36 Iustin Pop
          -> m (String, Group.Group) -- ^ The result, a tuple of group
171 525bfb36 Iustin Pop
                                     -- UUID and group object
172 6b6e335b Dato Simó
loadGroup [name, gid, apol, tags] = do
173 5f828ce4 Agata Murawska
  xapol <- allocPolicyFromRaw apol
174 6b6e335b Dato Simó
  let xtags = commaSplit tags
175 6b6e335b Dato Simó
  return (gid, Group.create name gid xapol defIPolicy xtags)
176 a679e9dc Iustin Pop
177 a679e9dc Iustin Pop
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
178 a679e9dc Iustin Pop
179 9188aeef Iustin Pop
-- | Load a node from a field list.
180 525bfb36 Iustin Pop
loadNode :: (Monad m) =>
181 525bfb36 Iustin Pop
            NameAssoc             -- ^ Association list with current groups
182 525bfb36 Iustin Pop
         -> [String]              -- ^ Input data as a list of fields
183 525bfb36 Iustin Pop
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
184 525bfb36 Iustin Pop
                                  -- and node object
185 f951bd09 Iustin Pop
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] = do
186 10ef6b4e Iustin Pop
  gdx <- lookupGroup ktg name gu
187 040afc35 Iustin Pop
  new_node <-
188 2cdaf225 Iustin Pop
      if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then
189 8bc34c7b Iustin Pop
          return $ Node.create name 0 0 0 0 0 0 True 0 gdx
190 040afc35 Iustin Pop
      else do
191 040afc35 Iustin Pop
        vtm <- tryRead name tm
192 040afc35 Iustin Pop
        vnm <- tryRead name nm
193 040afc35 Iustin Pop
        vfm <- tryRead name fm
194 040afc35 Iustin Pop
        vtd <- tryRead name td
195 040afc35 Iustin Pop
        vfd <- tryRead name fd
196 1a82215d Iustin Pop
        vtc <- tryRead name tc
197 f951bd09 Iustin Pop
        vspindles <- tryRead name spindles
198 f951bd09 Iustin Pop
        return $ Node.create name vtm vnm vfm vtd vfd vtc False vspindles gdx
199 040afc35 Iustin Pop
  return (name, new_node)
200 f951bd09 Iustin Pop
201 f951bd09 Iustin Pop
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
202 f951bd09 Iustin Pop
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
203 f951bd09 Iustin Pop
204 10ef6b4e Iustin Pop
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
205 040afc35 Iustin Pop
206 9188aeef Iustin Pop
-- | Load an instance from a field list.
207 6429e8d8 Iustin Pop
loadInst :: NameAssoc -- ^ Association list with the current nodes
208 6429e8d8 Iustin Pop
         -> [String]  -- ^ Input data as a list of fields
209 6429e8d8 Iustin Pop
         -> Result (String, Instance.Instance) -- ^ A tuple of
210 6429e8d8 Iustin Pop
                                               -- instance name and
211 6429e8d8 Iustin Pop
                                               -- the instance object
212 6429e8d8 Iustin Pop
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
213 52cc1370 René Nussbaumer
             , dt, tags, su ] = do
214 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
215 3603605a Iustin Pop
  sidx <- if null snode
216 3603605a Iustin Pop
            then return Node.noSecondary
217 3603605a Iustin Pop
            else lookupNode ktn name snode
218 040afc35 Iustin Pop
  vmem <- tryRead name mem
219 040afc35 Iustin Pop
  vdsk <- tryRead name dsk
220 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
221 7dd14211 Agata Murawska
  vstatus <- instanceStatusFromRaw status
222 bc782180 Iustin Pop
  auto_balance <- case auto_bal of
223 bc782180 Iustin Pop
                    "Y" -> return True
224 bc782180 Iustin Pop
                    "N" -> return False
225 bc782180 Iustin Pop
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
226 bc782180 Iustin Pop
                         "' for instance " ++ name
227 2c9336a4 Iustin Pop
  disk_template <- annotateResult ("Instance " ++ name)
228 5f828ce4 Agata Murawska
                   (diskTemplateFromRaw dt)
229 ec629280 René Nussbaumer
  spindle_use <- tryRead name su
230 2cdaf225 Iustin Pop
  when (sidx == pidx) . fail $ "Instance " ++ name ++
231 040afc35 Iustin Pop
           " has same primary and secondary node - " ++ pnode
232 b37f4a76 Iustin Pop
  let vtags = commaSplit tags
233 7dd14211 Agata Murawska
      newinst = Instance.create name vmem vdsk vvcpus vstatus vtags
234 ec629280 René Nussbaumer
                auto_balance pidx sidx disk_template spindle_use
235 040afc35 Iustin Pop
  return (name, newinst)
236 52cc1370 René Nussbaumer
237 52cc1370 René Nussbaumer
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
238 52cc1370 René Nussbaumer
             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
239 52cc1370 René Nussbaumer
                                           auto_bal, pnode, snode, dt, tags,
240 52cc1370 René Nussbaumer
                                           "1" ]
241 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
242 040afc35 Iustin Pop
243 b37f4a76 Iustin Pop
-- | Loads a spec from a field list.
244 b37f4a76 Iustin Pop
loadISpec :: String -> [String] -> Result ISpec
245 d953a965 René Nussbaumer
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
246 b37f4a76 Iustin Pop
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
247 b37f4a76 Iustin Pop
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
248 b37f4a76 Iustin Pop
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
249 b37f4a76 Iustin Pop
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
250 b37f4a76 Iustin Pop
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
251 d953a965 René Nussbaumer
  xsu    <- tryRead (owner ++ "/spindleuse") su
252 d953a965 René Nussbaumer
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
253 b37f4a76 Iustin Pop
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
254 b37f4a76 Iustin Pop
255 b37f4a76 Iustin Pop
-- | Loads an ipolicy from a field list.
256 b37f4a76 Iustin Pop
loadIPolicy :: [String] -> Result (String, IPolicy)
257 c22d4dd4 Iustin Pop
loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates,
258 c22d4dd4 Iustin Pop
             vcpu_ratio, spindle_ratio] = do
259 b37f4a76 Iustin Pop
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
260 b37f4a76 Iustin Pop
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
261 b37f4a76 Iustin Pop
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
262 b37f4a76 Iustin Pop
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
263 e8fa4ff6 Iustin Pop
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
264 c22d4dd4 Iustin Pop
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
265 5b11f8db Iustin Pop
  return (owner,
266 5b11f8db Iustin Pop
          IPolicy xstdspec xminspec xmaxspec xdts xvcpu_ratio xspindle_ratio)
267 b37f4a76 Iustin Pop
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
268 b37f4a76 Iustin Pop
269 b37f4a76 Iustin Pop
loadOnePolicy :: (IPolicy, Group.List) -> String
270 b37f4a76 Iustin Pop
              -> Result (IPolicy, Group.List)
271 b37f4a76 Iustin Pop
loadOnePolicy (cpol, gl) line = do
272 b37f4a76 Iustin Pop
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
273 b37f4a76 Iustin Pop
  case owner of
274 b37f4a76 Iustin Pop
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
275 b37f4a76 Iustin Pop
    _ -> do
276 b37f4a76 Iustin Pop
      grp <- Container.findByName gl owner
277 b37f4a76 Iustin Pop
      let grp' = grp { Group.iPolicy = ipol }
278 b37f4a76 Iustin Pop
          gl' = Container.add (Group.idx grp') grp' gl
279 b37f4a76 Iustin Pop
      return (cpol, gl')
280 b37f4a76 Iustin Pop
281 b37f4a76 Iustin Pop
-- | Loads all policies from the policy section
282 b37f4a76 Iustin Pop
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
283 b37f4a76 Iustin Pop
loadAllIPolicies gl =
284 b37f4a76 Iustin Pop
  foldM loadOnePolicy (defIPolicy, gl)
285 b37f4a76 Iustin Pop
286 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
287 9188aeef Iustin Pop
--
288 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
289 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
290 9188aeef Iustin Pop
-- a supplied conversion function.
291 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
292 525bfb36 Iustin Pop
               [String] -- ^ Input data, as a list of lines
293 525bfb36 Iustin Pop
            -> ([String] -> m (String, a)) -- ^ Conversion function
294 525bfb36 Iustin Pop
            -> m ( NameAssoc
295 525bfb36 Iustin Pop
                 , Container.Container a ) -- ^ A tuple of an
296 525bfb36 Iustin Pop
                                           -- association list (name
297 525bfb36 Iustin Pop
                                           -- to object) and a set as
298 525bfb36 Iustin Pop
                                           -- used in
299 525bfb36 Iustin Pop
                                           -- "Ganeti.HTools.Container"
300 525bfb36 Iustin Pop
301 f5197d89 Iustin Pop
loadTabular lines_data convert_fn = do
302 f5197d89 Iustin Pop
  let rows = map (sepSplit '|') lines_data
303 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
304 497e30a1 Iustin Pop
  return $ assignIndices kerows
305 040afc35 Iustin Pop
306 dadfc261 Iustin Pop
-- | Load the cluser data from disk.
307 525bfb36 Iustin Pop
--
308 525bfb36 Iustin Pop
-- This is an alias to 'readFile' just for consistency with the other
309 525bfb36 Iustin Pop
-- modules.
310 525bfb36 Iustin Pop
readData :: String    -- ^ Path to the text file
311 525bfb36 Iustin Pop
         -> IO String -- ^ Contents of the file
312 dadfc261 Iustin Pop
readData = readFile
313 dadfc261 Iustin Pop
314 16c2369c Iustin Pop
-- | Builds the cluster data from text input.
315 dadfc261 Iustin Pop
parseData :: String -- ^ Text data
316 f4f6eb0b Iustin Pop
          -> Result ClusterData
317 dadfc261 Iustin Pop
parseData fdata = do
318 16c2369c Iustin Pop
  let flines = lines fdata
319 b37f4a76 Iustin Pop
  (glines, nlines, ilines, ctags, pollines) <-
320 a604456d Iustin Pop
      case sepSplit "" flines of
321 b37f4a76 Iustin Pop
        [a, b, c, d, e] -> Ok (a, b, c, d, e)
322 b37f4a76 Iustin Pop
        [a, b, c, d] -> Ok (a, b, c, d, [])
323 a604456d Iustin Pop
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
324 b37f4a76 Iustin Pop
                           \ instead of 4 or 5" (length xs)
325 b0b8337a Dato Simó
  {- group file: name uuid alloc_policy -}
326 10ef6b4e Iustin Pop
  (ktg, gl) <- loadTabular glines loadGroup
327 b0b8337a Dato Simó
  {- node file: name t_mem n_mem f_mem t_disk f_disk t_cpu offline grp_uuid
328 b0b8337a Dato Simó
                spindles -}
329 a604456d Iustin Pop
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
330 b0b8337a Dato Simó
  {- instance file: name mem disk vcpus status auto_bal pnode snode
331 b0b8337a Dato Simó
                    disk_template tags spindle_use -}
332 a604456d Iustin Pop
  (_, il) <- loadTabular ilines (loadInst ktn)
333 afcd5a0b Iustin Pop
  {- the tags are simply line-based, no processing needed -}
334 b37f4a76 Iustin Pop
  {- process policies -}
335 b37f4a76 Iustin Pop
  (cpol, gl') <- loadAllIPolicies gl pollines
336 b37f4a76 Iustin Pop
  return (ClusterData gl' nl il ctags cpol)
337 dadfc261 Iustin Pop
338 525bfb36 Iustin Pop
-- | Top level function for data loading.
339 dadfc261 Iustin Pop
loadData :: String -- ^ Path to the text file
340 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
341 2a8e2dc9 Iustin Pop
loadData = fmap parseData . readData