Revision 525bfb36 htools/Ganeti/HTools/Text.hs

b/htools/Ganeti/HTools/Text.hs
1
{-| Parsing data from text-files
1
{-| Parsing data from text-files.
2 2

  
3 3
This module holds the code for loading the cluster state from text
4
files, as produced by gnt-node and gnt-instance list.
4
files, as produced by @gnt-node@ and @gnt-instance@ @list@ command.
5 5

  
6 6
-}
7 7

  
......
51 51
import qualified Ganeti.HTools.Node as Node
52 52
import qualified Ganeti.HTools.Instance as Instance
53 53

  
54
-- | Serialize a single group
54
-- * Serialisation functions
55

  
56
-- | Serialize a single group.
55 57
serializeGroup :: Group.Group -> String
56 58
serializeGroup grp =
57 59
    printf "%s|%s|%s" (Group.name grp) (Group.uuid grp)
58 60
               (apolToString (Group.allocPolicy grp))
59 61

  
60
-- | Generate group file data from a group list
62
-- | Generate group file data from a group list.
61 63
serializeGroups :: Group.List -> String
62 64
serializeGroups = unlines . map serializeGroup . Container.elems
63 65

  
64
-- | Serialize a single node
65
serializeNode :: Group.List -> Node.Node -> String
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
66 70
serializeNode gl node =
67 71
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
68 72
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
......
71 75
               (Group.uuid grp)
72 76
    where grp = Container.find (Node.group node) gl
73 77

  
74
-- | Generate node file data from node objects
78
-- | Generate node file data from node objects.
75 79
serializeNodes :: Group.List -> Node.List -> String
76 80
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
77 81

  
78
-- | Serialize a single instance
79
serializeInstance :: Node.List -> Instance.Instance -> String
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
80 87
serializeInstance nl inst =
81 88
    let
82 89
        iname = Instance.name inst
......
92 99
             (if Instance.auto_balance inst then "Y" else "N")
93 100
             pnode snode (intercalate "," (Instance.tags inst))
94 101

  
95
-- | Generate instance file data from instance objects
102
-- | Generate instance file data from instance objects.
96 103
serializeInstances :: Node.List -> Instance.List -> String
97 104
serializeInstances nl =
98 105
    unlines . map (serializeInstance nl) . Container.elems
99 106

  
100
-- | Generate complete cluster data from node and instance lists
107
-- | Generate complete cluster data from node and instance lists.
101 108
serializeCluster :: ClusterData -> String
102 109
serializeCluster (ClusterData gl nl il ctags) =
103 110
  let gdata = serializeGroups gl
......
106 113
  -- note: not using 'unlines' as that adds too many newlines
107 114
  in intercalate "\n" [gdata, ndata, idata, unlines ctags]
108 115

  
116
-- * Parsing functions
117

  
109 118
-- | Load a group from a field list.
110
loadGroup :: (Monad m) => [String] -> m (String, Group.Group)
119
loadGroup :: (Monad m) => [String]
120
          -> m (String, Group.Group) -- ^ The result, a tuple of group
121
                                     -- UUID and group object
111 122
loadGroup [name, gid, apol] = do
112 123
  xapol <- apolFromString apol
113 124
  return (gid, Group.create name gid xapol)
......
115 126
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
116 127

  
117 128
-- | Load a node from a field list.
118
loadNode :: (Monad m) => NameAssoc -> [String] -> m (String, Node.Node)
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
119 134
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
120 135
  gdx <- lookupGroup ktg name gu
121 136
  new_node <-
......
134 149

  
135 150
-- | Load an instance from a field list.
136 151
loadInst :: (Monad m) =>
137
            NameAssoc -> [String] -> m (String, Instance.Instance)
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
138 159
loadInst ktn [name, mem, dsk, vcpus, status, auto_bal, pnode, snode, tags] = do
139 160
  pidx <- lookupNode ktn name pnode
140 161
  sidx <- (if null snode then return Node.noSecondary
......
161 182
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
162 183
-- a supplied conversion function.
163 184
loadTabular :: (Monad m, Element a) =>
164
               [String] -> ([String] -> m (String, a))
165
            -> m (NameAssoc, Container.Container 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

  
166 194
loadTabular lines_data convert_fn = do
167 195
  let rows = map (sepSplit '|') lines_data
168 196
  kerows <- mapM convert_fn rows
169 197
  return $ assignIndices kerows
170 198

  
171 199
-- | Load the cluser data from disk.
172
readData :: String -- ^ Path to the text file
173
         -> IO String
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
174 205
readData = readFile
175 206

  
176 207
-- | Builds the cluster data from text input.
......
192 223
  {- the tags are simply line-based, no processing needed -}
193 224
  return (ClusterData gl nl il ctags)
194 225

  
195
-- | Top level function for data loading
226
-- | Top level function for data loading.
196 227
loadData :: String -- ^ Path to the text file
197 228
         -> IO (Result ClusterData)
198 229
loadData = fmap parseData . readData

Also available in: Unified diff