Replace tempfile by mktemp in QA code
[ganeti-local] / qa / qa_utils.py
index bf4f226..bcef97f 100644 (file)
@@ -1,7 +1,7 @@
 #
 #
 
-# Copyright (C) 2007, 2011 Google Inc.
+# Copyright (C) 2007, 2011, 2012, 2013 Google Inc.
 #
 # This program is free software; you can redistribute it and/or modify
 # it under the terms of the GNU General Public License as published by
 
 """
 
+import copy
+import operator
 import os
+import random
 import re
-import sys
 import subprocess
-import random
+import sys
 import tempfile
+import yaml
 
 try:
   import functools
@@ -39,6 +42,8 @@ from ganeti import utils
 from ganeti import compat
 from ganeti import constants
 from ganeti import ht
+from ganeti import pathutils
+from ganeti import vcluster
 
 import qa_config
 import qa_error
@@ -54,6 +59,9 @@ _MULTIPLEXERS = {}
 #: Unique ID per QA run
 _RUN_UUID = utils.NewUUID()
 
+#: Path to the QA query output log file
+_QA_OUTPUT = pathutils.GetLogFilename("qa-output")
+
 
 (INST_DOWN,
  INST_UP) = range(500, 502)
@@ -117,14 +125,6 @@ def AssertEqual(first, second):
     raise qa_error.Error("%r == %r" % (first, second))
 
 
-def AssertNotEqual(first, second):
-  """Raises an error when values are equal.
-
-  """
-  if not first != second:
-    raise qa_error.Error("%r != %r" % (first, second))
-
-
 def AssertMatch(string, pattern):
   """Raises an error when string doesn't match regexp pattern.
 
@@ -133,21 +133,17 @@ def AssertMatch(string, pattern):
     raise qa_error.Error("%r doesn't match /%r/" % (string, pattern))
 
 
-def _GetName(entity, key):
+def _GetName(entity, fn):
   """Tries to get name of an entity.
 
   @type entity: string or dict
-  @type key: string
-  @param key: Dictionary key containing name
+  @param fn: Function retrieving name from entity
 
   """
   if isinstance(entity, basestring):
     result = entity
-  elif isinstance(entity, dict):
-    result = entity[key]
   else:
-    raise qa_error.Error("Expected string or dictionary, got %s: %s" %
-                         (type(entity), entity))
+    result = fn(entity)
 
   if not ht.TNonEmptyString(result):
     raise Exception("Invalid name '%s'" % result)
@@ -155,7 +151,19 @@ def _GetName(entity, key):
   return result
 
 
-def AssertCommand(cmd, fail=False, node=None):
+def _AssertRetCode(rcode, fail, cmdstr, nodename):
+  """Check the return value from a command and possibly raise an exception.
+
+  """
+  if fail and rcode == 0:
+    raise qa_error.Error("Command '%s' on node %s was expected to fail but"
+                         " didn't" % (cmdstr, nodename))
+  elif not fail and rcode != 0:
+    raise qa_error.Error("Command '%s' on node %s failed, exit code %s" %
+                         (cmdstr, nodename, rcode))
+
+
+def AssertCommand(cmd, fail=False, node=None, log_cmd=True):
   """Checks that a remote command succeeds.
 
   @param cmd: either a string (the command to execute) or a list (to
@@ -165,32 +173,49 @@ def AssertCommand(cmd, fail=False, node=None):
   @param node: if passed, it should be the node on which the command
       should be executed, instead of the master node (can be either a
       dict or a string)
+  @param log_cmd: if False, the command won't be logged (simply passed to
+      StartSSH)
+  @return: the return code of the command
+  @raise qa_error.Error: if the command fails when it shouldn't or vice versa
 
   """
   if node is None:
     node = qa_config.GetMasterNode()
 
-  nodename = _GetName(node, "primary")
+  nodename = _GetName(node, operator.attrgetter("primary"))
 
   if isinstance(cmd, basestring):
     cmdstr = cmd
   else:
     cmdstr = utils.ShellQuoteArgs(cmd)
 
-  rcode = StartSSH(nodename, cmdstr).wait()
-
-  if fail:
-    if rcode == 0:
-      raise qa_error.Error("Command '%s' on node %s was expected to fail but"
-                           " didn't" % (cmdstr, nodename))
-  else:
-    if rcode != 0:
-      raise qa_error.Error("Command '%s' on node %s failed, exit code %s" %
-                           (cmdstr, nodename, rcode))
+  rcode = StartSSH(nodename, cmdstr, log_cmd=log_cmd).wait()
+  _AssertRetCode(rcode, fail, cmdstr, nodename)
 
   return rcode
 
 
+def AssertRedirectedCommand(cmd, fail=False, node=None, log_cmd=True):
+  """Executes a command with redirected output.
+
+  The log will go to the qa-output log file in the ganeti log
+  directory on the node where the command is executed. The fail and
+  node parameters are passed unchanged to AssertCommand.
+
+  @param cmd: the command to be executed, as a list; a string is not
+      supported
+
+  """
+  if not isinstance(cmd, list):
+    raise qa_error.Error("Non-list passed to AssertRedirectedCommand")
+  ofile = utils.ShellQuote(_QA_OUTPUT)
+  cmdstr = utils.ShellQuoteArgs(cmd)
+  AssertCommand("echo ---- $(date) %s ---- >> %s" % (cmdstr, ofile),
+                fail=False, node=node, log_cmd=False)
+  return AssertCommand(cmdstr + " >> %s" % ofile,
+                       fail=fail, node=node, log_cmd=log_cmd)
+
+
 def GetSSHCommand(node, cmd, strict=True, opts=None, tty=None):
   """Builds SSH command to be executed.
 
@@ -207,7 +232,7 @@ def GetSSHCommand(node, cmd, strict=True, opts=None, tty=None):
   @param tty: if we should use tty; if None, will be auto-detected
 
   """
-  args = ["ssh", "-oEscapeChar=none", "-oBatchMode=yes", "-l", "root"]
+  args = ["ssh", "-oEscapeChar=none", "-oBatchMode=yes", "-lroot"]
 
   if tty is None:
     tty = sys.stdout.isatty()
@@ -228,26 +253,48 @@ def GetSSHCommand(node, cmd, strict=True, opts=None, tty=None):
     spath = _MULTIPLEXERS[node][0]
     args.append("-oControlPath=%s" % spath)
     args.append("-oControlMaster=no")
-  args.append(node)
-  if cmd:
-    args.append(cmd)
+
+  (vcluster_master, vcluster_basedir) = \
+    qa_config.GetVclusterSettings()
+
+  if vcluster_master:
+    args.append(vcluster_master)
+    args.append("%s/%s/cmd" % (vcluster_basedir, node))
+
+    if cmd:
+      # For virtual clusters the whole command must be wrapped using the "cmd"
+      # script, as that script sets a number of environment variables. If the
+      # command contains shell meta characters the whole command needs to be
+      # quoted.
+      args.append(utils.ShellQuote(cmd))
+  else:
+    args.append(node)
+
+    if cmd:
+      args.append(cmd)
 
   return args
 
 
-def StartLocalCommand(cmd, **kwargs):
+def StartLocalCommand(cmd, _nolog_opts=False, log_cmd=True, **kwargs):
   """Starts a local command.
 
   """
-  print "Command: %s" % utils.ShellQuoteArgs(cmd)
+  if log_cmd:
+    if _nolog_opts:
+      pcmd = [i for i in cmd if not i.startswith("-")]
+    else:
+      pcmd = cmd
+    print "Command: %s" % utils.ShellQuoteArgs(pcmd)
   return subprocess.Popen(cmd, shell=False, **kwargs)
 
 
-def StartSSH(node, cmd, strict=True):
+def StartSSH(node, cmd, strict=True, log_cmd=True):
   """Starts SSH.
 
   """
-  return StartLocalCommand(GetSSHCommand(node, cmd, strict=strict))
+  return StartLocalCommand(GetSSHCommand(node, cmd, strict=strict),
+                           _nolog_opts=True, log_cmd=log_cmd)
 
 
 def StartMultiplexer(node):
@@ -278,16 +325,41 @@ def CloseMultiplexers():
     utils.RemoveFile(sname)
 
 
-def GetCommandOutput(node, cmd, tty=None):
+def GetCommandOutput(node, cmd, tty=None, fail=False):
   """Returns the output of a command executed on the given node.
 
+  @type node: string
+  @param node: node the command should run on
+  @type cmd: string
+  @param cmd: command to be executed in the node (cannot be empty or None)
+  @type tty: bool or None
+  @param tty: if we should use tty; if None, it will be auto-detected
+  @type fail: bool
+  @param fail: whether the command is expected to fail
   """
+  assert cmd
   p = StartLocalCommand(GetSSHCommand(node, cmd, tty=tty),
                         stdout=subprocess.PIPE)
-  AssertEqual(p.wait(), 0)
+  rcode = p.wait()
+  _AssertRetCode(rcode, fail, cmd, node)
   return p.stdout.read()
 
 
+def GetObjectInfo(infocmd):
+  """Get and parse information about a Ganeti object.
+
+  @type infocmd: list of strings
+  @param infocmd: command to be executed, e.g. ["gnt-cluster", "info"]
+  @return: the information parsed, appropriately stored in dictionaries,
+      lists...
+
+  """
+  master = qa_config.GetMasterNode()
+  cmdline = utils.ShellQuoteArgs(infocmd)
+  info_out = GetCommandOutput(master.primary, cmdline)
+  return yaml.load(info_out)
+
+
 def UploadFile(node, src):
   """Uploads a file to a node and returns the filename.
 
@@ -298,7 +370,8 @@ def UploadFile(node, src):
   # Make sure nobody else has access to it while preserving local permissions
   mode = os.stat(src).st_mode & 0700
 
-  cmd = ('tmp=$(tempfile --mode %o --prefix gnt) && '
+  cmd = ('tmp=$(mktemp --tmpdir gnt.XXXXXX) && '
+         'chmod %o "${tmp}" && '
          '[[ -f "${tmp}" ]] && '
          'cat > "${tmp}" && '
          'echo "${tmp}"') % mode
@@ -325,7 +398,8 @@ def UploadData(node, data, mode=0600, filename=None):
   if filename:
     tmp = "tmp=%s" % utils.ShellQuote(filename)
   else:
-    tmp = "tmp=$(tempfile --mode %o --prefix gnt)" % mode
+    tmp = ('tmp=$(mktemp --tmpdir gnt.XXXXXX) && '
+           'chmod %o "${tmp}"') % mode
   cmd = ("%s && "
          "[[ -f \"${tmp}\" ]] && "
          "cat > \"${tmp}\" && "
@@ -348,27 +422,19 @@ def BackupFile(node, path):
   anymore.
 
   """
-  cmd = ("tmp=$(tempfile --prefix .gnt --directory=$(dirname %s)) && "
+  vpath = MakeNodePath(node, path)
+
+  cmd = ("tmp=$(mktemp .gnt.XXXXXX --tmpdir=$(dirname %s)) && "
          "[[ -f \"$tmp\" ]] && "
          "cp %s $tmp && "
-         "echo $tmp") % (utils.ShellQuote(path), utils.ShellQuote(path))
+         "echo $tmp") % (utils.ShellQuote(vpath), utils.ShellQuote(vpath))
 
   # Return temporary filename
-  return GetCommandOutput(node, cmd).strip()
-
-
-def _ResolveName(cmd, key):
-  """Helper function.
+  result = GetCommandOutput(node, cmd).strip()
 
-  """
-  master = qa_config.GetMasterNode()
+  print "Backup filename: %s" % result
 
-  output = GetCommandOutput(master["primary"], utils.ShellQuoteArgs(cmd))
-  for line in output.splitlines():
-    (lkey, lvalue) = line.split(":", 1)
-    if lkey == key:
-      return lvalue.lstrip()
-  raise KeyError("Key not found")
+  return result
 
 
 def ResolveInstanceName(instance):
@@ -378,16 +444,16 @@ def ResolveInstanceName(instance):
   @param instance: Instance name
 
   """
-  return _ResolveName(["gnt-instance", "info", instance],
-                      "Instance name")
+  info = GetObjectInfo(["gnt-instance", "info", instance])
+  return info[0]["Instance name"]
 
 
 def ResolveNodeName(node):
   """Gets the full name of a node.
 
   """
-  return _ResolveName(["gnt-node", "info", node["primary"]],
-                      "Node name")
+  info = GetObjectInfo(["gnt-node", "info", node.primary])
+  return info[0]["Node name"]
 
 
 def GetNodeInstances(node, secondaries=False):
@@ -400,7 +466,7 @@ def GetNodeInstances(node, secondaries=False):
   # Get list of all instances
   cmd = ["gnt-instance", "list", "--separator=:", "--no-headers",
          "--output=name,pnode,snodes"]
-  output = GetCommandOutput(master["primary"], utils.ShellQuoteArgs(cmd))
+  output = GetCommandOutput(master.primary, utils.ShellQuoteArgs(cmd))
 
   instances = []
   for line in output.splitlines():
@@ -444,7 +510,7 @@ def _List(listcmd, fields, names):
   if names:
     cmd.extend(names)
 
-  return GetCommandOutput(master["primary"],
+  return GetCommandOutput(master.primary,
                           utils.ShellQuoteArgs(cmd)).splitlines()
 
 
@@ -462,7 +528,7 @@ def GenericQueryTest(cmd, fields, namefield="name", test_unknown=True):
 
   # Test a number of field combinations
   for testfields in _SelectQueryFields(rnd, fields):
-    AssertCommand([cmd, "list", "--output", ",".join(testfields)])
+    AssertRedirectedCommand([cmd, "list", "--output", ",".join(testfields)])
 
   if namefield is not None:
     namelist_fn = compat.partial(_List, cmd, [namefield])
@@ -485,8 +551,9 @@ def GenericQueryTest(cmd, fields, namefield="name", test_unknown=True):
                   fail=True)
 
   # Check exit code for listing unknown field
-  AssertEqual(AssertCommand([cmd, "list", "--output=field/does/not/exist"],
-                            fail=True),
+  AssertEqual(AssertRedirectedCommand([cmd, "list",
+                                       "--output=field/does/not/exist"],
+                                      fail=True),
               constants.EXIT_UNKNOWN_FIELD)
 
 
@@ -494,12 +561,12 @@ def GenericQueryFieldsTest(cmd, fields):
   master = qa_config.GetMasterNode()
 
   # Listing fields
-  AssertCommand([cmd, "list-fields"])
-  AssertCommand([cmd, "list-fields"] + fields)
+  AssertRedirectedCommand([cmd, "list-fields"])
+  AssertRedirectedCommand([cmd, "list-fields"] + fields)
 
   # Check listed fields (all, must be sorted)
   realcmd = [cmd, "list-fields", "--separator=|", "--no-headers"]
-  output = GetCommandOutput(master["primary"],
+  output = GetCommandOutput(master.primary,
                             utils.ShellQuoteArgs(realcmd)).splitlines()
   AssertEqual([line.split("|", 1)[0] for line in output],
               utils.NiceSort(fields))
@@ -528,19 +595,22 @@ def AddToEtcHosts(hostnames):
 
   """
   master = qa_config.GetMasterNode()
-  tmp_hosts = UploadData(master["primary"], "", mode=0644)
+  tmp_hosts = UploadData(master.primary, "", mode=0644)
 
-  quoted_tmp_hosts = utils.ShellQuote(tmp_hosts)
   data = []
   for localhost in ("::1", "127.0.0.1"):
     data.append("%s %s" % (localhost, " ".join(hostnames)))
 
   try:
-    AssertCommand(("cat /etc/hosts > %s && echo -e '%s' >> %s && mv %s"
-                   " /etc/hosts") % (quoted_tmp_hosts, "\\n".join(data),
-                                     quoted_tmp_hosts, quoted_tmp_hosts))
-  except qa_error.Error:
-    AssertCommand(["rm", tmp_hosts])
+    AssertCommand("{ cat %s && echo -e '%s'; } > %s && mv %s %s" %
+                  (utils.ShellQuote(pathutils.ETC_HOSTS),
+                   "\\n".join(data),
+                   utils.ShellQuote(tmp_hosts),
+                   utils.ShellQuote(tmp_hosts),
+                   utils.ShellQuote(pathutils.ETC_HOSTS)))
+  except Exception:
+    AssertCommand(["rm", "-f", tmp_hosts])
+    raise
 
 
 def RemoveFromEtcHosts(hostnames):
@@ -550,23 +620,26 @@ def RemoveFromEtcHosts(hostnames):
 
   """
   master = qa_config.GetMasterNode()
-  tmp_hosts = UploadData(master["primary"], "", mode=0644)
+  tmp_hosts = UploadData(master.primary, "", mode=0644)
   quoted_tmp_hosts = utils.ShellQuote(tmp_hosts)
 
   sed_data = " ".join(hostnames)
   try:
-    AssertCommand(("sed -e '/^\(::1\|127\.0\.0\.1\)\s\+%s/d' /etc/hosts > %s"
-                   " && mv %s /etc/hosts") % (sed_data, quoted_tmp_hosts,
-                                              quoted_tmp_hosts))
-  except qa_error.Error:
-    AssertCommand(["rm", tmp_hosts])
+    AssertCommand(("sed -e '/^\(::1\|127\.0\.0\.1\)\s\+%s/d' %s > %s"
+                   " && mv %s %s") %
+                   (sed_data, utils.ShellQuote(pathutils.ETC_HOSTS),
+                    quoted_tmp_hosts, quoted_tmp_hosts,
+                    utils.ShellQuote(pathutils.ETC_HOSTS)))
+  except Exception:
+    AssertCommand(["rm", "-f", tmp_hosts])
+    raise
 
 
 def RunInstanceCheck(instance, running):
   """Check if instance is running or not.
 
   """
-  instance_name = _GetName(instance, "name")
+  instance_name = _GetName(instance, operator.attrgetter("name"))
 
   script = qa_config.GetInstanceCheckScript()
   if not script:
@@ -575,7 +648,7 @@ def RunInstanceCheck(instance, running):
   master_node = qa_config.GetMasterNode()
 
   # Build command to connect to master node
-  master_ssh = GetSSHCommand(master_node["primary"], "--")
+  master_ssh = GetSSHCommand(master_node.primary, "--")
 
   if running:
     running_shellval = "1"
@@ -641,3 +714,193 @@ def InstanceCheck(before, after, instarg):
       return result
     return wrapper
   return decorator
+
+
+def GetNonexistentGroups(count):
+  """Gets group names which shouldn't exist on the cluster.
+
+  @param count: Number of groups to get
+  @rtype: integer
+
+  """
+  return GetNonexistentEntityNames(count, "groups", "group")
+
+
+def GetNonexistentEntityNames(count, name_config, name_prefix):
+  """Gets entity names which shouldn't exist on the cluster.
+
+  The actualy names can refer to arbitrary entities (for example
+  groups, networks).
+
+  @param count: Number of names to get
+  @rtype: integer
+  @param name_config: name of the leaf in the config containing
+    this entity's configuration, including a 'inexistent-'
+    element
+  @rtype: string
+  @param name_prefix: prefix of the entity's names, used to compose
+    the default values; for example for groups, the prefix is
+    'group' and the generated names are then group1, group2, ...
+  @rtype: string
+
+  """
+  entities = qa_config.get(name_config, {})
+
+  default = [name_prefix + str(i) for i in range(count)]
+  assert count <= len(default)
+
+  name_config_inexistent = "inexistent-" + name_config
+  candidates = entities.get(name_config_inexistent, default)[:count]
+
+  if len(candidates) < count:
+    raise Exception("At least %s non-existent %s are needed" %
+                    (count, name_config))
+
+  return candidates
+
+
+def MakeNodePath(node, path):
+  """Builds an absolute path for a virtual node.
+
+  @type node: string or L{qa_config._QaNode}
+  @param node: Node
+  @type path: string
+  @param path: Path without node-specific prefix
+
+  """
+  (_, basedir) = qa_config.GetVclusterSettings()
+
+  if isinstance(node, basestring):
+    name = node
+  else:
+    name = node.primary
+
+  if basedir:
+    assert path.startswith("/")
+    return "%s%s" % (vcluster.MakeNodeRoot(basedir, name), path)
+  else:
+    return path
+
+
+def _GetParameterOptions(specs):
+  """Helper to build policy options."""
+  values = ["%s=%s" % (par, val)
+            for (par, val) in specs.items()]
+  return ",".join(values)
+
+
+def TestSetISpecs(new_specs=None, diff_specs=None, get_policy_fn=None,
+                  build_cmd_fn=None, fail=False, old_values=None):
+  """Change instance specs for an object.
+
+  At most one of new_specs or diff_specs can be specified.
+
+  @type new_specs: dict
+  @param new_specs: new complete specs, in the same format returned by
+      L{ParseIPolicy}.
+  @type diff_specs: dict
+  @param diff_specs: partial specs, it can be an incomplete specifications, but
+      if min/max specs are specified, their number must match the number of the
+      existing specs
+  @type get_policy_fn: function
+  @param get_policy_fn: function that returns the current policy as in
+      L{ParseIPolicy}
+  @type build_cmd_fn: function
+  @param build_cmd_fn: function that return the full command line from the
+      options alone
+  @type fail: bool
+  @param fail: if the change is expected to fail
+  @type old_values: tuple
+  @param old_values: (old_policy, old_specs), as returned by
+     L{ParseIPolicy}
+  @return: same as L{ParseIPolicy}
+
+  """
+  assert get_policy_fn is not None
+  assert build_cmd_fn is not None
+  assert new_specs is None or diff_specs is None
+
+  if old_values:
+    (old_policy, old_specs) = old_values
+  else:
+    (old_policy, old_specs) = get_policy_fn()
+
+  if diff_specs:
+    new_specs = copy.deepcopy(old_specs)
+    if constants.ISPECS_MINMAX in diff_specs:
+      AssertEqual(len(new_specs[constants.ISPECS_MINMAX]),
+                  len(diff_specs[constants.ISPECS_MINMAX]))
+      for (new_minmax, diff_minmax) in zip(new_specs[constants.ISPECS_MINMAX],
+                                           diff_specs[constants.ISPECS_MINMAX]):
+        for (key, parvals) in diff_minmax.items():
+          for (par, val) in parvals.items():
+            new_minmax[key][par] = val
+    for (par, val) in diff_specs.get(constants.ISPECS_STD, {}).items():
+      new_specs[constants.ISPECS_STD][par] = val
+
+  if new_specs:
+    cmd = []
+    if (diff_specs is None or constants.ISPECS_MINMAX in diff_specs):
+      minmax_opt_items = []
+      for minmax in new_specs[constants.ISPECS_MINMAX]:
+        minmax_opts = []
+        for key in ["min", "max"]:
+          keyopt = _GetParameterOptions(minmax[key])
+          minmax_opts.append("%s:%s" % (key, keyopt))
+        minmax_opt_items.append("/".join(minmax_opts))
+      cmd.extend([
+        "--ipolicy-bounds-specs",
+        "//".join(minmax_opt_items)
+        ])
+    if diff_specs is None:
+      std_source = new_specs
+    else:
+      std_source = diff_specs
+    std_opt = _GetParameterOptions(std_source.get("std", {}))
+    if std_opt:
+      cmd.extend(["--ipolicy-std-specs", std_opt])
+    AssertCommand(build_cmd_fn(cmd), fail=fail)
+
+    # Check the new state
+    (eff_policy, eff_specs) = get_policy_fn()
+    AssertEqual(eff_policy, old_policy)
+    if fail:
+      AssertEqual(eff_specs, old_specs)
+    else:
+      AssertEqual(eff_specs, new_specs)
+
+  else:
+    (eff_policy, eff_specs) = (old_policy, old_specs)
+
+  return (eff_policy, eff_specs)
+
+
+def ParseIPolicy(policy):
+  """Parse and split instance an instance policy.
+
+  @type policy: dict
+  @param policy: policy, as returned by L{GetObjectInfo}
+  @rtype: tuple
+  @return: (policy, specs), where:
+      - policy is a dictionary of the policy values, instance specs excluded
+      - specs is a dictionary containing only the specs, using the internal
+        format (see L{constants.IPOLICY_DEFAULTS} for an example)
+
+  """
+  ret_specs = {}
+  ret_policy = {}
+  for (key, val) in policy.items():
+    if key == "bounds specs":
+      ret_specs[constants.ISPECS_MINMAX] = []
+      for minmax in val:
+        ret_minmax = {}
+        for key in minmax:
+          keyparts = key.split("/", 1)
+          assert len(keyparts) > 1
+          ret_minmax[keyparts[0]] = minmax[key]
+        ret_specs[constants.ISPECS_MINMAX].append(ret_minmax)
+    elif key == constants.ISPECS_STD:
+      ret_specs[key] = val
+    else:
+      ret_policy[key] = val
+  return (ret_policy, ret_specs)