Further hlint fixes
[ganeti-local] / htools / Ganeti / HTools / Text.hs
index 3334d20..39a568c 100644 (file)
@@ -78,11 +78,12 @@ serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
               -> Node.Node  -- ^ The node to be serialised
               -> String
 serializeNode gl node =
-  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
+  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d" (Node.name node)
            (Node.tMem node) (Node.nMem node) (Node.fMem node)
            (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
            (if Node.offline node then 'Y' else 'N')
            (Group.uuid grp)
+           (Node.spindleCount node)
     where grp = Container.find (Node.group node) gl
 
 -- | Generate node file data from node objects.
@@ -101,12 +102,12 @@ serializeInstance nl inst =
       snode = (if sidx == Node.noSecondary
                  then ""
                  else Container.nameOf nl sidx)
-  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s"
+  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d"
        iname (Instance.mem inst) (Instance.dsk inst)
        (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
        (if Instance.autoBalance inst then "Y" else "N")
        pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
-       (intercalate "," (Instance.tags inst))
+       (intercalate "," (Instance.tags inst)) (Instance.spindleUse inst)
 
 -- | Generate instance file data from instance objects.
 serializeInstances :: Node.List -> Instance.List -> String
@@ -117,8 +118,9 @@ serializeInstances nl =
 serializeISpec :: ISpec -> String
 serializeISpec ispec =
   -- this needs to be kept in sync with the object definition
-  let ISpec mem_s cpu_c disk_s disk_c nic_c = ispec
-      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c]
+  let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec
+      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c,
+                 show su]
   in intercalate "," strings
 
 -- | Generate disk template data.
@@ -128,13 +130,14 @@ serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
 -- | Generate policy data from a given policy object.
 serializeIPolicy :: String -> IPolicy -> String
 serializeIPolicy owner ipol =
-  let IPolicy stdspec minspec maxspec dts vcpu_ratio = ipol
+  let IPolicy stdspec minspec maxspec dts vcpu_ratio spindle_ratio = ipol
       strings = [ owner
                 , serializeISpec stdspec
                 , serializeISpec minspec
                 , serializeISpec maxspec
                 , serializeDiskTemplates dts
                 , show vcpu_ratio
+                , show spindle_ratio
                 ]
   in intercalate "|" strings
 
@@ -143,7 +146,7 @@ serializeIPolicy owner ipol =
 serializeAllIPolicies :: IPolicy -> Group.List -> String
 serializeAllIPolicies cpol gl =
   let groups = Container.elems gl
-      allpolicies = [("", cpol)] ++
+      allpolicies = ("", cpol) :
                     map (\g -> (Group.name g, Group.iPolicy g)) groups
       strings = map (uncurry serializeIPolicy) allpolicies
   in unlines strings
@@ -176,11 +179,11 @@ loadNode :: (Monad m) =>
          -> [String]              -- ^ Input data as a list of fields
          -> m (String, Node.Node) -- ^ The result, a tuple o node name
                                   -- and node object
-loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
+loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] = do
   gdx <- lookupGroup ktg name gu
   new_node <-
-      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
-          return $ Node.create name 0 0 0 0 0 0 True gdx
+      if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then
+          return $ Node.create name 0 0 0 0 0 0 True 0 gdx
       else do
         vtm <- tryRead name tm
         vnm <- tryRead name nm
@@ -188,8 +191,13 @@ loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] = do
         vtd <- tryRead name td
         vfd <- tryRead name fd
         vtc <- tryRead name tc
-        return $ Node.create name vtm vnm vfm vtd vfd vtc False gdx
+        vspindles <- tryRead name spindles
+        return $ Node.create name vtm vnm vfm vtd vfd vtc False vspindles gdx
   return (name, new_node)
+
+loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
+  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
+
 loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
 
 -- | Load an instance from a field list.
@@ -199,7 +207,7 @@ loadInst :: NameAssoc -- ^ Association list with the current nodes
                                                -- instance name and
                                                -- the instance object
 loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
-             , dt, tags ] = do
+             , dt, tags, su ] = do
   pidx <- lookupNode ktn name pnode
   sidx <- if null snode
             then return Node.noSecondary
@@ -215,34 +223,44 @@ loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
                          "' for instance " ++ name
   disk_template <- annotateResult ("Instance " ++ name)
                    (diskTemplateFromRaw dt)
-  when (sidx == pidx) $ fail $ "Instance " ++ name ++
+  spindle_use <- tryRead name su
+  when (sidx == pidx) . fail $ "Instance " ++ name ++
            " has same primary and secondary node - " ++ pnode
   let vtags = commaSplit tags
       newinst = Instance.create name vmem vdsk vvcpus vstatus vtags
-                auto_balance pidx sidx disk_template
+                auto_balance pidx sidx disk_template spindle_use
   return (name, newinst)
+
+loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
+             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
+                                           auto_bal, pnode, snode, dt, tags,
+                                           "1" ]
 loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
 
 -- | Loads a spec from a field list.
 loadISpec :: String -> [String] -> Result ISpec
-loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c] = do
+loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
   xmem_s <- tryRead (owner ++ "/memsize") mem_s
   xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
   xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
   xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
   xnic_c <- tryRead (owner ++ "/niccount") nic_c
-  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c
+  xsu    <- tryRead (owner ++ "/spindleuse") su
+  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
 loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
 
 -- | Loads an ipolicy from a field list.
 loadIPolicy :: [String] -> Result (String, IPolicy)
-loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates, vcpu_ratio] = do
+loadIPolicy [owner, stdspec, minspec, maxspec, dtemplates,
+             vcpu_ratio, spindle_ratio] = do
   xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
   xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
   xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
   xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
   xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
-  return $ (owner, IPolicy xstdspec xminspec xmaxspec xdts xvcpu_ratio)
+  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
+  return (owner,
+          IPolicy xstdspec xminspec xmaxspec xdts xvcpu_ratio xspindle_ratio)
 loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
 
 loadOnePolicy :: (IPolicy, Group.List) -> String