Rework the types used during data loading
[ganeti-local] / 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.
5
6 -}
7
8 {-
9
10 Copyright (C) 2009, 2010 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.Node as Node
51 import qualified Ganeti.HTools.Instance as Instance
52
53 -- | Serialize a single node
54 serializeNode :: Node.Node -> String
55 serializeNode node =
56     printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
57                (Node.tMem node) (Node.nMem node) (Node.fMem node)
58                (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
59                (if Node.offline node then 'Y' else 'N')
60                (Node.group node)
61
62 -- | Generate node file data from node objects
63 serializeNodes :: Node.List -> String
64 serializeNodes = unlines . map serializeNode . Container.elems
65
66 -- | Serialize a single instance
67 serializeInstance :: Node.List -> Instance.Instance -> String
68 serializeInstance nl inst =
69     let
70         iname = Instance.name inst
71         pnode = Container.nameOf nl (Instance.pNode inst)
72         sidx = Instance.sNode inst
73         snode = (if sidx == Node.noSecondary
74                     then ""
75                     else Container.nameOf nl sidx)
76     in
77       printf "%s|%d|%d|%d|%s|%s|%s|%s"
78              iname (Instance.mem inst) (Instance.dsk inst)
79              (Instance.vcpus inst) (Instance.runSt inst)
80              pnode snode (intercalate "," (Instance.tags inst))
81
82 -- | Generate instance file data from instance objects
83 serializeInstances :: Node.List -> Instance.List -> String
84 serializeInstances nl =
85     unlines . map (serializeInstance nl) . Container.elems
86
87 -- | Generate complete cluster data from node and instance lists
88 serializeCluster :: Node.List -> Instance.List -> String
89 serializeCluster nl il =
90   let ndata = serializeNodes nl
91       idata = serializeInstances nl il
92   in ndata ++ ['\n'] ++ idata
93
94 -- | Load a node from a field list.
95 loadNode :: (Monad m) => [String] -> m (String, Node.Node)
96 -- compatibility wrapper for old text files
97 loadNode [name, tm, nm, fm, td, fd, tc, fo] =
98   loadNode [name, tm, nm, fm, td, fd, tc, fo, defaultGroupID]
99 loadNode [name, tm, nm, fm, td, fd, tc, fo, gu] = do
100   new_node <-
101       if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
102           return $ Node.create name 0 0 0 0 0 0 True gu
103       else do
104         vtm <- tryRead name tm
105         vnm <- tryRead name nm
106         vfm <- tryRead name fm
107         vtd <- tryRead name td
108         vfd <- tryRead name fd
109         vtc <- tryRead name tc
110         return $ Node.create name vtm vnm vfm vtd vfd vtc False gu
111   return (name, new_node)
112 loadNode s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
113
114 -- | Load an instance from a field list.
115 loadInst :: (Monad m) =>
116             NameAssoc -> [String] -> m (String, Instance.Instance)
117 loadInst ktn [name, mem, dsk, vcpus, status, pnode, snode, tags] = do
118   pidx <- lookupNode ktn name pnode
119   sidx <- (if null snode then return Node.noSecondary
120            else lookupNode ktn name snode)
121   vmem <- tryRead name mem
122   vdsk <- tryRead name dsk
123   vvcpus <- tryRead name vcpus
124   when (sidx == pidx) $ fail $ "Instance " ++ name ++
125            " has same primary and secondary node - " ++ pnode
126   let vtags = sepSplit ',' tags
127       newinst = Instance.create name vmem vdsk vvcpus status vtags pidx sidx
128   return (name, newinst)
129 loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
130
131 -- | Convert newline and delimiter-separated text.
132 --
133 -- This function converts a text in tabular format as generated by
134 -- @gnt-instance list@ and @gnt-node list@ to a list of objects using
135 -- a supplied conversion function.
136 loadTabular :: (Monad m, Element a) =>
137                [String] -> ([String] -> m (String, a))
138             -> m (NameAssoc, Container.Container a)
139 loadTabular lines_data convert_fn = do
140   let rows = map (sepSplit '|') lines_data
141   kerows <- mapM convert_fn rows
142   return $ assignIndices kerows
143
144 -- | Load the cluser data from disk.
145 readData :: String -- ^ Path to the text file
146          -> IO String
147 readData = readFile
148
149 -- | Builds the cluster data from text input.
150 parseData :: String -- ^ Text data
151           -> Result (Node.List, Instance.List, [String])
152 parseData fdata = do
153   let flines = lines fdata
154       (nlines, ilines) = break null flines
155   ifixed <- case ilines of
156     [] -> Bad "Invalid format of the input file (no instance data)"
157     _:xs -> Ok xs
158   {- node file: name t_mem n_mem f_mem t_disk f_disk -}
159   (ktn, nl) <- loadTabular nlines loadNode
160   {- instance file: name mem disk status pnode snode -}
161   (_, il) <- loadTabular ifixed (loadInst ktn)
162   return (nl, il, [])
163
164 -- | Top level function for data loading
165 loadData :: String -- ^ Path to the text file
166          -> IO (Result (Node.List, Instance.List, [String]))
167 loadData afile = readData afile >>= return . parseData