diff --git a/testsuite/config/ghc b/testsuite/config/ghc
index 031d955552d544fae493f914306baaac05298b63..84b89d49bbd50bedeadac496401fc000a6b41e35 100644
--- a/testsuite/config/ghc
+++ b/testsuite/config/ghc
@@ -148,21 +148,17 @@ config.way_rts_flags = {
 # Useful classes of ways that can be used with only_ways() and
 # expect_broken_for().
 
-prof_ways = map (lambda x: x[0], \
-                 filter(lambda x: '-prof' in x[1], \
-                        config.way_flags('dummy_name').items()))
+prof_ways     = [x[0] for x in config.way_flags('dummy_name').items()
+                      if '-prof' in x[1]]
 
-threaded_ways = map (lambda x: x[0], \
-                 filter(lambda x: '-threaded' in x[1] or 'ghci' == x[0], \
-                        config.way_flags('dummy_name').items()))
+threaded_ways = [x[0] for x in config.way_flags('dummy_name').items()
+                      if '-threaded' in x[1] or 'ghci' == x[0]]
 
-opt_ways = map (lambda x: x[0], \
-                 filter(lambda x: '-O' in x[1], \
-                        config.way_flags('dummy_name').items()))
+opt_ways      = [x[0] for x in config.way_flags('dummy_name').items()
+                      if '-O' in x[1]]
 
-llvm_ways = map (lambda x: x[0], \
-                 filter(lambda x: '-fllvm' in x[1], \
-                        config.way_flags('dummy_name').items()))
+llvm_ways     = [x[0] for x in config.way_flags('dummy_name').items()
+                      if '-fflvm' in x[1]]
 
 def get_compiler_info():
 # This should really not go through the shell
@@ -192,7 +188,7 @@ def get_compiler_info():
 
     if re.match(".*_p(_.*|$)", rtsInfoDict["RTS way"]):
         config.compiler_profiled = True
-        config.run_ways = filter(lambda x: x != 'ghci', config.run_ways)
+        config.run_ways = [x for x in config.run_ways if x != 'ghci']
     else:
         config.compiler_profiled = False
 
diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py
index 103c7ace7c71d4a4a653c6ec7bf2b4086ca75e44..883bda754ea1fe9e8911edc74d64222379d00acc 100644
--- a/testsuite/driver/runtests.py
+++ b/testsuite/driver/runtests.py
@@ -2,6 +2,8 @@
 # (c) Simon Marlow 2002
 #
 
+from __future__ import print_function
+
 import sys
 import os
 import string
@@ -21,6 +23,11 @@ try:
 except:
     pass
 
+PYTHON3 = sys.version_info >= (3, 0)
+if PYTHON3:
+    print("*** WARNING: running testsuite using Python 3.\n"
+          "*** Python 3 support is experimental. See Trac #9184.")
+
 from testutil import *
 from testglobals import *
 
@@ -52,12 +59,12 @@ opts, args = getopt.getopt(sys.argv[1:], "e:", long_options)
        
 for opt,arg in opts:
     if opt == '--config':
-        execfile(arg)
+        exec(open(arg).read())
 
     # -e is a string to execute from the command line.  For example:
     # testframe -e 'config.compiler=ghc-5.04'
     if opt == '-e':
-        exec arg
+        exec(arg)
 
     if opt == '--rootdir':
         config.rootdirs.append(arg)
@@ -83,9 +90,9 @@ for opt,arg in opts:
             sys.stderr.write("ERROR: requested way \'" +
                              arg + "\' does not exist\n")
             sys.exit(1)
-        config.other_ways = filter(neq(arg), config.other_ways)
-        config.run_ways = filter(neq(arg), config.run_ways)
-        config.compile_ways = filter(neq(arg), config.compile_ways)
+        config.other_ways = [w for w in config.other_ways if w != arg]
+        config.run_ways = [w for w in config.run_ways if w != arg]
+        config.compile_ways = [w for w in config.compile_ways if w != arg]
 
     if opt == '--threads':
         config.threads = int(arg)
@@ -117,17 +124,17 @@ if config.use_threads == 1:
     maj = int(re.sub('[^0-9].*', '', str(maj)))
     min = int(re.sub('[^0-9].*', '', str(min)))
     pat = int(re.sub('[^0-9].*', '', str(pat)))
-    if (maj, min, pat) < (2, 5, 2):
-        print "Warning: Ignoring request to use threads as python version < 2.5.2"
-        config.use_threads = 0
+    if (maj, min) < (2, 6):
+        print("Python < 2.6 is not supported")
+        sys.exit(1)
     # We also need to disable threads for python 2.7.2, because of
     # this bug: http://bugs.python.org/issue13817
     elif (maj, min, pat) == (2, 7, 2):
-        print "Warning: Ignoring request to use threads as python version is 2.7.2"
-        print "See http://bugs.python.org/issue13817 for details."
+        print("Warning: Ignoring request to use threads as python version is 2.7.2")
+        print("See http://bugs.python.org/issue13817 for details.")
         config.use_threads = 0
     if windows:
-        print "Warning: Ignoring request to use threads as running on Windows"
+        print("Warning: Ignoring request to use threads as running on Windows")
         config.use_threads = 0
 
 config.cygwin = False
@@ -182,10 +189,10 @@ else:
             h.close()
             if v != '':
                 os.environ['LC_ALL'] = v
-                print "setting LC_ALL to", v
+                print("setting LC_ALL to", v)
             else:
-                print 'WARNING: No UTF8 locale found.'
-                print 'You may get some spurious test failures.'
+                print('WARNING: No UTF8 locale found.')
+                print('You may get some spurious test failures.')
 
 # This has to come after arg parsing as the args can change the compiler
 get_compiler_info()
@@ -232,7 +239,7 @@ if config.use_threads:
 if config.timeout == -1:
     config.timeout = int(read_no_crs(config.top + '/timeout/calibrate.out'))
 
-print 'Timeout is ' + str(config.timeout)
+print('Timeout is ' + str(config.timeout))
 
 # -----------------------------------------------------------------------------
 # The main dude
@@ -242,40 +249,44 @@ if config.rootdirs == []:
 
 t_files = findTFiles(config.rootdirs)
 
-print 'Found', len(t_files), '.T files...'
+print('Found', len(t_files), '.T files...')
 
 t = getTestRun()
 
 # Avoid cmd.exe built-in 'date' command on Windows
 t.start_time = time.localtime()
 
-print 'Beginning test run at', time.strftime("%c %Z",t.start_time)
+print('Beginning test run at', time.strftime("%c %Z",t.start_time))
 
-# set stdout to unbuffered (is this the best way to do it?)
 sys.stdout.flush()
-sys.stdout = os.fdopen(sys.__stdout__.fileno(), "w", 0)
+if PYTHON3:
+    # in Python 3, we output text, which cannot be unbuffered
+    sys.stdout = os.fdopen(sys.__stdout__.fileno(), "w")
+else:
+    # set stdout to unbuffered (is this the best way to do it?)
+    sys.stdout = os.fdopen(sys.__stdout__.fileno(), "w", 0)
 
 # First collect all the tests to be run
 for file in t_files:
     if_verbose(2, '====> Scanning %s' % file)
     newTestDir(os.path.dirname(file))
     try:
-        execfile(file)
-    except:
-        print '*** framework failure: found an error while executing ', file, ':'
+        exec(open(file).read())
+    except Exception:
+        print('*** framework failure: found an error while executing ', file, ':')
         t.n_framework_failures = t.n_framework_failures + 1
         traceback.print_exc()
 
 if config.list_broken:
     global brokens
-    print ''
-    print 'Broken tests:'
-    print (' '.join(map (lambda (b, d, n) : '#' + str(b) + '(' + d + '/' + n + ')', brokens)))
-    print ''
+    print('')
+    print('Broken tests:')
+    print(' '.join(map (lambda bdn: '#' + str(bdn[0]) + '(' + bdn[1] + '/' + bdn[2] + ')', brokens)))
+    print('')
 
     if t.n_framework_failures != 0:
-        print 'WARNING:', str(t.n_framework_failures), 'framework failures!'
-        print ''
+        print('WARNING:', str(t.n_framework_failures), 'framework failures!')
+        print('')
 else:
     # Now run all the tests
     if config.use_threads:
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index e3562f7c541ab307a318976d736a6090efef447d..2e79476df8a6e4e12435a828944f6358991dbc18 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -2,8 +2,7 @@
 # (c) Simon Marlow 2002
 #
 
-# This allows us to use the "with X:" syntax with python 2.5:
-from __future__ import with_statement
+from __future__ import print_function
 
 import shutil
 import sys
@@ -16,7 +15,6 @@ import time
 import datetime
 import copy
 import glob
-import types
 from math import ceil, trunc
 
 have_subprocess = False
@@ -24,15 +22,17 @@ try:
     import subprocess
     have_subprocess = True
 except:
-    print "Warning: subprocess not found, will fall back to spawnv"
+    print("Warning: subprocess not found, will fall back to spawnv")
 
-from string import join
 from testglobals import *
 from testutil import *
 
 if config.use_threads:
     import threading
-    import thread
+    try:
+        import thread
+    except ImportError: # Python 3
+        import _thread as thread
 
 global wantToStop
 wantToStop = False
@@ -99,7 +99,7 @@ def reqlib( lib ):
 have_lib = {}
 
 def _reqlib( name, opts, lib ):
-    if have_lib.has_key(lib):
+    if lib in have_lib:
         got_it = have_lib[lib]
     else:
         if have_subprocess:
@@ -284,7 +284,7 @@ def _stats_num_field( name, opts, field, expecteds ):
     if field in opts.stats_range_fields:
         framework_fail(name, 'duplicate-numfield', 'Duplicate ' + field + ' num_field check')
 
-    if type(expecteds) is types.ListType:
+    if type(expecteds) is list:
         for (b, expected, dev) in expecteds:
             if b:
                 opts.stats_range_fields[field] = (expected, dev)
@@ -512,9 +512,10 @@ def two_normalisers(f, g):
 # Function for composing two opt-fns together
 
 def executeSetups(fs, name, opts):
-    if type(fs) is types.ListType:
+    if type(fs) is list:
         # If we have a list of setups, then execute each one
-        map (lambda f : executeSetups(f, name, opts), fs)
+        for f in fs:
+            executeSetups(f, name, opts)
     else:
         # fs is a single function, so just apply it
         fs(name, opts)
@@ -625,8 +626,7 @@ def test_common_work (name, opts, func, args):
             all_ways = ['normal']
 
         # A test itself can request extra ways by setting opts.extra_ways
-        all_ways = all_ways + filter(lambda way: way not in all_ways,
-                                     opts.extra_ways)
+        all_ways = all_ways + [way for way in opts.extra_ways if way not in all_ways]
 
         t.total_test_cases = t.total_test_cases + len(all_ways)
 
@@ -639,7 +639,7 @@ def test_common_work (name, opts, func, args):
             and way not in getTestOpts().omit_ways
 
         # Which ways we are asked to skip
-        do_ways = filter (ok_way,all_ways)
+        do_ways = list(filter (ok_way,all_ways))
 
         # In fast mode, we skip all but one way
         if config.fast and len(do_ways) > 0:
@@ -658,8 +658,8 @@ def test_common_work (name, opts, func, args):
 
         if getTestOpts().cleanup != '' and (config.clean_only or do_ways != []):
             pretest_cleanup(name)
-            clean(map (lambda suff: name + suff,
-                      ['', '.exe', '.exe.manifest', '.genscript',
+            clean([name + suff for suff in [
+                       '', '.exe', '.exe.manifest', '.genscript',
                        '.stderr.normalised',        '.stdout.normalised',
                        '.run.stderr.normalised',    '.run.stdout.normalised',
                        '.comp.stderr.normalised',   '.comp.stdout.normalised',
@@ -667,12 +667,13 @@ def test_common_work (name, opts, func, args):
                        '.stats', '.comp.stats',
                        '.hi', '.o', '.prof', '.exe.prof', '.hc',
                        '_stub.h', '_stub.c', '_stub.o',
-                       '.hp', '.exe.hp', '.ps', '.aux', '.hcr', '.eventlog']))
+                       '.hp', '.exe.hp', '.ps', '.aux', '.hcr', '.eventlog']])
 
             if func == multi_compile or func == multi_compile_fail:
                     extra_mods = args[1]
-                    clean(map (lambda (f,x): replace_suffix(f, 'o'), extra_mods))
-                    clean(map (lambda (f,x): replace_suffix(f, 'hi'), extra_mods))
+                    clean([replace_suffix(fx[0],'o') for fx in extra_mods])
+                    clean([replace_suffix(fx[0], 'hi') for fx in extra_mods])
+
 
             clean(getTestOpts().clean_files)
 
@@ -712,7 +713,7 @@ def test_common_work (name, opts, func, args):
                         files_written_not_removed[name] = [f]
         except:
             pass
-    except Exception, e:
+    except Exception as e:
         framework_fail(name, 'runTest', 'Unhandled exception: ' + str(e))
 
 def clean(strs):
@@ -724,19 +725,19 @@ def clean_full_path(name):
         try:
             # Remove files...
             os.remove(name)
-        except OSError, e1:
+        except OSError as e1:
             try:
                 # ... and empty directories
                 os.rmdir(name)
-            except OSError, e2:
+            except OSError as e2:
                 # We don't want to fail here, but we do want to know
                 # what went wrong, so print out the exceptions.
                 # ENOENT isn't a problem, though, as we clean files
                 # that don't necessarily exist.
                 if e1.errno != errno.ENOENT:
-                    print e1
+                    print(e1)
                 if e2.errno != errno.ENOENT:
-                    print e2
+                    print(e2)
 
 def do_test(name, way, func, args):
     full_name = name + '(' + way + ')'
@@ -761,7 +762,7 @@ def do_test(name, way, func, args):
             framework_fail(name, way, 'pre-command exception')
 
         try:
-            result = apply(func, [name,way] + args)
+            result = func(*[name,way] + args)
         finally:
             if config.use_threads:
                 t.lock.acquire()
@@ -892,7 +893,8 @@ def run_command( name, way, cmd ):
 def ghci_script( name, way, script ):
     # filter out -fforce-recomp from compiler_always_flags, because we're
     # actually testing the recompilation behaviour in the GHCi tests.
-    flags = filter(lambda f: f != '-fforce-recomp', getTestOpts().compiler_always_flags)
+    flags = [f for f in getTestOpts().compiler_always_flags if f != '-fforce-recomp']
+
     flags.append(getTestOpts().extra_hc_opts)
     if getTestOpts().outputdir != None:
         flags.extend(["-outputdir", getTestOpts().outputdir])
@@ -900,10 +902,10 @@ def ghci_script( name, way, script ):
     # We pass HC and HC_OPTS as environment variables, so that the
     # script can invoke the correct compiler by using ':! $HC $HC_OPTS'
     cmd = "HC='" + config.compiler + "' " + \
-          "HC_OPTS='" + join(flags,' ') + "' " + \
+          "HC_OPTS='" + ' '.join(flags) + "' " + \
           "'" + config.compiler + "'" + \
           ' --interactive -v0 -ignore-dot-ghci ' + \
-          join(flags,' ')
+          ' '.join(flags)
 
     getTestOpts().stdin = script
     return simple_run( name, way, cmd, getTestOpts().extra_run_opts )
@@ -967,7 +969,7 @@ def do_compile( name, way, should_fail, top_mod, extra_mods, extra_hc_opts ):
     return passed()
 
 def compile_cmp_asm( name, way, extra_hc_opts ):
-    print 'Compile only, extra args = ', extra_hc_opts
+    print('Compile only, extra args = ', extra_hc_opts)
     pretest_cleanup(name)
     result = simple_build( name + '.cmm', way, '-keep-s-files -O ' + extra_hc_opts, 0, '', 0, 0, 0)
 
@@ -1049,7 +1051,7 @@ def checkStats(name, way, stats_file, range_fields):
         for (field, (expected, dev)) in range_fields.items():
             m = re.search('\("' + field + '", "([0-9]+)"\)', contents)
             if m == None:
-                print 'Failed to find field: ', field
+                print('Failed to find field: ', field)
                 result = failBecause('no such stats field')
             val = int(m.group(1))
 
@@ -1059,12 +1061,12 @@ def checkStats(name, way, stats_file, range_fields):
             deviation = round(((float(val) * 100)/ expected) - 100, 1)
 
             if val < lowerBound:
-                print field, 'value is too low:'
-                print '(If this is because you have improved GHC, please'
-                print 'update the test so that GHC doesn\'t regress again)'
+                print(field, 'value is too low:')
+                print('(If this is because you have improved GHC, please')
+                print('update the test so that GHC doesn\'t regress again)')
                 result = failBecause('stat too good')
             if val > upperBound:
-                print field, 'value is too high:'
+                print(field, 'value is too high:')
                 result = failBecause('stat not good enough')
 
             if val < lowerBound or val > upperBound or config.verbose >= 4:
@@ -1072,9 +1074,11 @@ def checkStats(name, way, stats_file, range_fields):
                 valLen = len(valStr)
                 expectedStr = str(expected)
                 expectedLen = len(expectedStr)
-                length = max(map (lambda x : len(str(x)), [expected, lowerBound, upperBound, val]))
+                length = max(len(str(x)) for x in [expected, lowerBound, upperBound, val])
+
                 def display(descr, val, extra):
-                    print descr, string.rjust(str(val), length), extra
+                    print(descr, str(val).rjust(length), extra)
+
                 display('    Expected    ' + full_name + ' ' + field + ':', expected, '+/-' + str(dev) + '%')
                 display('    Lower bound ' + full_name + ' ' + field + ':', lowerBound, '')
                 display('    Upper bound ' + full_name + ' ' + field + ':', upperBound, '')
@@ -1149,15 +1153,15 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
 
     comp_flags = copy.copy(getTestOpts().compiler_always_flags)
     if noforce:
-        comp_flags = filter(lambda f: f != '-fforce-recomp', comp_flags)
+        comp_flags = [f for f in comp_flags if f != '-fforce-recomp']
     if getTestOpts().outputdir != None:
         comp_flags.extend(["-outputdir", getTestOpts().outputdir])
 
     cmd = 'cd ' + getTestOpts().testdir + " && " + cmd_prefix + "'" \
           + config.compiler + "' " \
-          + join(comp_flags,' ') + ' ' \
+          + ' '.join(comp_flags) + ' ' \
           + to_do + ' ' + srcname + ' ' \
-          + join(config.way_flags(name)[way],' ') + ' ' \
+          + ' '.join(config.way_flags(name)[way]) + ' ' \
           + extra_hc_opts + ' ' \
           + opts.extra_hc_opts + ' ' \
           + '>' + errname + ' 2>&1'
@@ -1166,7 +1170,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
 
     if result != 0 and not should_fail:
         actual_stderr = qualify(name, 'comp.stderr')
-        if_verbose(1,'Compile failed (status ' + `result` + ') errors were:')
+        if_verbose(1,'Compile failed (status ' + repr(result) + ') errors were:')
         if_verbose_dump(1,actual_stderr)
 
     # ToDo: if the sub-shell was killed by ^C, then exit
@@ -1250,7 +1254,7 @@ def simple_run( name, way, prog, args ):
 
     # check the exit code
     if exit_code != opts.exit_code:
-        print 'Wrong exit code (expected', opts.exit_code, ', actual', exit_code, ')'
+        print('Wrong exit code (expected', opts.exit_code, ', actual', exit_code, ')')
         dump_stdout(name)
         dump_stderr(name)
         return failBecause('bad exit code')
@@ -1282,7 +1286,7 @@ def rts_flags(way):
     if args == []:
         return ''
     else:
-        return '+RTS ' + join(args,' ') + ' -RTS'
+        return '+RTS ' + ' '.join(args) + ' -RTS'
 
 # -----------------------------------------------------------------------------
 # Run a program in the interpreter and check its output
@@ -1339,9 +1343,9 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ):
         flags.extend(["-outputdir", getTestOpts().outputdir])
 
     cmd = "'" + config.compiler + "' " \
-          + join(flags,' ') + ' ' \
+          + ' '.join(flags) + ' ' \
           + srcname + ' ' \
-          + join(config.way_flags(name)[way],' ') + ' ' \
+          + ' '.join(config.way_flags(name)[way]) + ' ' \
           + extra_hc_opts + ' ' \
           + getTestOpts().extra_hc_opts + ' ' \
           + '<' + scriptname +  ' 1>' + outname + ' 2>' + errname
@@ -1366,7 +1370,7 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ):
 
     # check the exit code
     if exit_code != getTestOpts().exit_code:
-        print 'Wrong exit code (expected', getTestOpts().exit_code, ', actual', exit_code, ')'
+        print('Wrong exit code (expected', getTestOpts().exit_code, ', actual', exit_code, ')')
         dump_stdout(name)
         dump_stderr(name)
         return failBecause('bad exit code')
@@ -1428,8 +1432,8 @@ def check_stdout_ok( name ):
                           expected_stdout_file, actual_stdout_file)
 
 def dump_stdout( name ):
-   print 'Stdout:'
-   print read_no_crs(qualify(name, 'run.stdout'))
+   print('Stdout:')
+   print(read_no_crs(qualify(name, 'run.stdout')))
 
 def check_stderr_ok( name ):
    if getTestOpts().with_namebase == None:
@@ -1451,8 +1455,8 @@ def check_stderr_ok( name ):
                           expected_stderr_file, actual_stderr_file)
 
 def dump_stderr( name ):
-   print "Stderr:"
-   print read_no_crs(qualify(name, 'run.stderr'))
+   print("Stderr:")
+   print(read_no_crs(qualify(name, 'run.stderr')))
 
 def read_no_crs(file):
     str = ''
@@ -1487,13 +1491,13 @@ def check_hp_ok(name):
                 if (gsResult == 0):
                     return (True)
                 else:
-                    print "hp2ps output for " + name + "is not valid PostScript"
+                    print("hp2ps output for " + name + "is not valid PostScript")
             else: return (True) # assume postscript is valid without ghostscript
         else:
-            print "hp2ps did not generate PostScript for " + name
+            print("hp2ps did not generate PostScript for " + name)
             return (False)
     else:
-        print "hp2ps error when processing heap profile for " + name
+        print("hp2ps error when processing heap profile for " + name)
         return(False)
 
 def check_prof_ok(name):
@@ -1501,11 +1505,11 @@ def check_prof_ok(name):
     prof_file = qualify(name,'prof')
 
     if not os.path.exists(prof_file):
-        print prof_file + " does not exist"
+        print(prof_file + " does not exist")
         return(False)
 
     if os.path.getsize(qualify(name,'prof')) == 0:
-        print prof_file + " is empty"
+        print(prof_file + " is empty")
         return(False)
 
     if getTestOpts().with_namebase == None:
@@ -1667,16 +1671,16 @@ def normalise_asm( str ):
     out = '\n'.join(out)
     return out
 
-def if_verbose( n, str ):
+def if_verbose( n, s ):
     if config.verbose >= n:
-        print str
+        print(s)
 
 def if_verbose_dump( n, f ):
     if config.verbose >= n:
         try:
-            print open(f).read()
+            print(open(f).read())
         except:
-            print ''
+            print('')
 
 def rawSystem(cmd_and_args):
     # We prefer subprocess.call to os.spawnv as the latter
@@ -1904,7 +1908,7 @@ def checkForFilesWrittenProblems(file):
     if len(files_written_not_removed) > 0:
         file.write("\n")
         file.write("\nSome files written but not removed:\n")
-        tests = files_written_not_removed.keys()
+        tests = list(files_written_not_removed.keys())
         tests.sort()
         for t in tests:
             for f in files_written_not_removed[t]:
@@ -1916,7 +1920,7 @@ def checkForFilesWrittenProblems(file):
     if len(bad_file_usages) > 0:
         file.write("\n")
         file.write("\nSome bad file usages:\n")
-        tests = bad_file_usages.keys()
+        tests = list(bad_file_usages.keys())
         tests.sort()
         for t in tests:
             for f in bad_file_usages[t]:
@@ -1931,7 +1935,7 @@ def genGSCmd(psfile):
 
 def gsNotWorking():
     global gs_working
-    print "GhostScript not available for hp2ps tests"
+    print("GhostScript not available for hp2ps tests")
 
 global gs_working
 gs_working = 0
@@ -1941,7 +1945,7 @@ if config.have_profiling:
     if resultGood == 0:
         resultBad = runCmdExitCode(genGSCmd(config.confdir + '/bad.ps'));
         if resultBad != 0:
-            print "GhostScript available for hp2ps tests"
+            print("GhostScript available for hp2ps tests")
             gs_working = 1;
         else:
             gsNotWorking();
@@ -2008,7 +2012,7 @@ def platform_wordsize_qualify( name, suff ):
              for vers in ['-' + config.compiler_maj_version, '']]
 
     dir = glob.glob(basepath + '*')
-    dir = map (lambda d: normalise_slashes_(d), dir)
+    dir = [normalise_slashes_(d) for d in dir]
 
     for (platformSpecific, f) in paths:
        if f in dir:
@@ -2041,19 +2045,14 @@ def pretest_cleanup(name):
    # not interested in the return code
 
 # -----------------------------------------------------------------------------
-# Return a list of all the files ending in '.T' below the directory dir.
+# Return a list of all the files ending in '.T' below directories roots.
 
 def findTFiles(roots):
-    return concat(map(findTFiles_,roots))
-
-def findTFiles_(path):
-    if os.path.isdir(path):
-        paths = map(lambda x, p=path: p + '/' + x, os.listdir(path))
-        return findTFiles(paths)
-    elif path[-2:] == '.T':
-        return [path]
-    else:
-        return []
+    return [os.path.join(path, filename)
+            for root in roots
+            for path, dirs, files in os.walk(root)
+            for filename in files
+            if filename.endswith('.T')]
 
 # -----------------------------------------------------------------------------
 # Output a test summary to the specified file object
@@ -2064,28 +2063,28 @@ def summary(t, file):
     printUnexpectedTests(file, [t.unexpected_passes, t.unexpected_failures])
     file.write('OVERALL SUMMARY for test run started at '
                + time.strftime("%c %Z", t.start_time) + '\n'
-               + string.rjust(str(datetime.timedelta(seconds=
-                    round(time.time() - time.mktime(t.start_time)))), 8)
+               + str(datetime.timedelta(seconds=
+                    round(time.time() - time.mktime(t.start_time)))).rjust(8)
                + ' spent to go through\n'
-               + string.rjust(`t.total_tests`, 8)
+               + repr(t.total_tests).rjust(8)
                + ' total tests, which gave rise to\n'
-               + string.rjust(`t.total_test_cases`, 8)
+               + repr(t.total_test_cases).rjust(8)
                + ' test cases, of which\n'
-               + string.rjust(`t.n_tests_skipped`, 8)
+               + repr(t.n_tests_skipped).rjust(8)
                + ' were skipped\n'
                + '\n'
-               + string.rjust(`t.n_missing_libs`, 8)
+               + repr(t.n_missing_libs).rjust(8)
                + ' had missing libraries\n'
-               + string.rjust(`t.n_expected_passes`, 8)
+               + repr(t.n_expected_passes).rjust(8)
                + ' expected passes\n'
-               + string.rjust(`t.n_expected_failures`, 8)
+               + repr(t.n_expected_failures).rjust(8)
                + ' expected failures\n'
                + '\n'
-               + string.rjust(`t.n_framework_failures`, 8)
+               + repr(t.n_framework_failures).rjust(8)
                + ' caused framework failures\n'
-               + string.rjust(`t.n_unexpected_passes`, 8)
+               + repr(t.n_unexpected_passes).rjust(8)
                + ' unexpected passes\n'
-               + string.rjust(`t.n_unexpected_failures`, 8)
+               + repr(t.n_unexpected_failures).rjust(8)
                + ' unexpected failures\n'
                + '\n')
 
@@ -2108,7 +2107,7 @@ def printUnexpectedTests(file, testInfoss):
     for testInfos in testInfoss:
         directories = testInfos.keys()
         for directory in directories:
-            tests = testInfos[directory].keys()
+            tests = list(testInfos[directory].keys())
             unexpected += tests
     if unexpected != []:
         file.write('Unexpected results from:\n')
@@ -2116,30 +2115,30 @@ def printUnexpectedTests(file, testInfoss):
         file.write('\n')
 
 def printPassingTestInfosSummary(file, testInfos):
-    directories = testInfos.keys()
+    directories = list(testInfos.keys())
     directories.sort()
-    maxDirLen = max(map ((lambda x : len(x)), directories))
+    maxDirLen = max(len(x) for x in directories)
     for directory in directories:
-        tests = testInfos[directory].keys()
+        tests = list(testInfos[directory].keys())
         tests.sort()
         for test in tests:
            file.write('   ' + directory.ljust(maxDirLen + 2) + test + \
-                      ' (' + join(testInfos[directory][test],',') + ')\n')
+                      ' (' + ','.join(testInfos[directory][test]) + ')\n')
     file.write('\n')
 
 def printFailingTestInfosSummary(file, testInfos):
-    directories = testInfos.keys()
+    directories = list(testInfos.keys())
     directories.sort()
-    maxDirLen = max(map ((lambda x : len(x)), directories))
+    maxDirLen = max(len(d) for d in directories)
     for directory in directories:
-        tests = testInfos[directory].keys()
+        tests = list(testInfos[directory].keys())
         tests.sort()
         for test in tests:
            reasons = testInfos[directory][test].keys()
            for reason in reasons:
                file.write('   ' + directory.ljust(maxDirLen + 2) + test + \
                           ' [' + reason + ']' + \
-                          ' (' + join(testInfos[directory][test][reason],',') + ')\n')
+                          ' (' + ','.join(testInfos[directory][test][reason]) + ')\n')
     file.write('\n')
 
 def getStdout(cmd):
diff --git a/testsuite/driver/testutil.py b/testsuite/driver/testutil.py
index 0738683111ee8ec0c6278d78153053b64651409d..ec45e939871953402b076ffe8249553ba5545d94 100644
--- a/testsuite/driver/testutil.py
+++ b/testsuite/driver/testutil.py
@@ -1,39 +1,5 @@
 # -----------------------------------------------------------------------------
 # Utils
-
-def id(a):
-    return a
-
-def eq(x):
-    return lambda y,z=x: y == z
-
-def neq(x):
-    return lambda y,z=x: y != z
-
-def append(x,y):
-    return x + y
-
-def concat(xs):
-    return reduce(append,xs,[])
-
-def chop(s):
-    if s[len(s)-1:] == '\n':
-        return s[:len(s)-1]
-    else:
-        return s
-    
-def all(p,xs):
-    for x in xs:
-        if not p(x):
-            return False
-    return True
-
-def elem(xs):
-    return lambda x: x in xs
-
-def notElem(xs):
-    return lambda x: x not in xs
-
 def version_to_ints(v):
     return [ int(x) for x in v.split('.') ]
 
diff --git a/testsuite/tests/ffi/should_run/all.T b/testsuite/tests/ffi/should_run/all.T
index 7efc6eb3d81de03a55308698b86b558ccfa6a742..6fe087884d9054989be4eb4c6fa286fdfb3701c5 100644
--- a/testsuite/tests/ffi/should_run/all.T
+++ b/testsuite/tests/ffi/should_run/all.T
@@ -50,10 +50,10 @@ test('ffi008', [exit_code(1), omit_ways(['ghci'])], compile_and_run, [''])
 maybe_skip = normal
 opts = ''
 if config.platform.startswith('i386-'):
-   if config.compiler_type == 'ghc' and \
+    if config.compiler_type == 'ghc' and \
       version_ge(config.compiler_version, '6.13'):
-	opts = '-msse2'
-   else:
+        opts = '-msse2'
+    else:
         maybe_skip = only_ways(['ghci'])
 
 test('ffi009', [when(fast(), skip),
@@ -69,9 +69,9 @@ test('ffi011', normal, compile_and_run, [''])
 # it.
 
 if config.os == 'mingw32':
-	skip_if_not_windows = normal
+    skip_if_not_windows = normal
 else:
-	skip_if_not_windows = skip
+    skip_if_not_windows = skip
 
 test('ffi012', skip_if_not_windows, compile_and_run, [''])
 test('ffi013', normal, compile_and_run, [''])
diff --git a/testsuite/tests/ghci/prog004/prog004.T b/testsuite/tests/ghci/prog004/prog004.T
index ed17afd088d0525cf310d70761104c3260b30507..4b6ee130283d1c8eab37f9e0639257b1c401d9d9 100644
--- a/testsuite/tests/ghci/prog004/prog004.T
+++ b/testsuite/tests/ghci/prog004/prog004.T
@@ -1,8 +1,8 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 def f(name, opts):
-  if not ('ghci' in config.run_ways):
-	opts.skip = 1
+    if not ('ghci' in config.run_ways):
+        opts.skip = 1
 setTestOpts(f)
 
 test('ghciprog004',
diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T
index 72c8e6a74a0605cdd2be155e1ef8c9c6afde62c6..76181a2115a01a77073988427293297cdd079bf8 100644
--- a/testsuite/tests/numeric/should_run/all.T
+++ b/testsuite/tests/numeric/should_run/all.T
@@ -15,11 +15,11 @@ test('arith007', normal, compile_and_run, [''])
 ways = normal
 opts = ''
 if config.platform.startswith('i386-'):
-   if config.compiler_type == 'ghc' and \
+    if config.compiler_type == 'ghc' and \
       version_ge(config.compiler_version, '6.13'):
-	opts = '-msse2'
-   else:
-	ways = expect_fail_for(['optasm','threaded2','hpc','dyn','profasm'])
+        opts = '-msse2'
+    else:
+        ways = expect_fail_for(['optasm','threaded2','hpc','dyn','profasm'])
 
 test('arith008', ways, compile_and_run, [opts])
 
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index a7783a497731c231194387b574f6de93137a6889..9868faefac6acf22e280ab2df00165fddaead4c4 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -1,6 +1,6 @@
 def no_lint(name, opts):
    opts.compiler_always_flags = \
-       filter(lambda opt: opt != '-dcore-lint' and opt != '-dcmm-lint', opts.compiler_always_flags)
+       [opt for opt in opts.compiler_always_flags if opt != '-dcore-lint' and opt != '-dcmm-lint']
 
 setTestOpts(no_lint)
 
diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T
index 7e5f9b407dda2a19a0a5074e3247ff583db65260..8b2256ac7031c3646398f01bcedad1ead1cbe833 100644
--- a/testsuite/tests/plugins/all.T
+++ b/testsuite/tests/plugins/all.T
@@ -1,6 +1,6 @@
 def f(name, opts):
-  if (ghc_with_interpreter == 0):
-	opts.skip = 1
+    if (ghc_with_interpreter == 0):
+        opts.skip = 1
 
 setTestOpts(f)
 setTestOpts(when(compiler_lt('ghc', '7.1'), skip))
diff --git a/testsuite/tests/th/TH_spliceViewPat/test.T b/testsuite/tests/th/TH_spliceViewPat/test.T
index c08e7cb6f556dc102f72aa53b5440d7c2027de8d..21fdff35187ff75c05edf15fe748d467a991bd59 100644
--- a/testsuite/tests/th/TH_spliceViewPat/test.T
+++ b/testsuite/tests/th/TH_spliceViewPat/test.T
@@ -1,7 +1,7 @@
 def f(name, opts):
-  opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
-  if (ghc_with_interpreter == 0):
-	opts.skip = 1
+    opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
+    if (ghc_with_interpreter == 0):
+        opts.skip = 1
 
 setTestOpts(f)
 setTestOpts(only_compiler_types(['ghc']))
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 6e86d303e5cf0ae165d6ef53976a6c2ae63c3caa..00f5fc967052b6fde3e88bf9247fe01e32b47a83 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -4,9 +4,9 @@
 test('T4255', unless(compiler_profiled(), skip), compile_fail, ['-v0'])
 
 def f(name, opts):
-  opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
-  if (ghc_with_interpreter == 0):
-	opts.skip = 1
+    opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
+    if (ghc_with_interpreter == 0):
+        opts.skip = 1
 
 setTestOpts(f)
 setTestOpts(only_compiler_types(['ghc']))
diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T
index 760d5e1452dedf291e15da48856874b5395b5430..5da7c8b1694539d59a524ed0283e46a5e43ff954 100755
--- a/testsuite/tests/typecheck/should_run/all.T
+++ b/testsuite/tests/typecheck/should_run/all.T
@@ -19,8 +19,8 @@ test('TcCoercible', when(compiler_lt('ghc', '7.7'), skip), compile_and_run, ['']
 # Skip everything else if fast is on
 
 def f(name, opts):
-  if config.fast:
-	opts.skip = 1
+    if config.fast:
+        opts.skip = 1
 setTestOpts(f)
 
 test('tcrun006', normal, compile_and_run, [''])
diff --git a/testsuite/timeout/calibrate b/testsuite/timeout/calibrate
index b0d75dac247b7095993a95c8fb351a380c302b81..f30c628e7a90b7e175c4a69037d681b5845c76f0 100644
--- a/testsuite/timeout/calibrate
+++ b/testsuite/timeout/calibrate
@@ -10,7 +10,7 @@ except:
     # We don't have resource, so this is a non-UNIX machine.
     # It's probably a reasonable modern x86/x86_64 machines, so we'd
     # probably calibrate to 300 anyway; thus just print 300.
-    print 300
+    print(300)
     exit(0)
 
 compiler = argv[1]
diff --git a/testsuite/timeout/timeout.py b/testsuite/timeout/timeout.py
index 6a57ac2f8212c2327a3a44ef17e2a53b1d0d190d..df50806b9b8c3a1a5815b503daaae53d3337892b 100644
--- a/testsuite/timeout/timeout.py
+++ b/testsuite/timeout/timeout.py
@@ -21,7 +21,7 @@ try:
                     os.killpg(pid, signal.SIGKILL)
                 else:
                     return
-            except OSError, e:
+            except OSError as e:
                 if e.errno == errno.ECHILD:
                     return
                 else:
diff --git a/utils/fingerprint/fingerprint.py b/utils/fingerprint/fingerprint.py
index 5738cda8cc21cd960f49cf3c5a11ada771273004..628e0c85bb2a61d6cf48fe0abedfbe8fe4962087 100755
--- a/utils/fingerprint/fingerprint.py
+++ b/utils/fingerprint/fingerprint.py
@@ -1,6 +1,8 @@
 #! /usr/bin/env python
 # Script to create and restore a git fingerprint of the ghc repositories.
 
+from __future__ import print_function
+
 from   datetime   import datetime
 from   optparse   import OptionParser
 import os
@@ -23,7 +25,7 @@ def create_action(opts):
   if len(fp) == 0:
     error("Got empty fingerprint from source: "+str(opts.source))
   if opts.output_file:
-    print "Writing fingerprint to: ", opts.output_file
+    print("Writing fingerprint to: ", opts.output_file)
   fp.write(opts.output)
 
 def restore_action(opts):
@@ -89,7 +91,7 @@ def restore(fp, branch_name=None):
   for (subdir, commit) in fp:
     if subdir != ".":
       cmd = checkout + [commit]
-      print "==", subdir, " ".join(cmd)
+      print("==", subdir, " ".join(cmd))
       if os.path.exists(subdir):
         rc = subprocess.call(cmd, cwd=subdir)
         if rc != 0:
@@ -184,7 +186,7 @@ def validate(opts, args, parser):
 
 def error(msg="fatal error", parser=None, exit=1):
   """Function that prints error message and exits"""
-  print "ERROR:", msg
+  print("ERROR:", msg)
   if parser:
     parser.print_help()
   sys.exit(exit)