Statistics
| Branch: | Tag: | Revision:

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

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