Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Text.hs @ 28f19313

History | View | Annotate | Download (7.1 kB)

1 040afc35 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 a8946537 Iustin Pop
files, as produced by gnt-node and gnt-instance list.
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 b2278348 Iustin Pop
    (
31 b2278348 Iustin Pop
      loadData
32 dadfc261 Iustin Pop
    , parseData
33 1ae7a904 Iustin Pop
    , loadInst
34 39d11971 Iustin Pop
    , loadNode
35 3bf75b7d Iustin Pop
    , serializeInstances
36 50811e2c Iustin Pop
    , serializeNode
37 3bf75b7d Iustin Pop
    , serializeNodes
38 4a273e97 Iustin Pop
    , serializeCluster
39 b2278348 Iustin Pop
    ) where
40 040afc35 Iustin Pop
41 040afc35 Iustin Pop
import Control.Monad
42 3bf75b7d Iustin Pop
import Data.List
43 3bf75b7d Iustin Pop
44 3bf75b7d Iustin Pop
import Text.Printf (printf)
45 040afc35 Iustin Pop
46 040afc35 Iustin Pop
import Ganeti.HTools.Utils
47 040afc35 Iustin Pop
import Ganeti.HTools.Loader
48 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
49 3bf75b7d Iustin Pop
import qualified Ganeti.HTools.Container as Container
50 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
51 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
52 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
53 040afc35 Iustin Pop
54 e4d8071d Iustin Pop
-- | Serialize a single group
55 e4d8071d Iustin Pop
serializeGroup :: Group.Group -> String
56 e4d8071d Iustin Pop
serializeGroup grp =
57 f4c7d37a Iustin Pop
    printf "%s|%s|%s" (Group.name grp) (Group.uuid grp)
58 f4c7d37a Iustin Pop
               (apolToString (Group.allocPolicy grp))
59 e4d8071d Iustin Pop
60 e4d8071d Iustin Pop
-- | Generate group file data from a group list
61 e4d8071d Iustin Pop
serializeGroups :: Group.List -> String
62 e4d8071d Iustin Pop
serializeGroups = unlines . map serializeGroup . Container.elems
63 e4d8071d Iustin Pop
64 3bf75b7d Iustin Pop
-- | Serialize a single node
65 10ef6b4e Iustin Pop
serializeNode :: Group.List -> Node.Node -> String
66 10ef6b4e Iustin Pop
serializeNode gl node =
67 b3707354 Iustin Pop
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
68 3bf75b7d Iustin Pop
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
69 3bf75b7d Iustin Pop
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
70 3bf75b7d Iustin Pop
               (if Node.offline node then 'Y' else 'N')
71 10ef6b4e Iustin Pop
               (Group.uuid grp)
72 10ef6b4e Iustin Pop
    where grp = Container.find (Node.group node) gl
73 3bf75b7d Iustin Pop
74 3bf75b7d Iustin Pop
-- | Generate node file data from node objects
75 10ef6b4e Iustin Pop
serializeNodes :: Group.List -> Node.List -> String
76 10ef6b4e Iustin Pop
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
77 3bf75b7d Iustin Pop
78 3bf75b7d Iustin Pop
-- | Serialize a single instance
79 3bf75b7d Iustin Pop
serializeInstance :: Node.List -> Instance.Instance -> String
80 3bf75b7d Iustin Pop
serializeInstance nl inst =
81 3bf75b7d Iustin Pop
    let
82 3bf75b7d Iustin Pop
        iname = Instance.name inst
83 3bf75b7d Iustin Pop
        pnode = Container.nameOf nl (Instance.pNode inst)
84 3bf75b7d Iustin Pop
        sidx = Instance.sNode inst
85 3bf75b7d Iustin Pop
        snode = (if sidx == Node.noSecondary
86 3bf75b7d Iustin Pop
                    then ""
87 3bf75b7d Iustin Pop
                    else Container.nameOf nl sidx)
88 3bf75b7d Iustin Pop
    in
89 bc782180 Iustin Pop
      printf "%s|%d|%d|%d|%s|%s|%s|%s|%s"
90 3bf75b7d Iustin Pop
             iname (Instance.mem inst) (Instance.dsk inst)
91 3bf75b7d Iustin Pop
             (Instance.vcpus inst) (Instance.runSt inst)
92 bc782180 Iustin Pop
             (if Instance.auto_balance inst then "Y" else "N")
93 3bf75b7d Iustin Pop
             pnode snode (intercalate "," (Instance.tags inst))
94 3bf75b7d Iustin Pop
95 3bf75b7d Iustin Pop
-- | Generate instance file data from instance objects
96 3bf75b7d Iustin Pop
serializeInstances :: Node.List -> Instance.List -> String
97 3bf75b7d Iustin Pop
serializeInstances nl =
98 3bf75b7d Iustin Pop
    unlines . map (serializeInstance nl) . Container.elems
99 3bf75b7d Iustin Pop
100 4a273e97 Iustin Pop
-- | Generate complete cluster data from node and instance lists
101 c0e31451 Iustin Pop
serializeCluster :: ClusterData -> String
102 c0e31451 Iustin Pop
serializeCluster (ClusterData gl nl il ctags) =
103 e4d8071d Iustin Pop
  let gdata = serializeGroups gl
104 e4d8071d Iustin Pop
      ndata = serializeNodes gl nl
105 4a273e97 Iustin Pop
      idata = serializeInstances nl il
106 716c6be5 Iustin Pop
  -- note: not using 'unlines' as that adds too many newlines
107 716c6be5 Iustin Pop
  in intercalate "\n" [gdata, ndata, idata, unlines ctags]
108 4a273e97 Iustin Pop
109 a679e9dc Iustin Pop
-- | Load a group from a field list.
110 a679e9dc Iustin Pop
loadGroup :: (Monad m) => [String] -> m (String, Group.Group)
111 f4c7d37a Iustin Pop
loadGroup [name, gid, apol] = do
112 f4c7d37a Iustin Pop
  xapol <- apolFromString apol
113 d5072e4c Iustin Pop
  return (gid, Group.create name gid xapol)
114 a679e9dc Iustin Pop
115 a679e9dc Iustin Pop
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
116 a679e9dc Iustin Pop
117 9188aeef Iustin Pop
-- | Load a node from a field list.
118 10ef6b4e Iustin Pop
loadNode :: (Monad m) => NameAssoc -> [String] -> m (String, Node.Node)
119 10ef6b4e Iustin Pop
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
120 10ef6b4e Iustin Pop
  gdx <- lookupGroup ktg name gu
121 040afc35 Iustin Pop
  new_node <-
122 1a82215d Iustin Pop
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
123 10ef6b4e Iustin Pop
          return $ Node.create name 0 0 0 0 0 0 True gdx
124 040afc35 Iustin Pop
      else do
125 040afc35 Iustin Pop
        vtm <- tryRead name tm
126 040afc35 Iustin Pop
        vnm <- tryRead name nm
127 040afc35 Iustin Pop
        vfm <- tryRead name fm
128 040afc35 Iustin Pop
        vtd <- tryRead name td
129 040afc35 Iustin Pop
        vfd <- tryRead name fd
130 1a82215d Iustin Pop
        vtc <- tryRead name tc
131 10ef6b4e Iustin Pop
        return $ Node.create name vtm vnm vfm vtd vfd vtc False gdx
132 040afc35 Iustin Pop
  return (name, new_node)
133 10ef6b4e Iustin Pop
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
134 040afc35 Iustin Pop
135 9188aeef Iustin Pop
-- | Load an instance from a field list.
136 040afc35 Iustin Pop
loadInst :: (Monad m) =>
137 6ff78049 Iustin Pop
            NameAssoc -> [String] -> m (String, Instance.Instance)
138 bc782180 Iustin Pop
loadInst ktn [name, mem, dsk, vcpus, status, auto_bal, pnode, snode, tags] = do
139 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
140 040afc35 Iustin Pop
  sidx <- (if null snode then return Node.noSecondary
141 040afc35 Iustin Pop
           else lookupNode ktn name snode)
142 040afc35 Iustin Pop
  vmem <- tryRead name mem
143 040afc35 Iustin Pop
  vdsk <- tryRead name dsk
144 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
145 bc782180 Iustin Pop
  auto_balance <- case auto_bal of
146 bc782180 Iustin Pop
                    "Y" -> return True
147 bc782180 Iustin Pop
                    "N" -> return False
148 bc782180 Iustin Pop
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
149 bc782180 Iustin Pop
                         "' for instance " ++ name
150 040afc35 Iustin Pop
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
151 040afc35 Iustin Pop
           " has same primary and secondary node - " ++ pnode
152 17e7af2b Iustin Pop
  let vtags = sepSplit ',' tags
153 c352b0a9 Iustin Pop
      newinst = Instance.create name vmem vdsk vvcpus status vtags
154 bc782180 Iustin Pop
                auto_balance pidx sidx
155 040afc35 Iustin Pop
  return (name, newinst)
156 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
157 040afc35 Iustin Pop
158 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
159 9188aeef Iustin Pop
--
160 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
161 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
162 9188aeef Iustin Pop
-- a supplied conversion function.
163 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
164 f5197d89 Iustin Pop
               [String] -> ([String] -> m (String, a))
165 99b63608 Iustin Pop
            -> m (NameAssoc, Container.Container a)
166 f5197d89 Iustin Pop
loadTabular lines_data convert_fn = do
167 f5197d89 Iustin Pop
  let rows = map (sepSplit '|') lines_data
168 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
169 497e30a1 Iustin Pop
  return $ assignIndices kerows
170 040afc35 Iustin Pop
171 dadfc261 Iustin Pop
-- | Load the cluser data from disk.
172 dadfc261 Iustin Pop
readData :: String -- ^ Path to the text file
173 dadfc261 Iustin Pop
         -> IO String
174 dadfc261 Iustin Pop
readData = readFile
175 dadfc261 Iustin Pop
176 16c2369c Iustin Pop
-- | Builds the cluster data from text input.
177 dadfc261 Iustin Pop
parseData :: String -- ^ Text data
178 f4f6eb0b Iustin Pop
          -> Result ClusterData
179 dadfc261 Iustin Pop
parseData fdata = do
180 16c2369c Iustin Pop
  let flines = lines fdata
181 afcd5a0b Iustin Pop
  (glines, nlines, ilines, ctags) <-
182 a604456d Iustin Pop
      case sepSplit "" flines of
183 afcd5a0b Iustin Pop
        [a, b, c, d] -> Ok (a, b, c, d)
184 a604456d Iustin Pop
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
185 afcd5a0b Iustin Pop
                           \ instead of 4" (length xs)
186 a679e9dc Iustin Pop
  {- group file: name uuid -}
187 10ef6b4e Iustin Pop
  (ktg, gl) <- loadTabular glines loadGroup
188 dadfc261 Iustin Pop
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
189 a604456d Iustin Pop
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
190 dadfc261 Iustin Pop
  {- instance file: name mem disk status pnode snode -}
191 a604456d Iustin Pop
  (_, il) <- loadTabular ilines (loadInst ktn)
192 afcd5a0b Iustin Pop
  {- the tags are simply line-based, no processing needed -}
193 f4f6eb0b Iustin Pop
  return (ClusterData gl nl il ctags)
194 dadfc261 Iustin Pop
195 dadfc261 Iustin Pop
-- | Top level function for data loading
196 dadfc261 Iustin Pop
loadData :: String -- ^ Path to the text file
197 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
198 2a8e2dc9 Iustin Pop
loadData = fmap parseData . readData