Revision 94e05c32

b/Ganeti/HTools/ExtLoader.hs
83 83

  
84 84
-- | External tool data loader from a variety of sources.
85 85
loadExternalData :: Options
86
                 -> IO (Node.List, Instance.List, String)
86
                 -> IO (Node.List, Instance.List, [String], String)
87 87
loadExternalData opts = do
88 88
  (env_node, env_inst) <- parseEnv ()
89 89
  let nodef = if optNodeSet opts then optNodeFile opts
......
131 131
          | otherwise -> wrapIO $ Text.loadData nodef instf
132 132

  
133 133
  let ldresult = input_data >>= Loader.mergeData util_data' exTags
134
  (loaded_nl, il, csf) <-
134
  (loaded_nl, il, tags, csf) <-
135 135
      (case ldresult of
136 136
         Ok x -> return x
137 137
         Bad s -> do
......
144 144
         hPutStrLn stderr "Warning: cluster has inconsistent data:"
145 145
         hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
146 146

  
147
  return (fixed_nl, il, csf)
147
  return (fixed_nl, il, tags, csf)
b/Ganeti/HTools/IAlloc.hs
110 110
  iobj <- mapM (\(x,y) ->
111 111
                    asJSObject y >>= parseInstance ktn x . fromJSObject) idata
112 112
  let (kti, il) = assignIndices iobj
113
  (map_n, map_i, csf) <- mergeData [] [] (nl, il)
113
  (map_n, map_i, _, csf) <- mergeData [] [] (nl, il, [])
114 114
  req_nodes <- fromObj "required_nodes" request
115 115
  optype <- fromObj "type" request
116 116
  rqtype <-
b/Ganeti/HTools/Loader.hs
140 140
-- list and massages it into the correct format.
141 141
mergeData :: [(String, DynUtil)]  -- ^ Instance utilisation data
142 142
          -> [String]             -- ^ Exclusion tags
143
          -> (Node.AssocList,
144
              Instance.AssocList) -- ^ Data from either Text.loadData
145
                                  -- or Rapi.loadData
146
          -> Result (Node.List, Instance.List, String)
147
mergeData um extags (nl, il) =
143
          -> (Node.AssocList, Instance.AssocList, [String])
144
          -- ^ Data from backends
145
          -> Result (Node.List, Instance.List, [String], String)
146
mergeData um extags (nl, il, tags) =
148 147
  let il2 = Container.fromAssocList il
149 148
      il3 = foldl' (\im (name, n_util) ->
150 149
                        case Container.findByName im name of
......
163 162
      csl = length common_suffix
164 163
      snl = Container.map (\n -> setName n (stripSuffix csl $ nameOf n)) nl3
165 164
      sil = Container.map (\i -> setName i (stripSuffix csl $ nameOf i)) il4
166
  in Ok (snl, sil, common_suffix)
165
  in Ok (snl, sil, tags, common_suffix)
167 166

  
168 167
-- | Checks the cluster data for consistency.
169 168
checkData :: Node.List -> Instance.List
b/Ganeti/HTools/Luxi.hs
144 144

  
145 145
-- | Builds the cluster data from an URL.
146 146
loadData :: String -- ^ Unix socket to use as source
147
         -> IO (Result (Node.AssocList, Instance.AssocList))
147
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
148 148
loadData master =
149 149
  E.bracket
150 150
       (L.getClient master)
......
157 157
            let (node_names, node_idx) = assignIndices node_data
158 158
            inst_data <- instances >>= getInstances node_names
159 159
            let (_, inst_idx) = assignIndices inst_data
160
            return (node_idx, inst_idx)
160
            return (node_idx, inst_idx, [])
161 161
       )
b/Ganeti/HTools/Rapi.hs
114 114

  
115 115
-- | Builds the cluster data from an URL.
116 116
loadData :: String -- ^ Cluster or URL to use as source
117
         -> IO (Result (Node.AssocList, Instance.AssocList))
117
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
118 118
loadData master = do -- IO monad
119 119
  let url = formatHost master
120 120
  node_body <- getUrl $ printf "%s/2/nodes?bulk=1" url
......
124 124
    let (node_names, node_idx) = assignIndices node_data
125 125
    inst_data <- inst_body >>= getInstances node_names
126 126
    let (_, inst_idx) = assignIndices inst_data
127
    return (node_idx, inst_idx)
127
    return (node_idx, inst_idx, [])
b/Ganeti/HTools/Simu.hs
52 52

  
53 53
-- | Builds the cluster data from node\/instance files.
54 54
loadData :: String -- ^ Cluster description in text format
55
         -> IO (Result (Node.AssocList, Instance.AssocList))
55
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
56 56
loadData ndata = -- IO monad, just for consistency with the other loaders
57 57
  return $ do
58 58
    (cnt, disk, mem, cpu) <- parseDesc ndata
......
63 63
                                 (fromIntegral cpu) False
64 64
                         in (idx, Node.setIdx n idx)
65 65
                    ) [1..cnt]
66
    return (nodes, [])
66
    return (nodes, [], [])
b/Ganeti/HTools/Text.hs
91 91
-- | Builds the cluster data from node\/instance files.
92 92
loadData :: String -- ^ Node data in string format
93 93
         -> String -- ^ Instance data in string format
94
         -> IO (Result (Node.AssocList, Instance.AssocList))
94
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
95 95
loadData nfile ifile = do -- IO monad
96 96
  ndata <- readFile nfile
97 97
  idata <- readFile ifile
......
100 100
    (ktn, nl) <- loadTabular ndata loadNode
101 101
    {- instance file: name mem disk status pnode snode -}
102 102
    (_, il) <- loadTabular idata (loadInst ktn)
103
    return (nl, il)
103
    return (nl, il, [])
b/hbal.hs
187 187
      verbose = optVerbose opts
188 188
      shownodes = optShowNodes opts
189 189

  
190
  (fixed_nl, il, csf) <- loadExternalData opts
190
  (fixed_nl, il, _, csf) <- loadExternalData opts
191 191

  
192 192
  let offline_names = optOffline opts
193 193
      all_nodes = Container.elems fixed_nl
b/hscan.hs
142 142
                 Bad err -> printf "\nError: failed to load data. \
143 143
                                   \Details:\n%s\n" err
144 144
                 Ok x -> do
145
                   let (nl, il, csf) = x
145
                   let (nl, il, _, csf) = x
146 146
                       (_, fix_nl) = Loader.checkData nl il
147 147
                   putStrLn $ printCluster fix_nl il
148 148
                   when (isJust shownodes) $
b/hspace.hs
216 216
      ispec = optISpec opts
217 217
      shownodes = optShowNodes opts
218 218

  
219
  (fixed_nl, il, csf) <- loadExternalData opts
219
  (fixed_nl, il, _, csf) <- loadExternalData opts
220 220

  
221 221
  printKeys $ map (\(a, fn) -> ("SPEC_" ++ a, fn ispec)) specData
222 222
  printKeys [ ("SPEC_RQN", printf "%d" (optINodes opts)) ]

Also available in: Unified diff