diff --git a/.gitlab/script/ghcup_version.sh b/.gitlab/script/ghcup_version.sh
index fd109f052acfe551496fc6b9bb27eee0298742f5..f8bdff849165cdcf316092fa07a77050b60372ed 100755
--- a/.gitlab/script/ghcup_version.sh
+++ b/.gitlab/script/ghcup_version.sh
@@ -84,8 +84,10 @@ ghcup-gen check -f ghcup-${JSON_VERSION}.yaml
 eghcup --numeric-version
 
 eghcup install ${GHC_VERSION}
+[ `$(eghcup whereis ghc ${GHC_VERSION}) --numeric-version` = "${GHC_VERSION}" ]
 eghcup set ${GHC_VERSION}
 eghcup install-cabal ${CABAL_VERSION}
+[ `$(eghcup whereis cabal ${CABAL_VERSION}) --numeric-version` = "${CABAL_VERSION}" ]
 
 cabal --version
 
@@ -125,10 +127,10 @@ else
 
 	if [ "${OS}" = "DARWIN" ] ; then
 		eghcup install hls
-		haskell-language-server-wrapper --version
+		$(eghcup whereis hls) --version
 
 		eghcup install stack
-		stack --version
+		$(eghcup whereis stack) --version
 	elif [ "${OS}" = "LINUX" ] ; then
 		if [ "${ARCH}" = "64" ] ; then
 			eghcup install hls
diff --git a/app/ghcup/Main.hs b/app/ghcup/Main.hs
index 726b3055432c4228bf1063842ecd49d359e0bb38..d985fb62c55b5a9fc99dd8d0d2decd7df09f9577 100644
--- a/app/ghcup/Main.hs
+++ b/app/ghcup/Main.hs
@@ -100,6 +100,7 @@ data Command
   | Rm (Either RmCommand RmOptions)
   | DInfo
   | Compile CompileCommand
+  | Whereis WhereisOptions WhereisCommand
   | Upgrade UpgradeOpts Bool
   | ToolRequirements
   | ChangeLog ChangeLogOptions
@@ -190,6 +191,13 @@ data ChangeLogOptions = ChangeLogOptions
   }
 
 
+data WhereisCommand = WhereisTool Tool (Maybe ToolVersion)
+
+data WhereisOptions = WhereisOptions {
+   directory :: Bool
+}
+
+
 -- https://github.com/pcapriotti/optparse-applicative/issues/148
 
 -- | A switch that can be enabled using --foo and disabled using --no-foo.
@@ -335,6 +343,17 @@ com =
            <$> info (compileP <**> helper)
                     (progDesc "Compile a tool from source")
            )
+      <> command
+           "whereis"
+            (info
+             (   (Whereis
+                     <$> (WhereisOptions <$> switch (short 'd' <> long "directory" <> help "return directory of the binary instead of the binary location"))
+                     <*> whereisP
+                 ) <**> helper
+             )
+             (progDesc "Find a tools location"
+             <> footerDoc ( Just $ text whereisFooter ))
+           )
       <> commandGroup "Main commands:"
       )
     <|> subparser
@@ -402,6 +421,23 @@ com =
   By default returns the URI of the ChangeLog of the latest GHC release.
   Pass '-o' to automatically open via xdg-open.|]
 
+  whereisFooter :: String
+  whereisFooter = [s|Discussion:
+  Finds the location of a tool. For GHC, this is the ghc binary, that
+  usually resides in a self-contained "~/.ghcup/ghc/<ghcver>" directory.
+  For cabal/stack/hls this the binary usually at "~/.ghcup/bin/<tool>-<ver>".
+
+Examples:
+  # outputs ~/.ghcup/ghc/8.10.5/bin/ghc.exe
+  ghcup whereis ghc 8.10.5
+  # outputs ~/.ghcup/ghc/8.10.5/bin/
+  ghcup whereis --directory ghc 8.10.5
+  # outputs ~/.ghcup/bin/cabal-3.4.0.0
+  ghcup whereis cabal 3.4.0.0
+  # outputs ~/.ghcup/bin/
+  ghcup whereis --directory cabal 3.4.0.0|]
+
+
 installCabalFooter :: String
 installCabalFooter = [s|Discussion:
   Installs the specified cabal-install version (or a recommended default one)
@@ -706,6 +742,86 @@ Examples:
   ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2 -x armv7-unknown-linux-gnueabihf --config $(pwd)/build.mk -- --enable-unregisterised|]
 
 
+whereisP :: Parser WhereisCommand
+whereisP = subparser
+  (  command
+      "ghc"
+      (WhereisTool GHC <$> info
+        ( optional (toolVersionArgument Nothing (Just GHC)) <**> helper )
+        ( progDesc "Get GHC location"
+        <> footerDoc (Just $ text whereisGHCFooter ))
+      )
+      <>
+     command
+      "cabal"
+      (WhereisTool Cabal <$> info
+        ( optional (toolVersionArgument Nothing (Just Cabal)) <**> helper )
+        ( progDesc "Get cabal location"
+        <> footerDoc (Just $ text whereisCabalFooter ))
+      )
+      <>
+     command
+      "hls"
+      (WhereisTool HLS <$> info
+        ( optional (toolVersionArgument Nothing (Just HLS)) <**> helper )
+        ( progDesc "Get HLS location"
+        <> footerDoc (Just $ text whereisHLSFooter ))
+      )
+      <>
+     command
+      "stack"
+      (WhereisTool Stack <$> info
+        ( optional (toolVersionArgument Nothing (Just Stack)) <**> helper )
+        ( progDesc "Get stack location"
+        <> footerDoc (Just $ text whereisStackFooter ))
+      )
+      <>
+     command
+      "ghcup"
+      (WhereisTool GHCup <$> info ( (pure Nothing) <**> helper ) ( progDesc "Get ghcup location" ))
+  )
+ where
+  whereisGHCFooter = [s|Discussion:
+  Finds the location of a GHC executable, which usually resides in
+  a self-contained "~/.ghcup/ghc/<ghcver>" directory.
+
+Examples:
+  # outputs ~/.ghcup/ghc/8.10.5/bin/ghc.exe
+  ghcup whereis ghc 8.10.5
+  # outputs ~/.ghcup/ghc/8.10.5/bin/
+  ghcup whereis --directory ghc 8.10.5 |]
+
+  whereisCabalFooter = [s|Discussion:
+  Finds the location of a Cabal executable, which usually resides in
+  "~/.ghcup/bin/".
+
+Examples:
+  # outputs ~/.ghcup/bin/cabal-3.4.0.0
+  ghcup whereis cabal 3.4.0.0
+  # outputs ~/.ghcup/bin
+  ghcup whereis --directory cabal 3.4.0.0|]
+
+  whereisHLSFooter = [s|Discussion:
+  Finds the location of a HLS executable, which usually resides in
+  "~/.ghcup/bin/".
+
+Examples:
+  # outputs ~/.ghcup/bin/haskell-language-server-wrapper-1.2.0
+  ghcup whereis hls 1.2.0
+  # outputs ~/.ghcup/bin/
+  ghcup whereis --directory hls 1.2.0|]
+
+  whereisStackFooter = [s|Discussion:
+  Finds the location of a stack executable, which usually resides in
+  "~/.ghcup/bin/".
+
+Examples:
+  # outputs ~/.ghcup/bin/stack-2.7.1
+  ghcup whereis stack 2.7.1
+  # outputs ~/.ghcup/bin/
+  ghcup whereis --directory stack 2.7.1|]
+
+
 ghcCompileOpts :: Parser GHCCompileOptions
 ghcCompileOpts =
   GHCCompileOptions
@@ -1265,6 +1381,17 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
 #endif
                       ]
 
+          let
+            runWhereIs =
+              runLogger
+                . flip runReaderT appstate
+                . runE
+                  @'[ NotInstalled
+                    , NoToolVersionSet
+                    , NextVerNotFound
+                    , TagNotFound
+                    ]
+
           let runUpgrade =
                 runLogger
                   . flip runReaderT appstate
@@ -1628,6 +1755,22 @@ Make sure to clean up #{tmpdir} afterwards.|])
                         runLogger $ $(logError) $ T.pack $ prettyShow e
                         pure $ ExitFailure 9
 
+            Whereis WhereisOptions{..} (WhereisTool tool whereVer) ->
+              runWhereIs (do
+                (v, _) <- liftE $ fromVersion whereVer tool
+                loc <- liftE $ whereIsTool tool v
+                if directory
+                then pure $ takeDirectory loc
+                else pure loc
+                )
+                >>= \case
+                      VRight r -> do
+                        putStr r
+                        pure ExitSuccess
+                      VLeft e -> do
+                        runLogger $ $(logError) $ T.pack $ prettyShow e
+                        pure $ ExitFailure 30
+
             Upgrade uOpts force -> do
               target <- case uOpts of
                 UpgradeInplace  -> Just <$> liftIO getExecutablePath
diff --git a/lib/GHCup.hs b/lib/GHCup.hs
index 1b5f777da7aaf162439fbb42740f68e0ba1ffa36..e6466b3cb8023a231faf52614990e253d95b4db1 100644
--- a/lib/GHCup.hs
+++ b/lib/GHCup.hs
@@ -1880,3 +1880,49 @@ postGHCInstall ver@GHCTargetVersion {..} = do
     $ getMajorMinorV _tvVersion
   forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi _tvTarget)
     >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
+
+
+-- | Reports the binary location of a given tool:
+--
+--   * for GHC, this reports: '~/.ghcup/ghc/\<ver\>/bin/ghc'
+--   * for cabal, this reports '~/.ghcup/bin/cabal-\<ver\>'
+--   * for hls, this reports '~/.ghcup/bin/haskell-language-server-wrapper-\<ver\>'
+--   * for stack, this reports '~/.ghcup/bin/stack-\<ver\>'
+--   * for ghcup, this reports the location of the currently running executable
+whereIsTool :: ( MonadReader AppState m
+               , MonadLogger m
+               , MonadThrow m
+               , MonadFail m
+               , MonadIO m
+               , MonadCatch m
+               , MonadMask m
+               , MonadUnliftIO m
+               )
+            => Tool
+            -> GHCTargetVersion
+            -> Excepts '[NotInstalled] m FilePath
+whereIsTool tool ver@GHCTargetVersion {..} = do
+  AppState { dirs } <- lift ask
+
+  case tool of
+    GHC -> do
+      whenM (lift $ fmap not $ ghcInstalled ver)
+        $ throwE (NotInstalled GHC ver)
+      bdir <- lift $ ghcupGHCDir ver
+      pure (bdir </> "bin" </> "ghc" <> exeExt)
+    Cabal -> do
+      whenM (lift $ fmap not $ cabalInstalled _tvVersion)
+        $ throwE (NotInstalled Cabal (GHCTargetVersion Nothing _tvVersion))
+      pure (binDir dirs </> "cabal-" <> T.unpack (prettyVer _tvVersion) <> exeExt)
+    HLS -> do
+      whenM (lift $ fmap not $ hlsInstalled _tvVersion)
+        $ throwE (NotInstalled HLS (GHCTargetVersion Nothing _tvVersion))
+      pure (binDir dirs </> "haskell-language-server-wrapper-" <> T.unpack (prettyVer _tvVersion) <> exeExt)
+
+    Stack -> do
+      whenM (lift $ fmap not $ stackInstalled _tvVersion)
+        $ throwE (NotInstalled Stack (GHCTargetVersion Nothing _tvVersion))
+      pure (binDir dirs </> "stack-" <> T.unpack (prettyVer _tvVersion) <> exeExt)
+    GHCup -> do
+      currentRunningExecPath <- liftIO getExecutablePath
+      liftIO $ canonicalizePath currentRunningExecPath