Remove unsafePerformIO usage
[ganeti-local] / htools / Ganeti / HTools / Program / Hspace.hs
index c7fcfde..d1b62c3 100644 (file)
@@ -23,15 +23,18 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 
 -}
 
-module Ganeti.HTools.Program.Hspace (main, options) where
+module Ganeti.HTools.Program.Hspace
+  (main
+  , options
+  , arguments
+  ) where
 
 import Control.Monad
-import Data.Char (toUpper, isAlphaNum, toLower)
+import Data.Char (toUpper, toLower)
 import Data.Function (on)
 import Data.List
 import Data.Maybe (fromMaybe)
 import Data.Ord (comparing)
-import System.Exit
 import System.IO
 
 import Text.Printf (printf, hPrintf)
@@ -41,36 +44,42 @@ import qualified Ganeti.HTools.Cluster as Cluster
 import qualified Ganeti.HTools.Node as Node
 import qualified Ganeti.HTools.Instance as Instance
 
-import Ganeti.HTools.Utils
+import Ganeti.BasicTypes
+import Ganeti.Common
 import Ganeti.HTools.Types
 import Ganeti.HTools.CLI
 import Ganeti.HTools.ExtLoader
 import Ganeti.HTools.Loader
+import Ganeti.Utils
 
 -- | Options list and functions.
-options :: [OptType]
-options =
-  [ oPrintNodes
-  , oDataFile
-  , oDiskTemplate
-  , oSpindleUse
-  , oNodeSim
-  , oRapiMaster
-  , oLuxiSocket
-  , oIAllocSrc
-  , oVerbose
-  , oQuiet
-  , oOfflineNode
-  , oMachineReadable
-  , oMaxCpu
-  , oMaxSolLength
-  , oMinDisk
-  , oStdSpec
-  , oTieredSpec
-  , oSaveCluster
-  , oShowVer
-  , oShowHelp
-  ]
+options :: IO [OptType]
+options = do
+  luxi <- oLuxiSocket
+  return
+    [ oPrintNodes
+    , oDataFile
+    , oDiskTemplate
+    , oSpindleUse
+    , oNodeSim
+    , oRapiMaster
+    , luxi
+    , oIAllocSrc
+    , oVerbose
+    , oQuiet
+    , oOfflineNode
+    , oMachineReadable
+    , oMaxCpu
+    , oMaxSolLength
+    , oMinDisk
+    , oStdSpec
+    , oTieredSpec
+    , oSaveCluster
+    ]
+
+-- | The list of arguments supported by the program.
+arguments :: [ArgCompletion]
+arguments = []
 
 -- | The allocation phase we're in (initial, after tiered allocs, or
 -- after regular allocation).
@@ -82,6 +91,10 @@ data Phase = PInitial
 data SpecType = SpecNormal
               | SpecTiered
 
+-- | Prefix for machine readable names
+htsPrefix :: String
+htsPrefix = "HTS"
+
 -- | What we prefix a spec with.
 specPrefix :: SpecType -> String
 specPrefix SpecNormal = "SPEC"
@@ -111,7 +124,7 @@ cpuEff :: Cluster.CStats -> Double
 cpuEff = effFn Cluster.csIcpu (fromIntegral . Cluster.csVcpu)
 
 -- | Holds data for converting a 'Cluster.CStats' structure into
--- detailed statictics.
+-- detailed statistics.
 statsData :: [(String, Cluster.CStats -> String)]
 statsData = [ ("SCORE", printf "%.8f" . Cluster.csScore)
             , ("INST_CNT", printf "%d" . Cluster.csNinst)
@@ -173,22 +186,20 @@ printResults True _ fin_nl num_instances allocs sreason = do
   let fin_stats = Cluster.totalResources fin_nl
       fin_instances = num_instances + allocs
 
-  when (num_instances + allocs /= Cluster.csNinst fin_stats) $
-       do
-         hPrintf stderr "ERROR: internal inconsistency, allocated (%d)\
-                        \ != counted (%d)\n" (num_instances + allocs)
-                                 (Cluster.csNinst fin_stats) :: IO ()
-         exitWith $ ExitFailure 1
-
-  printKeys $ printStats PFinal fin_stats
-  printKeys [ ("ALLOC_USAGE", printf "%.8f"
-                                ((fromIntegral num_instances::Double) /
-                                 fromIntegral fin_instances))
-            , ("ALLOC_INSTANCES", printf "%d" allocs)
-            , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
-            ]
-  printKeys $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
-                               printf "%d" y)) sreason
+  exitWhen (num_instances + allocs /= Cluster.csNinst fin_stats) $
+           printf "internal inconsistency, allocated (%d)\
+                  \ != counted (%d)\n" (num_instances + allocs)
+           (Cluster.csNinst fin_stats)
+
+  printKeysHTS $ printStats PFinal fin_stats
+  printKeysHTS [ ("ALLOC_USAGE", printf "%.8f"
+                                   ((fromIntegral num_instances::Double) /
+                                   fromIntegral fin_instances))
+               , ("ALLOC_INSTANCES", printf "%d" allocs)
+               , ("ALLOC_FAIL_REASON", map toUpper . show . fst $ head sreason)
+               ]
+  printKeysHTS $ map (\(x, y) -> (printf "ALLOC_%s_CNT" (show x),
+                                  printf "%d" y)) sreason
 
 printResults False ini_nl fin_nl _ allocs sreason = do
   putStrLn "Normal (fixed-size) allocation results:"
@@ -196,12 +207,8 @@ printResults False ini_nl fin_nl _ allocs sreason = do
   printFRScores ini_nl fin_nl sreason
 
 -- | Prints the final @OK@ marker in machine readable output.
-printFinal :: Bool -> IO ()
-printFinal True =
-  -- this should be the final entry
-  printKeys [("OK", "1")]
-
-printFinal False = return ()
+printFinalHTS :: Bool -> IO ()
+printFinalHTS = printFinal htsPrefix
 
 -- | Compute the tiered spec counts from a list of allocated
 -- instances.
@@ -235,20 +242,13 @@ printAllocationStats ini_nl fin_nl = do
   let ini_stats = Cluster.totalResources ini_nl
       fin_stats = Cluster.totalResources fin_nl
       (rini, ralo, runa) = Cluster.computeAllocationDelta ini_stats fin_stats
-  printKeys $ formatRSpec "USED" rini
-  printKeys $ formatRSpec "POOL" ralo
-  printKeys $ formatRSpec "UNAV" runa
-
--- | Ensure a value is quoted if needed.
-ensureQuoted :: String -> String
-ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
-                 then '\'':v ++ "'"
-                 else v
+  printKeysHTS $ formatRSpec "USED" rini
+  printKeysHTS $ formatRSpec "POOL" ralo
+  printKeysHTS $ formatRSpec "UNAV" runa
 
 -- | Format a list of key\/values as a shell fragment.
-printKeys :: [(String, String)] -> IO ()
-printKeys = mapM_ (\(k, v) ->
-                   printf "HTS_%s=%s\n" (map toUpper k) (ensureQuoted v))
+printKeysHTS :: [(String, String)] -> IO ()
+printKeysHTS = printKeys htsPrefix
 
 -- | Converts instance data to a list of strings.
 printInstance :: Node.List -> Instance.Instance -> [String]
@@ -283,9 +283,9 @@ formatResources res =
 -- | Print the cluster resources.
 printCluster :: Bool -> Cluster.CStats -> Int -> IO ()
 printCluster True ini_stats node_count = do
-  printKeys $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
-  printKeys [("CLUSTER_NODES", printf "%d" node_count)]
-  printKeys $ printStats PInitial ini_stats
+  printKeysHTS $ map (\(a, fn) -> ("CLUSTER_" ++ a, fn ini_stats)) clusterData
+  printKeysHTS [("CLUSTER_NODES", printf "%d" node_count)]
+  printKeysHTS $ printStats PInitial ini_stats
 
 printCluster False ini_stats node_count = do
   printf "The cluster has %d nodes and the following resources:\n  %s.\n"
@@ -297,10 +297,10 @@ printCluster False ini_stats node_count = do
 -- | Prints the normal instance spec.
 printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
 printISpec True ispec spec disk_template = do
-  printKeys $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
-  printKeys [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
-  printKeys [ (prefix ++ "_DISK_TEMPLATE",
-               diskTemplateToRaw disk_template) ]
+  printKeysHTS $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
+  printKeysHTS [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
+  printKeysHTS [ (prefix ++ "_DISK_TEMPLATE",
+                  diskTemplateToRaw disk_template) ]
       where req_nodes = Instance.requiredNodes disk_template
             prefix = specPrefix spec
 
@@ -314,8 +314,8 @@ printISpec False ispec spec disk_template =
 printTiered :: Bool -> [(RSpec, Int)]
             -> Node.List -> Node.List -> [(FailMode, Int)] -> IO ()
 printTiered True spec_map nl trl_nl _ = do
-  printKeys $ printStats PTiered (Cluster.totalResources trl_nl)
-  printKeys [("TSPEC", unwords (formatSpecMap spec_map))]
+  printKeysHTS $ printStats PTiered (Cluster.totalResources trl_nl)
+  printKeysHTS [("TSPEC", unwords (formatSpecMap spec_map))]
   printAllocationStats nl trl_nl
 
 printTiered False spec_map ini_nl fin_nl sreason = do
@@ -350,12 +350,6 @@ failureReason = show . fst . head
 sortReasons :: [(FailMode, Int)] -> [(FailMode, Int)]
 sortReasons = reverse . sortBy (comparing snd)
 
--- | Aborts the program if we get a bad value.
-exitIfBad :: Result a -> IO a
-exitIfBad (Bad s) =
-  hPrintf stderr "Failure: %s\n" s >> exitWith (ExitFailure 1)
-exitIfBad (Ok v) = return v
-
 -- | Runs an allocation algorithm and saves cluster state.
 runAllocation :: ClusterData                -- ^ Cluster data
               -> Maybe Cluster.AllocResult  -- ^ Optional stop-allocation
@@ -369,7 +363,7 @@ runAllocation cdata stop_allocation actual_result spec dt mode opts = do
   (reasons, new_nl, new_il, new_ixes, _) <-
       case stop_allocation of
         Just result_noalloc -> return result_noalloc
-        Nothing -> exitIfBad actual_result
+        Nothing -> exitIfBad "failure during allocation" actual_result
 
   let name = head . words . specDescription $ mode
       descr = name ++ " allocation"
@@ -388,16 +382,14 @@ runAllocation cdata stop_allocation actual_result spec dt mode opts = do
 
 -- | Create an instance from a given spec.
 instFromSpec :: RSpec -> DiskTemplate -> Int -> Instance.Instance
-instFromSpec spx disk_template su =
+instFromSpec spx =
   Instance.create "new" (rspecMem spx) (rspecDsk spx)
-    (rspecCpu spx) Running [] True (-1) (-1) disk_template su
+    (rspecCpu spx) Running [] True (-1) (-1)
 
 -- | Main function.
 main :: Options -> [String] -> IO ()
 main opts args = do
-  unless (null args) $ do
-         hPutStrLn stderr "Error: this program doesn't take any arguments."
-         exitWith $ ExitFailure 1
+  exitUnless (null args) "This program doesn't take any arguments."
 
   let verbose = optVerbose opts
       machine_r = optMachineReadable opts
@@ -408,10 +400,7 @@ main opts args = do
   cluster_disk_template <-
     case iPolicyDiskTemplates ipol of
       first_templ:_ -> return first_templ
-      _ -> do
-         _ <- hPutStrLn stderr $ "Error: null list of disk templates\
-                               \ received from cluster!"
-         exitWith $ ExitFailure 1
+      _ -> exitErr "null list of disk templates received from cluster"
 
   let num_instances = Container.size il
       all_nodes = Container.elems fixed_nl
@@ -440,7 +429,8 @@ main opts args = do
                    then Nothing
                    else Just (optMaxLength opts)
 
-  allocnodes <- exitIfBad $ Cluster.genAllocNodes gl nl req_nodes True
+  allocnodes <- exitIfBad "failure during allocation" $
+                Cluster.genAllocNodes gl nl req_nodes True
 
   -- Run the tiered allocation
 
@@ -470,4 +460,4 @@ main opts args = do
 
   -- Print final result
 
-  printFinal machine_r
+  printFinalHTS machine_r