htools: read the disk template in Luxi and Rapi
[ganeti-local] / htools / Ganeti / HTools / Text.hs
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                (apolToString (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"
97              iname (Instance.mem inst) (Instance.dsk inst)
98              (Instance.vcpus inst) (Instance.runSt inst)
99              (if Instance.autoBalance inst then "Y" else "N")
100              pnode snode (intercalate "," (Instance.tags inst))
101
102 -- | Generate instance file data from instance objects.
103 serializeInstances :: Node.List -> Instance.List -> String
104 serializeInstances nl =
105     unlines . map (serializeInstance nl) . Container.elems
106
107 -- | Generate complete cluster data from node and instance lists.
108 serializeCluster :: ClusterData -> String
109 serializeCluster (ClusterData gl nl il ctags) =
110   let gdata = serializeGroups gl
111       ndata = serializeNodes gl nl
112       idata = serializeInstances nl il
113   -- note: not using 'unlines' as that adds too many newlines
114   in intercalate "\n" [gdata, ndata, idata, unlines ctags]
115
116 -- * Parsing functions
117
118 -- | Load a group from a field list.
119 loadGroup :: (Monad m) => [String]
120           -> m (String, Group.Group) -- ^ The result, a tuple of group
121                                      -- UUID and group object
122 loadGroup [name, gid, apol] = do
123   xapol <- apolFromString apol
124   return (gid, Group.create name gid xapol)
125
126 loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
127
128 -- | Load a node from a field list.
129 loadNode :: (Monad m) =>
130             NameAssoc             -- ^ Association list with current groups
131          -> [String]              -- ^ Input data as a list of fields
132          -> m (String, Node.Node) -- ^ The result, a tuple o node name
133                                   -- and node object
134 loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
135   gdx <- lookupGroup ktg name gu
136   new_node <-
137       if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
138           return $ Node.create name 0 0 0 0 0 0 True gdx
139       else do
140         vtm <- tryRead name tm
141         vnm <- tryRead name nm
142         vfm <- tryRead name fm
143         vtd <- tryRead name td
144         vfd <- tryRead name fd
145         vtc <- tryRead name tc
146         return $ Node.create name vtm vnm vfm vtd vfd vtc False gdx
147   return (name, new_node)
148 loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
149
150 -- | Load an instance from a field list.
151 loadInst :: (Monad m) =>
152             NameAssoc                     -- ^ Association list with
153                                           -- the current nodes
154          -> [String]                      -- ^ Input data as a list of
155                                           -- fields
156          -> m (String, Instance.Instance) -- ^ The result, a tuple of
157                                           -- instance name and the
158                                           -- instance object
159 loadInst ktn [name, mem, dsk, vcpus, status, auto_bal, pnode, snode, tags] = do
160   pidx <- lookupNode ktn name pnode
161   sidx <- (if null snode then return Node.noSecondary
162            else lookupNode ktn name snode)
163   vmem <- tryRead name mem
164   vdsk <- tryRead name dsk
165   vvcpus <- tryRead name vcpus
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   when (sidx == pidx) $ fail $ "Instance " ++ name ++
172            " has same primary and secondary node - " ++ pnode
173   let vtags = sepSplit ',' tags
174       newinst = Instance.create name vmem vdsk vvcpus status vtags
175                 auto_balance pidx sidx DTDrbd8
176   return (name, newinst)
177 loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
178
179 -- | Convert newline and delimiter-separated text.
180 --
181 -- This function converts a text in tabular format as generated by
182 -- @gnt-instance list@ and @gnt-node list@ to a list of objects using
183 -- a supplied conversion function.
184 loadTabular :: (Monad m, Element a) =>
185                [String] -- ^ Input data, as a list of lines
186             -> ([String] -> m (String, a)) -- ^ Conversion function
187             -> m ( NameAssoc
188                  , Container.Container a ) -- ^ A tuple of an
189                                            -- association list (name
190                                            -- to object) and a set as
191                                            -- used in
192                                            -- "Ganeti.HTools.Container"
193
194 loadTabular lines_data convert_fn = do
195   let rows = map (sepSplit '|') lines_data
196   kerows <- mapM convert_fn rows
197   return $ assignIndices kerows
198
199 -- | Load the cluser data from disk.
200 --
201 -- This is an alias to 'readFile' just for consistency with the other
202 -- modules.
203 readData :: String    -- ^ Path to the text file
204          -> IO String -- ^ Contents of the file
205 readData = readFile
206
207 -- | Builds the cluster data from text input.
208 parseData :: String -- ^ Text data
209           -> Result ClusterData
210 parseData fdata = do
211   let flines = lines fdata
212   (glines, nlines, ilines, ctags) <-
213       case sepSplit "" flines of
214         [a, b, c, d] -> Ok (a, b, c, d)
215         xs -> Bad $ printf "Invalid format of the input file: %d sections\
216                            \ instead of 4" (length xs)
217   {- group file: name uuid -}
218   (ktg, gl) <- loadTabular glines loadGroup
219   {- node file: name t_mem n_mem f_mem t_disk f_disk -}
220   (ktn, nl) <- loadTabular nlines (loadNode ktg)
221   {- instance file: name mem disk status pnode snode -}
222   (_, il) <- loadTabular ilines (loadInst ktn)
223   {- the tags are simply line-based, no processing needed -}
224   return (ClusterData gl nl il ctags)
225
226 -- | Top level function for data loading.
227 loadData :: String -- ^ Path to the text file
228          -> IO (Result ClusterData)
229 loadData = fmap parseData . readData