diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 91bf627aaa20dc422fa78d0fc06652254c12ba7a..5217fced5f5fe18e45ba10e1e462244a9971aa5b 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -911,6 +911,7 @@ data WarningFlag =
    | Opt_WarnSpaceAfterBang
    | Opt_WarnMissingDerivingStrategies    -- Since 8.8
    | Opt_WarnPrepositiveQualifiedModule   -- Since TBD
+   | Opt_WarnUnusedPackages               -- Since 8.10
    deriving (Eq, Show, Enum)
 
 data Language = Haskell98 | Haskell2010
@@ -4110,7 +4111,8 @@ wWarningFlagsDeps = [
   flagSpec "missing-space-after-bang"    Opt_WarnSpaceAfterBang,
   flagSpec "partial-fields"              Opt_WarnPartialFields,
   flagSpec "prepositive-qualified-module"
-                                         Opt_WarnPrepositiveQualifiedModule
+                                         Opt_WarnPrepositiveQualifiedModule,
+  flagSpec "unused-packages"             Opt_WarnUnusedPackages
  ]
 
 -- | These @-\<blah\>@ flags can all be reversed with @-no-\<blah\>@
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index a748cc668b304f1ce184d8c83f4d634770180d49..491504d3bdbc0c4ea4e7cf08096ade896511a276 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -267,7 +267,75 @@ data LoadHowMuch
 load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
 load how_much = do
     mod_graph <- depanal [] False
-    load' how_much (Just batchMsg) mod_graph
+    success <- load' how_much (Just batchMsg) mod_graph
+    warnUnusedPackages
+    pure success
+
+-- Note [Unused packages]
+--
+-- Cabal passes `--package-id` flag for each direct dependency. But GHC
+-- loads them lazily, so when compilation is done, we have a list of all
+-- actually loaded packages. All the packages, specified on command line,
+-- but never loaded, are probably unused dependencies.
+
+warnUnusedPackages :: GhcMonad m => m ()
+warnUnusedPackages = do
+    hsc_env <- getSession
+    eps <- liftIO $ hscEPS hsc_env
+
+    let dflags = hsc_dflags hsc_env
+        pit = eps_PIT eps
+
+    let loadedPackages
+          = map (getPackageDetails dflags)
+          . nub . sort
+          . map moduleUnitId
+          . moduleEnvKeys
+          $ pit
+
+        requestedArgs = mapMaybe packageArg (packageFlags dflags)
+
+        unusedArgs
+          = filter (\arg -> not $ any (matching dflags arg) loadedPackages)
+                   requestedArgs
+
+    let warn = makeIntoWarning
+          (Reason Opt_WarnUnusedPackages)
+          (mkPlainErrMsg dflags noSrcSpan msg)
+        msg = hang
+          ( text "The following packages were specified "
+            <> text "via -package or -package-id flags, "
+            <> text "but were not needed for compilation: ")
+          4
+          (sep (map pprUnusedArg unusedArgs))
+
+    when (wopt Opt_WarnUnusedPackages dflags && not (null unusedArgs)) $
+      logWarnings (listToBag [warn])
+
+    where
+        packageArg (ExposePackage _ arg _) = Just arg
+        packageArg _ = Nothing
+
+        pprUnusedArg (PackageArg str) = text str
+        pprUnusedArg (UnitIdArg uid) = ppr uid
+
+        matchingStr :: String -> PackageConfig -> Bool
+        matchingStr str p
+                =  str == sourcePackageIdString p
+                || str == packageNameString p
+
+        matching :: DynFlags -> PackageArg -> PackageConfig -> Bool
+        matching _ (PackageArg str) p = matchingStr str p
+        matching dflags (UnitIdArg uid) p = uid == realUnitId dflags p
+
+        -- For wired-in packages, we have to unwire their id,
+        -- otherwise they won't match package flags
+        realUnitId :: DynFlags -> PackageConfig -> UnitId
+        realUnitId dflags
+          = unwireUnitId dflags
+          . DefiniteUnitId
+          . DefUnitId
+          . installedPackageConfigId
 
 -- | Generalized version of 'load' which also supports a custom
 -- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
diff --git a/docs/users_guide/8.8.1-notes.rst b/docs/users_guide/8.8.1-notes.rst
index a781ec41817a47812c8872156ca583259d0f5b57..972e4c04461185df82361e0af74559c1fe4a43da 100644
--- a/docs/users_guide/8.8.1-notes.rst
+++ b/docs/users_guide/8.8.1-notes.rst
@@ -102,6 +102,8 @@ Compiler
 
 - The :ghc-flag:`-Wcompat` warning group now includes :ghc-flag:`-Wstar-is-type`.
 
+- New :ghc-flag:`-Wunused-packages` warning reports unused packages.
+
 - The :ghc-flag:`-fllvm-pass-vectors-in-regs` flag is now deprecated as vector
   arguments are now passed in registers by default.
 
diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst
index ab61da936a8fbc454a97958d0bd1587ba2d9b3e7..dda7bb656c8d80a2da8db548452ee617e99d3bd1 100644
--- a/docs/users_guide/using-warnings.rst
+++ b/docs/users_guide/using-warnings.rst
@@ -1683,6 +1683,21 @@ of ``-W(no-)*``.
 
         data Foo = Foo { f :: Int } | Bar
 
+.. ghc-flag:: -Wunused-packages
+    :shortdesc: warn when package is requested on command line, but was never loaded.
+    :type: dynamic
+    :reverse: -Wno-unused-packages
+    :category:
+
+    :since: 8.8
+
+    The option :ghc-flag:`-Wunused-packages` warns about packages, specified on
+    command line via :ghc-flag:`-package` or :ghc-flag:`-package-id`, but were not
+    loaded during compication. Usually it means that you have an unused dependency.
+
+    You may want to enable this warning on a clean build or enable :ghc-flag:`-fforce-recomp`
+    in order to get reliable results.
+
 If you're feeling really paranoid, the :ghc-flag:`-dcore-lint` option is a good choice.
 It turns on heavyweight intra-pass sanity-checking within GHC. (It checks GHC's
 sanity, not yours.)
diff --git a/testsuite/tests/warnings/should_compile/UnusedPackages.hs b/testsuite/tests/warnings/should_compile/UnusedPackages.hs
new file mode 100644
index 0000000000000000000000000000000000000000..ef70dbb08497d3b4f90f5a921c5d915e3e5901eb
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/UnusedPackages.hs
@@ -0,0 +1,5 @@
+module Main
+where
+
+main :: IO ()
+main = return ()
diff --git a/testsuite/tests/warnings/should_compile/UnusedPackages.stderr b/testsuite/tests/warnings/should_compile/UnusedPackages.stderr
new file mode 100644
index 0000000000000000000000000000000000000000..7660287aa893b2c4d52e8c878b865f9b808a0a16
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/UnusedPackages.stderr
@@ -0,0 +1,6 @@
+[1 of 1] Compiling Main             ( UnusedPackages.hs, UnusedPackages.o )
+Linking UnusedPackages ...
+
+<no location info>: warning: [-Wunused-packages]
+    The following packages were specified via -package or -package-id flags, but were not needed for compilation: 
+        bytestring
diff --git a/testsuite/tests/warnings/should_compile/all.T b/testsuite/tests/warnings/should_compile/all.T
index fcf03443d3f4b7cef0ece84061344fa73cb51a21..55dee873ae9f051beb96052bc14f4e29474ba891 100644
--- a/testsuite/tests/warnings/should_compile/all.T
+++ b/testsuite/tests/warnings/should_compile/all.T
@@ -27,3 +27,5 @@ test('T16551', [extra_files(['T16551/'])], multimod_compile, ['T16551/A.hs T1655
 test('StarBinder', normal, compile, [''])
 
 test('Overflow', normal, compile, [''])
+
+test('UnusedPackages', normal, multimod_compile, ['UnusedPackages.hs', '-package=bytestring -package=base -Wunused-packages'])