diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/A.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/A/A.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..a1420d9676eaf79fa9f9d6d56d15f544eb071e44
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/A.cabal
@@ -0,0 +1,23 @@
+cabal-version:       2.4
+name:                A
+version:             0.1.0.0
+license:             BSD-3-Clause
+
+library
+  exposed-modules:     A
+  build-depends:       base >=4
+  hs-source-dirs:      src
+  default-language:    Haskell2010
+
+executable A
+  main-is:             Main.hs
+  build-depends:       base >=4
+  hs-source-dirs:      src
+  default-language:    Haskell2010
+
+test-suite A-tests
+  type:                exitcode-stdio-1.0
+  main-is:             Test.hs
+  build-depends:       base >=4, A
+  hs-source-dirs:      src
+  default-language:    Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/B.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/B.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..e81b9eb3a1d2655f63ba71e67696babfdcbf09cb
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/B.cabal
@@ -0,0 +1,10 @@
+cabal-version:       2.4
+name:                B
+version:             0.1.0.0
+license:             BSD-3-Clause
+
+library
+  exposed-modules:     B
+  build-depends:       base >=4.0.0.0, A
+  hs-source-dirs:      lib
+  default-language:    Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/lib/B.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/lib/B.hs
new file mode 100644
index 0000000000000000000000000000000000000000..8b74dfe6b439b8dc3c448836d4d2464f8c74c0e4
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/B/lib/B.hs
@@ -0,0 +1,4 @@
+module B where
+
+foo :: Int -> Int
+foo = id
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.out b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.out
new file mode 100644
index 0000000000000000000000000000000000000000..4ea2b2ee427a590cff0566afcd34e6f8548f46ec
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.out
@@ -0,0 +1,20 @@
+# cabal build
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - A-0.1.0.0 (lib) (first run)
+ - A-0.1.0.0 (exe:A) (first run)
+ - B-0.1.0.0 (lib) (first run)
+ - A-0.1.0.0 (test:A-tests) (first run)
+Configuring library for A-0.1.0.0..
+Preprocessing library for A-0.1.0.0..
+Building library for A-0.1.0.0..
+Configuring executable 'A' for A-0.1.0.0..
+Preprocessing executable 'A' for A-0.1.0.0..
+Building executable 'A' for A-0.1.0.0..
+Configuring library for B-0.1.0.0..
+Preprocessing library for B-0.1.0.0..
+Building library for B-0.1.0.0..
+Configuring test suite 'A-tests' for A-0.1.0.0..
+Preprocessing test suite 'A-tests' for A-0.1.0.0..
+Building test suite 'A-tests' for A-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..8fdc04e7a2ac71b18a06710ab947e2ed2f57f360
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-all.test.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE OverloadedStrings #-}
+import           Test.Cabal.Prelude
+import           Test.Cabal.DecodeShowBuildInfo
+
+main = cabalTest $ do
+  runShowBuildInfo ["all", "--enable-tests"]
+  withPlan $ do
+    assertComponent "A" (exe "A")
+      defCompAssertion
+        { sourceFiles = ["Main.hs"]
+        , sourceDirs = ["src"]
+        }
+    assertComponent "A" mainLib
+      defCompAssertion
+        { modules = ["A"]
+        , sourceDirs = ["src"]
+        }
+
+    assertComponent "B" mainLib
+      defCompAssertion
+        { modules = ["B"]
+        , sourceDirs = ["lib"]
+        }
+    assertComponent "A" (test "A-tests")
+      defCompAssertion
+        { sourceFiles = ["Test.hs"]
+        , sourceDirs = ["src"]
+        }
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.out b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.out
new file mode 100644
index 0000000000000000000000000000000000000000..9a6b8886d8711c2f2895e1bac4c4215be9b8cbc7
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.out
@@ -0,0 +1,8 @@
+# cabal build
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - A-0.1.0.0 (exe:A) (first run)
+Configuring executable 'A' for A-0.1.0.0..
+Preprocessing executable 'A' for A-0.1.0.0..
+Building executable 'A' for A-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..a27bf2d81671123a8fb77502bd00d22631df37ee
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/build-info-exe.test.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE OverloadedStrings #-}
+import           Test.Cabal.Prelude
+import           Test.Cabal.DecodeShowBuildInfo
+
+main = cabalTest $ do
+  runShowBuildInfo ["exe:A"]
+  withPlan $ do
+    assertComponent "A" (exe "A")
+      defCompAssertion
+          { sourceFiles = ["Main.hs"]
+          , sourceDirs = ["src"]
+          -- does not list lib as a target
+          , compilerArgsPred = all (/= "A-0.1.0.0-inplace")
+          }
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/cabal.project b/cabal-testsuite/PackageTests/ShowBuildInfo/A/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..9a091f69b3b7227f9e6834a418d3aa917cb9c54c
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/cabal.project
@@ -0,0 +1 @@
+packages: . ./B/
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.out b/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.out
new file mode 100644
index 0000000000000000000000000000000000000000..7bb32b8b674ec6e9561299e20aa69a2b9639cb7f
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.out
@@ -0,0 +1,15 @@
+# cabal build
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - A-0.1.0.0 (exe:A) (first run)
+Configuring executable 'A' for A-0.1.0.0..
+Preprocessing executable 'A' for A-0.1.0.0..
+Building executable 'A' for A-0.1.0.0..
+# cabal v2-build
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - A-0.1.0.0 (exe:A) (configuration changed)
+Configuring executable 'A' for A-0.1.0.0..
+Preprocessing executable 'A' for A-0.1.0.0..
+Building executable 'A' for A-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..f6bcdf047fe5eed54ff71df750e7efa7e38ca419
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/remove-outdated.test.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE OverloadedStrings #-}
+import           Test.Cabal.Prelude
+import           Test.Cabal.DecodeShowBuildInfo
+import           Test.Cabal.Plan
+import           Control.Monad.Trans.Reader
+import           System.Directory
+
+main = cabalTest $ do
+  runShowBuildInfo ["exe:A"]
+  withPlan $ do
+    assertComponent "A" (exe "A")
+      defCompAssertion
+          { sourceFiles = ["Main.hs"]
+          , sourceDirs = ["src"]
+          -- does not list lib as a target
+          , compilerArgsPred = all (/= "A-0.1.0.0-inplace")
+          }
+
+  cabal' "v2-build" ["exe:A", "--disable-build-info"]
+  withPlan $ do
+    Just plan <- fmap testPlan ask
+    let fp = buildInfoFile plan "A" (exe "A")
+    shouldNotExist fp
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/A.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/A.hs
new file mode 100644
index 0000000000000000000000000000000000000000..2ec6a4f2188508917d8d4750e034bf31d201ded1
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/A.hs
@@ -0,0 +1,3 @@
+module A where
+
+foo = 2
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Main.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..de106fe48f9a76b921e01d9461624a688aec0d31
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Main.hs
@@ -0,0 +1,3 @@
+module Main where
+
+main = return ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..d82a4bd93b7e75a6ff9845150450ae0709b93086
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/A/src/Test.hs
@@ -0,0 +1,4 @@
+module Main where
+
+main :: IO ()
+main = return ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/Complex.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/Complex.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..d8ea0a46eca2b2a7836bc2ac3a7db257f5e87824
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/Complex.cabal
@@ -0,0 +1,72 @@
+cabal-version: 2.4
+name:          Complex
+version:       0.1.0.0
+license:       MIT
+
+library
+  build-depends:    base
+  hs-source-dirs:   src doesnt-exist
+  default-language: Haskell2010
+  exposed-modules:
+    A
+    B
+
+  autogen-modules:  Paths_Complex
+  other-modules:
+    C
+    D
+    Paths_Complex
+
+  ghc-options:      -Wall
+
+executable Complex
+  main-is:          Main.lhs
+  build-depends:
+    , base
+    , Complex
+
+  hs-source-dirs:   app
+  autogen-modules:  Paths_Complex
+  other-modules:
+    Other
+    Paths_Complex
+
+  ghc-options:
+    -threaded -rtsopts "-with-rtsopts=-N -T" -Wredundant-constraints
+
+  default-language: Haskell2010
+
+test-suite unit-test
+  type:             exitcode-stdio-1.0
+  hs-source-dirs:   test
+  build-depends:
+    , another-framework
+    , base
+
+  main-is:          UnitMain.hs
+  default-language: Haskell2010
+
+test-suite func-test
+  type:             exitcode-stdio-1.0
+  hs-source-dirs:   test
+  build-depends:
+    , base
+    , Complex
+    , test-framework
+
+  main-is:          FuncMain.hs
+  default-language: Haskell2010
+
+benchmark complex-benchmarks
+  type:             exitcode-stdio-1.0
+  main-is:          Main.hs
+  other-modules:    Paths_Complex
+  autogen-modules:  Paths_Complex
+  hs-source-dirs:   benchmark
+  ghc-options:      -Wall -rtsopts -threaded -with-rtsopts=-N
+  build-depends:
+    , base
+    , Complex
+    , criterion  ^>=1.1.4
+
+  default-language: Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Main.lhs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Main.lhs
new file mode 100644
index 0000000000000000000000000000000000000000..6f482ce06954d784cc24f6d73d99ea7feaed061f
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Main.lhs
@@ -0,0 +1,8 @@
+> module Main where
+>
+> import A
+> import Other
+>
+> main = do
+>     print foo
+>     print bar
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Other.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Other.hs
new file mode 100644
index 0000000000000000000000000000000000000000..5d0685b1815ab7d2b81f4cceae99f73d806c61c0
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/app/Other.hs
@@ -0,0 +1,3 @@
+module Other where
+
+bar = ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/benchmark/Main.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/benchmark/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..7753bcff18c01207b5f8746d7da5eb66e1e27f25
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/benchmark/Main.hs
@@ -0,0 +1,3 @@
+module Main where
+
+main = pure ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/cabal.project b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..a40dbcbdd1e0ecdc8391c954ed49ee741aa8539e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/cabal.project
@@ -0,0 +1,4 @@
+packages: .
+
+tests: True
+benchmarks: True
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/another-framework-0.8.1.1/another-framework.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/another-framework-0.8.1.1/another-framework.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..173443e1906fd719e613e43f3f366741c3d883b0
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/another-framework-0.8.1.1/another-framework.cabal
@@ -0,0 +1,8 @@
+name: another-framework
+version: 0.8.1.1
+build-type: Simple
+cabal-version: >= 1.10
+
+library
+    build-depends: base
+    default-language: Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/criterion-1.1.4.0/criterion.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/criterion-1.1.4.0/criterion.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..e7cdc916530af0263fdc6f92a5239ebc28166df2
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/criterion-1.1.4.0/criterion.cabal
@@ -0,0 +1,8 @@
+name: criterion
+version: 1.1.4.0
+build-type: Simple
+cabal-version: >= 1.10
+
+library
+    build-depends: base, ghc-prim
+    default-language: Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/test-framework-0.8.1.1/test-framework.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/test-framework-0.8.1.1/test-framework.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..2235e2eeb39fc27b2abbf1827df8865c3c02ff2f
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/repo/test-framework-0.8.1.1/test-framework.cabal
@@ -0,0 +1,8 @@
+name: test-framework
+version: 0.8.1.1
+build-type: Simple
+cabal-version: >= 1.10
+
+library
+    build-depends: base
+    default-language: Haskell2010
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.out b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.out
new file mode 100644
index 0000000000000000000000000000000000000000..a0e8e3cde86be4bb353d3111e4d4f5b8a2f45b30
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.out
@@ -0,0 +1,67 @@
+# cabal v2-update
+Downloading the latest package list from test-local-repo
+# cabal build
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - Complex-0.1.0.0 (lib) (first run)
+ - Complex-0.1.0.0 (exe:Complex) (first run)
+Configuring library for Complex-0.1.0.0..
+Warning: 'hs-source-dirs: doesnt-exist' specifies a directory which does not exist.
+Preprocessing library for Complex-0.1.0.0..
+Building library for Complex-0.1.0.0..
+Configuring executable 'Complex' for Complex-0.1.0.0..
+Warning: 'hs-source-dirs: doesnt-exist' specifies a directory which does not exist.
+Preprocessing executable 'Complex' for Complex-0.1.0.0..
+Building executable 'Complex' for Complex-0.1.0.0..
+# show-build-info Complex exe:Complex
+{"cabal-lib-version":"3.7.0.0","compiler":{"flavour":"ghc","compiler-id":"ghc-<GHCVER>","path":"<GHCPATH>"},"components":[{"type":"exe","name":"exe:Complex","unit-id":"Complex-0.1.0.0-inplace-Complex","compiler-args":["-fbuilding-cabal-package","-O","-outputdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-odir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-hidir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-stubdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-i","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-iapp","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build/Complex/autogen","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build/Complex/autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build","-optP-include","-optP<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/x/Complex/build/Complex/autogen/cabal_macros.h","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","<ROOT>/single.dist/home/.cabal/store/ghc-<GHCVER>/package.db","-package-db","<ROOT>/single.dist/work/./dist/packagedb/ghc-<GHCVER>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-XHaskell2010","-threaded","-rtsopts","-with-rtsopts=-N -T","-Wredundant-constraints"],"modules":["Other","Paths_Complex"],"src-files":["Main.lhs"],"hs-src-dirs":["app"],"src-dir":"<ROOT>/","cabal-file":"./Complex.cabal"}]}
+# cabal build
+Up to date
+# show-build-info Complex lib
+{"cabal-lib-version":"3.7.0.0","compiler":{"flavour":"ghc","compiler-id":"ghc-<GHCVER>","path":"<GHCPATH>"},"components":[{"type":"lib","name":"lib","unit-id":"Complex-0.1.0.0-inplace","compiler-args":["-fbuilding-cabal-package","-O","-outputdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-odir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-hidir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-stubdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-i","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-isrc","-idoesnt-exist","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build/autogen","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build/autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build","-optP-include","-optP<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/build/autogen/cabal_macros.h","-this-unit-id","Complex-0.1.0.0-inplace","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","<ROOT>/single.dist/home/.cabal/store/ghc-<GHCVER>/package.db","-package-db","<ROOT>/single.dist/work/./dist/packagedb/ghc-<GHCVER>","-package-id","<PACKAGEDEP>","-XHaskell2010","-Wall"],"modules":["A","B","C","D","Paths_Complex"],"src-files":[],"hs-src-dirs":["src","doesnt-exist"],"src-dir":"<ROOT>/","cabal-file":"./Complex.cabal"}]}
+# cabal build
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - criterion-1.1.4.0 (lib) (requires build)
+ - Complex-0.1.0.0 (bench:complex-benchmarks) (first run)
+Configuring library for criterion-1.1.4.0..
+Preprocessing library for criterion-1.1.4.0..
+Building library for criterion-1.1.4.0..
+Installing library in <PATH>
+Configuring benchmark 'complex-benchmarks' for Complex-0.1.0.0..
+Warning: 'hs-source-dirs: doesnt-exist' specifies a directory which does not exist.
+Preprocessing benchmark 'complex-benchmarks' for Complex-0.1.0.0..
+Building benchmark 'complex-benchmarks' for Complex-0.1.0.0..
+# show-build-info Complex bench:complex-benchmarks
+{"cabal-lib-version":"3.7.0.0","compiler":{"flavour":"ghc","compiler-id":"ghc-<GHCVER>","path":"<GHCPATH>"},"components":[{"type":"bench","name":"bench:complex-benchmarks","unit-id":"Complex-0.1.0.0-inplace-complex-benchmarks","compiler-args":["-fbuilding-cabal-package","-O","-outputdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-odir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-hidir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-stubdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-i","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-ibenchmark","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build/complex-benchmarks/autogen","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build/complex-benchmarks/autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build","-optP-include","-optP<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/b/complex-benchmarks/build/complex-benchmarks/autogen/cabal_macros.h","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","<ROOT>/single.dist/home/.cabal/store/ghc-<GHCVER>/package.db","-package-db","<ROOT>/single.dist/work/./dist/packagedb/ghc-<GHCVER>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-XHaskell2010","-Wall","-rtsopts","-threaded","-with-rtsopts=-N"],"modules":["Paths_Complex"],"src-files":["Main.hs"],"hs-src-dirs":["benchmark"],"src-dir":"<ROOT>/","cabal-file":"./Complex.cabal"}]}
+# cabal build
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - test-framework-0.8.1.1 (lib) (requires build)
+ - Complex-0.1.0.0 (test:func-test) (first run)
+Configuring library for test-framework-0.8.1.1..
+Preprocessing library for test-framework-0.8.1.1..
+Building library for test-framework-0.8.1.1..
+Installing library in <PATH>
+Configuring test suite 'func-test' for Complex-0.1.0.0..
+Warning: 'hs-source-dirs: doesnt-exist' specifies a directory which does not exist.
+Preprocessing test suite 'func-test' for Complex-0.1.0.0..
+Building test suite 'func-test' for Complex-0.1.0.0..
+# show-build-info Complex test:func-test
+{"cabal-lib-version":"3.7.0.0","compiler":{"flavour":"ghc","compiler-id":"ghc-<GHCVER>","path":"<GHCPATH>"},"components":[{"type":"test","name":"test:func-test","unit-id":"Complex-0.1.0.0-inplace-func-test","compiler-args":["-fbuilding-cabal-package","-O","-outputdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-odir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-hidir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-stubdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-i","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-itest","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build/func-test/autogen","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build/func-test/autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build","-optP-include","-optP<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/func-test/build/func-test/autogen/cabal_macros.h","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","<ROOT>/single.dist/home/.cabal/store/ghc-<GHCVER>/package.db","-package-db","<ROOT>/single.dist/work/./dist/packagedb/ghc-<GHCVER>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-XHaskell2010"],"modules":[],"src-files":["FuncMain.hs"],"hs-src-dirs":["test"],"src-dir":"<ROOT>/","cabal-file":"./Complex.cabal"}]}
+# cabal build
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - another-framework-0.8.1.1 (lib) (requires build)
+ - Complex-0.1.0.0 (test:unit-test) (first run)
+Configuring library for another-framework-0.8.1.1..
+Preprocessing library for another-framework-0.8.1.1..
+Building library for another-framework-0.8.1.1..
+Installing library in <PATH>
+Configuring test suite 'unit-test' for Complex-0.1.0.0..
+Warning: 'hs-source-dirs: doesnt-exist' specifies a directory which does not exist.
+Preprocessing test suite 'unit-test' for Complex-0.1.0.0..
+Building test suite 'unit-test' for Complex-0.1.0.0..
+# show-build-info Complex test:unit-test
+{"cabal-lib-version":"3.7.0.0","compiler":{"flavour":"ghc","compiler-id":"ghc-<GHCVER>","path":"<GHCPATH>"},"components":[{"type":"test","name":"test:unit-test","unit-id":"Complex-0.1.0.0-inplace-unit-test","compiler-args":["-fbuilding-cabal-package","-O","-outputdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-odir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-hidir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-stubdir","<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-i","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-itest","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build/unit-test/autogen","-i<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build/unit-test/autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build/global-autogen","-I<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build","-optP-include","-optP<ROOT>/single.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/Complex-0.1.0.0/t/unit-test/build/unit-test/autogen/cabal_macros.h","-hide-all-packages","-Wmissing-home-modules","-no-user-package-db","-package-db","<ROOT>/single.dist/home/.cabal/store/ghc-<GHCVER>/package.db","-package-db","<ROOT>/single.dist/work/./dist/packagedb/ghc-<GHCVER>","-package-id","<PACKAGEDEP>","-package-id","<PACKAGEDEP>","-XHaskell2010"],"modules":[],"src-files":["UnitMain.hs"],"hs-src-dirs":["test"],"src-dir":"<ROOT>/","cabal-file":"./Complex.cabal"}]}
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..5b083d69c160dc8374f564e6e8a1ad13c30a8166
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/single.test.hs
@@ -0,0 +1,41 @@
+{-# LANGUAGE OverloadedStrings #-}
+import           Test.Cabal.Prelude
+import           Test.Cabal.DecodeShowBuildInfo
+
+main = cabalTest $ withRepo "repo" $ do
+  runShowBuildInfo ["exe:Complex"] >> withPlan (do
+    recordBuildInfo "Complex" (exe "Complex")
+    assertComponent "Complex" (exe "Complex") defCompAssertion
+      { modules = ["Other", "Paths_Complex"]
+      , sourceFiles = ["Main.lhs"]
+      , sourceDirs = ["app"]
+      })
+
+  runShowBuildInfo ["lib:Complex"] >> withPlan (do
+    recordBuildInfo "Complex" mainLib
+    assertComponent "Complex" mainLib defCompAssertion
+      { modules = ["A", "B", "C", "D", "Paths_Complex"]
+      , sourceDirs = ["src", "doesnt-exist"]
+      })
+
+  runShowBuildInfo ["benchmark:complex-benchmarks"] >> withPlan (do
+    recordBuildInfo "Complex" (bench "complex-benchmarks")
+    assertComponent "Complex" (bench "complex-benchmarks") defCompAssertion
+      { modules = ["Paths_Complex"]
+      , sourceFiles = ["Main.hs"]
+      , sourceDirs = ["benchmark"]
+      })
+
+  runShowBuildInfo ["test:func-test"] >> withPlan (do
+    recordBuildInfo "Complex" (test "func-test")
+    assertComponent "Complex" (test "func-test") defCompAssertion
+      { sourceFiles = ["FuncMain.hs"]
+      , sourceDirs = ["test"]
+      })
+
+  runShowBuildInfo ["test:unit-test"] >> withPlan (do
+    recordBuildInfo "Complex" (test "unit-test")
+    assertComponent "Complex" (test "unit-test") defCompAssertion
+      { sourceFiles = ["UnitMain.hs"]
+      , sourceDirs = ["test"]
+      })
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/A.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/A.hs
new file mode 100644
index 0000000000000000000000000000000000000000..18032f689884a10882c2344dd09281fd03e673a0
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/A.hs
@@ -0,0 +1,5 @@
+module A where
+
+import D
+
+foo = d
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/B.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/B.hs
new file mode 100644
index 0000000000000000000000000000000000000000..93b0222a65db8bbf38b11b733dba8e4283fa88b2
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/B.hs
@@ -0,0 +1,3 @@
+module B where
+
+b = 1
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/C.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/C.hs
new file mode 100644
index 0000000000000000000000000000000000000000..419eb7eca64375e07818da86176987b55c00b8b0
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/C.hs
@@ -0,0 +1,5 @@
+module C where
+
+import B
+
+c = b
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/D.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/D.hs
new file mode 100644
index 0000000000000000000000000000000000000000..d9be40b5ba2ead09e9eca33f49690881d3aeb241
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/src/D.hs
@@ -0,0 +1,5 @@
+module D where
+
+import C
+
+d = c
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/FuncMain.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/FuncMain.hs
new file mode 100644
index 0000000000000000000000000000000000000000..b3549c2fe3d794dddfdf687ed1163ff5302f20e8
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/FuncMain.hs
@@ -0,0 +1 @@
+main = return ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/UnitMain.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/UnitMain.hs
new file mode 100644
index 0000000000000000000000000000000000000000..b3549c2fe3d794dddfdf687ed1163ff5302f20e8
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Complex/test/UnitMain.hs
@@ -0,0 +1 @@
+main = return ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Custom.cabal b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Custom.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..26e2d7f00fb08c8d7b3cfb4dcd367f71040f4305
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Custom.cabal
@@ -0,0 +1,21 @@
+cabal-version:      3.0
+name:               Custom
+version:            0.1.0.0
+
+build-type:         Custom
+
+custom-setup
+  setup-depends: Cabal >= 3.7, base
+
+library
+    exposed-modules:  MyLib
+    build-depends:    base
+    hs-source-dirs:   src
+    default-language: Haskell2010
+
+executable great-exe
+    main-is:          Main.hs
+    build-depends:    base, Custom
+    hs-source-dirs:   app
+    default-language: Haskell2010
+
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Setup.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Setup.hs
new file mode 100644
index 0000000000000000000000000000000000000000..a1825767ed7f0978f845e8009a648aceef18eb55
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/Setup.hs
@@ -0,0 +1,12 @@
+-- Setup.hs taken from 'cabal-testsuite/Setup.hs'
+{-# LANGUAGE Haskell2010 #-}
+module Main (main) where
+
+import Distribution.Simple
+
+main :: IO ()
+main = defaultMainWithHooks simpleUserHooks
+    { buildHook = \pkg lbi hooks flags -> do
+        putStrLn "Custom Setup.hs has been invoked!"
+        buildHook simpleUserHooks pkg lbi hooks flags
+    }
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/app/Main.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/app/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..83b7ee473d7f5de21aac233f29f9344368ab7c7e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/app/Main.hs
@@ -0,0 +1,5 @@
+module Main where
+
+import MyLib
+
+main = pure ()
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/cabal.project b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..1b8a75ee74b94bbeaa77bcfb020908abb588dba3
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/cabal.project
@@ -0,0 +1,2 @@
+packages:
+    .
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.out b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.out
new file mode 100644
index 0000000000000000000000000000000000000000..3cd432d6bb2c6cc4550455f0ab96318949edc57c
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.out
@@ -0,0 +1,7 @@
+# Setup configure
+Configuring Custom-0.1.0.0...
+# Setup build
+Preprocessing library for Custom-0.1.0.0..
+Building library for Custom-0.1.0.0..
+Preprocessing executable 'great-exe' for Custom-0.1.0.0..
+Building executable 'great-exe' for Custom-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.test.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..a76e888c2b788d3bc10b186e025120798413d55d
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/custom.test.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE OverloadedStrings #-}
+import           Test.Cabal.Prelude
+import           Test.Cabal.DecodeShowBuildInfo
+import           Control.Monad.Trans.Reader
+
+main = setupTest $ do
+  -- No cabal test because per-component is broken with it
+  skipUnlessGhcVersion ">= 8.1"
+  withPackageDb $ do
+    setup_build ["--enable-build-info"]
+    env <- ask
+    let buildInfoFp = testDistDir env </> "build-info.json"
+    buildInfo <- decodeBuildInfoFile buildInfoFp
+    assertCommonBuildInfo buildInfo
+    let [libBI, exeBI] = components buildInfo
+    
+    assertComponentPure libBI defCompAssertion
+      { modules = ["MyLib"]
+      , compType = "lib"
+      , sourceDirs = ["src"]
+      }
+
+    assertComponentPure exeBI defCompAssertion
+      { sourceFiles = ["Main.hs"]
+      , compType = "exe"
+      , sourceDirs = ["app"]
+      }
+
diff --git a/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/src/MyLib.hs b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/src/MyLib.hs
new file mode 100644
index 0000000000000000000000000000000000000000..e657c4403f66f966da13d2027bf595d9673387f6
--- /dev/null
+++ b/cabal-testsuite/PackageTests/ShowBuildInfo/Custom/src/MyLib.hs
@@ -0,0 +1,4 @@
+module MyLib (someFunc) where
+
+someFunc :: IO ()
+someFunc = putStrLn "someFunc"
diff --git a/cabal-testsuite/cabal-testsuite.cabal b/cabal-testsuite/cabal-testsuite.cabal
index a3a9ad46f276e8b89a65e1592c6b9cdb8b9b84b4..5285bffb84600b4916c09d1c99b526f9150dc396 100644
--- a/cabal-testsuite/cabal-testsuite.cabal
+++ b/cabal-testsuite/cabal-testsuite.cabal
@@ -39,6 +39,7 @@ library
   hs-source-dirs: src
   exposed-modules:
     Test.Cabal.CheckArMetadata
+    Test.Cabal.DecodeShowBuildInfo
     Test.Cabal.Monad
     Test.Cabal.OutputNormalizer
     Test.Cabal.Plan
diff --git a/cabal-testsuite/src/Test/Cabal/DecodeShowBuildInfo.hs b/cabal-testsuite/src/Test/Cabal/DecodeShowBuildInfo.hs
new file mode 100644
index 0000000000000000000000000000000000000000..47fbcc837953c7c5113a7033c233fc3a1a427942
--- /dev/null
+++ b/cabal-testsuite/src/Test/Cabal/DecodeShowBuildInfo.hs
@@ -0,0 +1,188 @@
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE FlexibleContexts #-}
+module Test.Cabal.DecodeShowBuildInfo where
+
+import           Test.Cabal.Prelude
+import           Test.Cabal.Plan
+import           Distribution.Compat.Stack
+import           Distribution.Text (display)
+import           Distribution.Types.ComponentName
+import           Distribution.Types.LibraryName
+import           Distribution.Types.UnqualComponentName
+import           Distribution.Package
+import           Distribution.Pretty (prettyShow)
+import           Control.Monad.Trans.Reader
+import           Data.Aeson
+import           GHC.Generics
+import           System.Exit
+
+-- | Execute 'cabal build --enable-build-info'.
+--
+-- Results can be read via 'withPlan', 'buildInfoFile' and 'decodeBuildInfoFile'.
+runShowBuildInfo :: [String] -> TestM ()
+runShowBuildInfo args = cabal "build" ("--enable-build-info":args)
+
+-- | Read 'build-info.json' for a given package and component
+-- from disk and record the content. Helpful for defining test-cases
+-- where the build info matters.
+recordBuildInfo :: PackageName -> ComponentName -> TestM ()
+recordBuildInfo pkgName cname = do
+  Just plan <- fmap testPlan ask
+  let fp = buildInfoFile plan pkgName cname
+  recordMode RecordAll $ do
+    recordHeader ["show-build-info", prettyShow pkgName, prettyShow cname]
+    buildInfo <- liftIO $ readFile fp
+    recordLog $ Result ExitSuccess "build --enable-build-info" buildInfo
+
+-- | Decode the given filepath into a 'BuildInfo'.
+--
+-- If the filepath doesn't exist or its contents are not a valid 'BuildInfo'
+-- json file, then an error is raised.
+decodeBuildInfoFile :: FilePath -> TestM BuildInfo
+decodeBuildInfoFile fp = do
+  shouldExist fp
+  res <- liftIO $ eitherDecodeFileStrict fp
+  case res of
+    Left err -> fail $ "Could not parse show-build-info file: " ++ err
+    Right buildInfos -> return buildInfos
+
+data BuildInfo = BuildInfo
+  { cabalLibVersion :: String
+  , compiler :: CompilerInfo
+  , components :: [ComponentInfo]
+  } deriving (Generic, Show)
+
+data CompilerInfo = CompilerInfo
+  { flavour :: String
+  , compilerId :: String
+  , path :: String
+  } deriving (Generic, Show)
+
+data ComponentInfo = ComponentInfo
+  { componentType :: String
+  , componentName :: String
+  , componentUnitId :: String
+  , componentCompilerArgs :: [String]
+  , componentModules :: [String]
+  , componentSrcFiles :: [FilePath]
+  , componentHsSrcDirs :: [FilePath]
+  , componentSrcDir :: FilePath
+  } deriving (Generic, Show)
+
+instance ToJSON BuildInfo where
+  toEncoding = genericToEncoding defaultOptions
+instance FromJSON BuildInfo where
+  parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = camelTo2 '-' }
+
+instance ToJSON CompilerInfo where
+  toEncoding = genericToEncoding defaultOptions
+instance FromJSON CompilerInfo where
+  parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = camelTo2 '-' }
+
+instance ToJSON ComponentInfo where
+  toEncoding = genericToEncoding defaultOptions
+instance FromJSON ComponentInfo where
+  parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = drop 10 . camelTo2 '-' }
+
+-- -----------------------------------------------------------
+-- Assertion Helpers to define succinct test cases
+-- -----------------------------------------------------------
+
+data ComponentAssertion = ComponentAssertion
+  { unitIdPred :: (String -> Bool)
+  -- ^ Predicate to apply to a component's unit id.
+  , compilerArgsPred :: ([String] -> Bool)
+  -- ^ Predicate the compilation arguments must satisfy.
+  , modules :: [String]
+  -- ^ Which modules should a component contain.
+  , sourceFiles :: [FilePath]
+  -- ^ Which source files are part of a component.
+  , sourceDirs :: [FilePath]
+  -- ^ Expected source directories for a component.
+  , compType :: String
+  -- ^ Type of the component, usually one of 'bench', 'exe', 'test', 'lib', 'flib'
+  }
+
+defCompAssertion :: ComponentAssertion
+defCompAssertion = ComponentAssertion
+  { unitIdPred = not . null
+  , compilerArgsPred = not . null
+  , modules = []
+  , sourceFiles = []
+  , sourceDirs = []
+  , compType = mempty
+  }
+
+-- | Assert common build information, such as compiler location, compiler version
+-- and cabal library version.
+assertCommonBuildInfo :: WithCallStack (BuildInfo -> TestM ())
+assertCommonBuildInfo buildInfo = do
+  assertEqual "Cabal Version" (display cabalVersionLibrary) (cabalLibVersion buildInfo)
+  assertEqual "Compiler flavour" "ghc" (flavour $ compiler buildInfo)
+  assertBool "Compiler id" (and $ zipWith (==) "ghc" (compilerId $ compiler buildInfo))
+  assertBool "Compiler path non-empty" (not . null . path $ compiler buildInfo)
+
+-- | Pure assertion helper. Check whether the given 'ComponentInfo' satisfy
+-- the 'ComponentAssertion'.
+assertComponentPure :: WithCallStack (ComponentInfo -> ComponentAssertion -> TestM ())
+assertComponentPure component ComponentAssertion{..} = do
+  assertEqual "Component type" compType (componentType component)
+  assertBool  "Component Unit Id" (unitIdPred $ componentUnitId component)
+  assertBool  "Component compiler args" (compilerArgsPred  $ componentCompilerArgs component)
+  assertEqual "Component modules" modules (componentModules component)
+  assertEqual "Component source files" sourceFiles (componentSrcFiles component)
+  assertEqual "Component source directories" sourceDirs (componentHsSrcDirs component)
+
+-- | @'assertComponent' pkgName cname assertion@
+--
+-- Assert that a component identified by 'pkgName' and 'cname', generated
+-- a 'build-info.json' and its contents satisfy the assertions specified in 'assertion'.
+--
+-- This assertion must be wrapped in 'withPlan'.
+assertComponent :: WithCallStack (PackageName -> ComponentName -> ComponentAssertion -> TestM ())
+assertComponent pkgName cname assert = do
+  Just plan <- fmap testPlan ask
+  let fp = buildInfoFile plan pkgName cname
+  buildInfo <- decodeBuildInfoFile fp
+  assertCommonBuildInfo buildInfo
+
+  let component = findComponentInfo buildInfo
+  let assertWithCompType = assert { compType = compTypeStr cname }
+  assertComponentPure component assertWithCompType
+  where
+    compTypeStr :: ComponentName -> String
+    compTypeStr (CLibName _)    = "lib"
+    compTypeStr (CFLibName _) = "flib"
+    compTypeStr (CExeName _) = "exe"
+    compTypeStr (CTestName _) = "test"
+    compTypeStr (CBenchName _) = "bench"
+
+    findComponentInfo :: BuildInfo -> ComponentInfo
+    findComponentInfo buildInfo =
+      case filter (\c -> prettyShow cname == componentName c) (components buildInfo) of
+        [x] -> x
+        [] ->  error $ "findComponentInfo: component " ++ prettyShow cname ++ " does not"
+                    ++ " exist in build info-file"
+        _   -> error $ "findComponentInfo: found multiple copies of component " ++ prettyShow cname
+                    ++ " in build info plan"
+
+-- | Helper function to create an executable component name.
+exe :: String -> ComponentName
+exe = CExeName . mkUnqualComponentName
+
+-- | Helper function to create a named sub-library component name.
+lib :: String -> ComponentName
+lib = CLibName . LSubLibName . mkUnqualComponentName
+
+-- | Helper function to create an test component name.
+test :: String -> ComponentName
+test = CTestName . mkUnqualComponentName
+
+-- | Helper function to create an benchmark component name.
+bench :: String -> ComponentName
+bench = CBenchName . mkUnqualComponentName
+
+-- | Helper function to create a main library component name.
+mainLib :: ComponentName
+mainLib = CLibName LMainLibName
diff --git a/cabal-testsuite/src/Test/Cabal/Monad.hs b/cabal-testsuite/src/Test/Cabal/Monad.hs
index fa1407eae03dc7288cc7dd2090d5bd74609f25a9..376d144e60689468399983db3fd069ef305ce420 100644
--- a/cabal-testsuite/src/Test/Cabal/Monad.hs
+++ b/cabal-testsuite/src/Test/Cabal/Monad.hs
@@ -48,6 +48,8 @@ module Test.Cabal.Monad (
     CommonArgs(..),
     renderCommonArgs,
     commonArgParser,
+    -- * Version Constants
+    cabalVersionLibrary,
 ) where
 
 import Test.Cabal.Script
@@ -63,9 +65,11 @@ import Distribution.Simple.Program.Db
 import Distribution.Simple.Program
 import Distribution.Simple.Configure
     ( configCompilerEx )
+import qualified Distribution.Simple.Utils as U (cabalVersion)
 import Distribution.Text
 
 import Distribution.Verbosity
+import Distribution.Version
 
 import Data.Monoid ((<>), mempty)
 import qualified Control.Exception as E
@@ -399,6 +403,7 @@ mkNormalizerEnv = do
     list_out <- liftIO $ readProcess (programPath ghc_pkg_program)
                       ["list", "--global", "--simple-output"] ""
     tmpDir <- liftIO $ getTemporaryDirectory
+
     return NormalizerEnv {
         normalizerRoot
             = addTrailingPathSeparator (testSourceDir env),
@@ -411,8 +416,14 @@ mkNormalizerEnv = do
         normalizerKnownPackages
             = mapMaybe simpleParse (words list_out),
         normalizerPlatform
-            = testPlatform env
+            = testPlatform env,
+        normalizerCabalVersion
+            = cabalVersionLibrary
     }
+    where
+
+cabalVersionLibrary :: Version
+cabalVersionLibrary = U.cabalVersion
 
 requireProgramM :: Program -> TestM ConfiguredProgram
 requireProgramM program = do
diff --git a/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs b/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs
index 4e6aec198909e0f816a4d7c38d6251da99fc947b..e67c63b0dc66a1d5dbfcf342f86360855dcec101 100644
--- a/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs
+++ b/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs
@@ -49,6 +49,7 @@ normalizeOutput nenv =
           "/incoming/new-<RAND>"
     -- Normalize architecture
   . resub (posixRegexEscape (display (normalizerPlatform nenv))) "<ARCH>"
+  . normalizeBuildInfoJson
     -- Some GHC versions are chattier than others
   . resub "^ignoring \\(possibly broken\\) abi-depends field for packages" ""
     -- Normalize the current GHC version.  Apply this BEFORE packageIdRegex,
@@ -67,6 +68,30 @@ normalizeOutput nenv =
         resub (posixRegexEscape (display pid) ++ "(-[A-Za-z0-9.-]+)?")
               (prettyShow (packageName pid) ++ "-<VERSION>")
 
+    -- 'build-info.json' contains a plethora of host system specific information.
+    --
+    -- This must happen before the root-dir normalisation.
+    normalizeBuildInfoJson =
+        -- Remove ghc path from show-build-info output
+        resub ("\"path\":\"[^\"]*\"}")
+          "\"path\":\"<GHCPATH>\"}"
+        -- Remove cabal version output from show-build-info output
+      . resub ("{\"cabal-version\":\"" ++ posixRegexEscape (display (normalizerCabalVersion nenv)) ++ "\"")
+              "{\"cabal-version\":\"<CABALVER>\""
+        -- Remove the package id for stuff such as:
+        -- > "-package-id","base-4.14.0.0-<some-hash>"
+        -- and replace it with:
+        -- > "-package-id","<PACKAGEDEP>"
+        --
+        -- Otherwise, output can not be properly normalized as on MacOs we remove
+        -- vowels from packages to make the names shorter.
+        -- E.g. "another-framework-0.8.1.1" -> "nthr-frmwrk-0.8.1.1"
+        --
+        -- This makes it impossible to have a stable package id, thus remove it completely.
+        -- Check manually in your test-cases if the package-id needs to be verified.
+      . resub ("\"-package-id\",\"([^\"]*)\"")
+              "\"-package-id\",\"<PACKAGEDEP>\""
+
 data NormalizerEnv = NormalizerEnv
     { normalizerRoot          :: FilePath
     , normalizerTmpDir        :: FilePath
@@ -74,6 +99,7 @@ data NormalizerEnv = NormalizerEnv
     , normalizerGhcVersion    :: Version
     , normalizerKnownPackages :: [PackageId]
     , normalizerPlatform      :: Platform
+    , normalizerCabalVersion  :: Version
     }
 
 posixSpecialChars :: [Char]
diff --git a/cabal-testsuite/src/Test/Cabal/Plan.hs b/cabal-testsuite/src/Test/Cabal/Plan.hs
index 223832edc19f0406e3a921b61e2c95360159a622..0665de9a9b9b21b1222ea424b4aa7eecd883bf3c 100644
--- a/cabal-testsuite/src/Test/Cabal/Plan.hs
+++ b/cabal-testsuite/src/Test/Cabal/Plan.hs
@@ -5,6 +5,7 @@ module Test.Cabal.Plan (
     Plan,
     DistDirOrBinFile(..),
     planDistDir,
+    buildInfoFile,
 ) where
 
 import Distribution.Parsec (simpleParsec)
@@ -27,6 +28,7 @@ data InstallItem
 -- local or inplace package
 data ConfiguredInplace = ConfiguredInplace
     { configuredInplaceDistDir       :: FilePath
+    , configuredInplaceBuildInfo     :: Maybe FilePath
     , configuredInplacePackageName   :: PackageName
     , configuredInplaceComponentName :: Maybe ComponentName }
 
@@ -57,9 +59,10 @@ instance FromJSON InstallItem where
 instance FromJSON ConfiguredInplace where
     parseJSON (Object v) = do
         dist_dir <- v .: "dist-dir"
+        build_info <- v .:? "build-info"
         pkg_name <- v .: "pkg-name"
         component_name <- v .:? "component-name"
-        return (ConfiguredInplace dist_dir pkg_name component_name)
+        return (ConfiguredInplace dist_dir build_info pkg_name component_name)
     parseJSON invalid = typeMismatch "ConfiguredInplace" invalid
 
 instance FromJSON ConfiguredGlobal where
@@ -109,3 +112,25 @@ planDistDir plan pkg_name cname =
                     Nothing     -> True
                     Just cname' -> cname == cname'
         return $ DistDir $ configuredInplaceDistDir conf
+
+buildInfoFile :: Plan -> PackageName -> ComponentName -> FilePath
+buildInfoFile plan pkg_name cname =
+    case concatMap p (planInstallPlan plan) of
+        [Just x] -> x
+        [Nothing] -> error $ "buildInfoFile: component " ++ prettyShow cname
+                    ++ " of package " ++ prettyShow pkg_name ++ " does not"
+                    ++ " have a build info-file"
+        []  -> error $ "buildInfoFile: component " ++ prettyShow cname
+                    ++ " of package " ++ prettyShow pkg_name ++ " either does not"
+                    ++ " exist in the install plan or build info-file"
+        _   -> error $ "buildInfoFile: found multiple copies of component " ++ prettyShow cname
+                    ++ " of package " ++ prettyShow pkg_name ++ " in install plan"
+  where
+    p APreExisting      = []
+    p (AConfiguredGlobal _) = []
+    p (AConfiguredInplace conf) = do
+        guard (configuredInplacePackageName conf == pkg_name)
+        guard $ case configuredInplaceComponentName conf of
+                    Nothing     -> True
+                    Just cname' -> cname == cname'
+        return $ configuredInplaceBuildInfo conf