diff --git a/hadrian/bindist/version-wrapper.hs b/hadrian/bindist/version-wrapper.hs
new file mode 100644
index 0000000000000000000000000000000000000000..dc7c344c5cfed6f51fbff65afbee2bc7ca138984
--- /dev/null
+++ b/hadrian/bindist/version-wrapper.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE CPP #-}
+module Main (main) where
+
+import System.Environment (getArgs, getExecutablePath)
+import System.Exit (exitWith)
+import System.Process (spawnProcess, waitForProcess)
+import System.FilePath (replaceFileName)
+
+exe = EXE_PATH
+
+main :: IO ()
+main = do
+  args <- getArgs
+  exe_name <- getExecutablePath
+  ph <- spawnProcess (replaceFileName exe_name exe) args
+  code <- waitForProcess ph
+  exitWith code
diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs
index eebe6e93556150623252e83564b7a2775b69f699..7730f43f4ce3e935d18b8d4eb18894344b3259e1 100644
--- a/hadrian/src/Rules/BinaryDist.hs
+++ b/hadrian/src/Rules/BinaryDist.hs
@@ -29,10 +29,21 @@ It does so by following the steps below.
 
 - make sure we have a complete stage 2 compiler + haddock
 
-- copy the bin and lib directories of the compiler we built:
-    <build root>/stage1/{bin, lib}
+- copy the specific binaries which should be in the bindist to the
+  bin folder and add the version suffix:
+    <build root>/stage1/bin/xxxx
   to
-    <build root>/bindist/ghc-<X>.<Y>.<Z>-<arch>-<os>/{bin, lib}
+    <build root/bindist/ghc-<X>.<Y>.<Z>-<arch>-<os>/bin/xxxx-<VER>
+
+- create symlink (or bash) wrapper to from unversioned to versioned executable:
+    <build root/bindist/ghc-<X>.<Y>.<Z>-<arch>-<os>/bin/xxxx-<VER>
+  points to:
+    <build root/bindist/ghc-<X>.<Y>.<Z>-<arch>-<os>/bin/xxxx
+
+- copy the lib directories of the compiler we built:
+    <build root>/stage1/lib
+  to
+    <build root>/bindist/ghc-<X>.<Y>.<Z>-<arch>-<os>/lib
 
 - copy the generated docs (user guide, haddocks, etc):
     <build root>/docs/
@@ -120,10 +131,23 @@ bindistRules = do
         createDirectory bindistFilesDir
         createDirectory (bindistFilesDir -/- "bin")
         createDirectory (bindistFilesDir -/- "lib")
-        -- Also create symlinks with version suffixes (#20074)
-        forM_ (bin_targets ++ iserv_targets) $ \(prog_path, _ver) -> do
-            let install_path = bindistFilesDir -/- "bin" -/- takeFileName prog_path
+        -- Also create wrappers with version suffixes (#20074)
+        forM_ (bin_targets ++ iserv_targets) $ \(prog_path, ver) -> do
+            let orig_filename = takeFileName prog_path
+                (name, ext) = splitExtensions orig_filename
+                version_prog = name ++ "-" ++ ver ++ ext
+                -- Install the actual executable with a version suffix
+                install_path = bindistFilesDir -/- "bin" -/- version_prog
+                -- The wrapper doesn't have a version
+                unversioned_install_path = (bindistFilesDir -/- "bin" -/- orig_filename)
+            -- 1. Copy the executable to the versioned executable name in
+            -- the directory
             copyFile prog_path install_path
+            -- 2. Either make a symlink for the unversioned version or
+            -- a wrapper script on platforms (windows) which don't support symlinks.
+            if windowsHost
+              then createVersionWrapper version_prog unversioned_install_path
+              else createFileLink install_path unversioned_install_path
         copyDirectory (ghcBuildDir -/- "lib") bindistFilesDir
         copyDirectory (rtsIncludeDir)         bindistFilesDir
         need ["docs"]
@@ -331,3 +355,17 @@ iservBins = do
       | w <- [vanilla, profiling, dynamic]
       , w `elem` rtsways
       ]
+
+-- Version wrapper scripts
+
+-- | Create a wrapper script calls the executable given as first argument
+createVersionWrapper :: String -> FilePath -> Action ()
+createVersionWrapper versioned_exe install_path = do
+  ghcPath <- builderPath (Ghc CompileHs Stage2)
+  top <- topDirectory
+  let version_wrapper = top -/- "hadrian" -/- "bindist" -/- "version-wrapper.hs"
+  cmd ghcPath ["-o", install_path, "-no-keep-hi-files"
+              , "-no-keep-o-files", "-rtsopts=ignore"
+              , "-DEXE_PATH=\"" ++ versioned_exe ++ "\""
+              , version_wrapper]
+
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index 0eeda3e97ef2eb079d9568911418be9534a29412..cdceefc29ccfee151b952400f530ba3cd48f4ef7 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -2107,6 +2107,12 @@ def normalise_errmsg(s: str) -> str:
     # collisions, so we need to normalise that to just "ghc"
     s = re.sub('ghc-stage[123]', 'ghc', s)
 
+    # On windows error messages can mention versioned executables
+    s = re.sub('ghc-[0-9.]+', 'ghc', s)
+    s = re.sub('runghc-[0-9.]+', 'runghc', s)
+    s = re.sub('hpc-[0-9.]+', 'hpc', s)
+    s = re.sub('ghc-pkg-[0-9.]+', 'ghc-pkg', s)
+
     # Error messages sometimes contain integer implementation package
     s = re.sub('integer-(gmp|simple)-[0-9.]+', 'integer-<IMPL>-<VERSION>', s)