
Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC Commits: 75856938 by Hassan Al-Awwadi at 2025-07-11T13:30:37+02:00 revert returning dir contents from qAddDependetDirectory - - - - - 5 changed files: - compiler/GHC/Tc/Gen/Splice.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghci/GHCi/Message.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout Changes: ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1528,13 +1528,6 @@ instance TH.Quasi TcM where ref <- fmap tcg_dependent_dirs getGblEnv dep_dirs <- readTcRef ref writeTcRef ref (dp:dep_dirs) - -- listDirectory does not return an absolute path, so - -- we need to prepend the directory path to make the - -- the contents absolute. - contents <- liftIO $ listDirectory dp - let path_prefix = dp ++ "\\" - let abs_contents = map (path_prefix ++) contents - return abs_contents qAddTempFile suffix = do dflags <- getDynFlags ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs ===================================== @@ -136,7 +136,7 @@ class (MonadIO m, MonadFail m) => Quasi m where qAddDependentFile :: FilePath -> m () -- | See 'addDependentDirectory'. - qAddDependentDirectory :: FilePath -> m [FilePath] + qAddDependentDirectory :: FilePath -> m () -- | See 'addTempFile'. qAddTempFile :: String -> m FilePath @@ -839,23 +839,9 @@ getPackageRoot = Q qGetPackageRoot -- * The dependency is shallow, just a hash of its direct contents. It returns -- a list of the contents (absolute paths), files and subdirectories both, so -- you can manually depend on (a subset of) those, if you wish. -addDependentDirectory :: FilePath -> Q [FilePath] +addDependentDirectory :: FilePath -> Q () addDependentDirectory dp = Q (qAddDependentDirectory dp) --- | Record external directories that runIO is using (dependent upon). --- The compiler can then recognize that it should re-compile the Haskell file --- when a directory changes. --- --- Expects an absolute directory path. --- --- Notes: --- --- * ghc -M does not know about these dependencies - it does not execute TH. --- --- * The dependency is shallow, just a hash of its direct contents. --- See 'addDependentDirectory' for a version that returns the contents. -addDependentDirectory_ :: FilePath -> Q () -addDependentDirectory_ dp = addDependentDirectory dp >> pure () -- | Record external files that runIO is using (dependent upon). -- The compiler can then recognize that it should re-compile the Haskell file ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -291,7 +291,7 @@ data THMessage a where GetPackageRoot :: THMessage (THResult FilePath) AddDependentFile :: FilePath -> THMessage (THResult ()) - AddDependentDirectory :: FilePath -> THMessage (THResult [FilePath]) + AddDependentDirectory :: FilePath -> THMessage (THResult ()) AddTempFile :: String -> THMessage (THResult FilePath) AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ()) AddCorePlugin :: String -> THMessage (THResult ()) ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -33,7 +33,6 @@ module Language.Haskell.TH.Syntax ( addCorePlugin, addDependentFile, addDependentDirectory, - addDependentDirectory_, addForeignFile, addForeignFilePath, addForeignSource, ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -1715,7 +1715,7 @@ module Language.Haskell.TH.Syntax where qRunIO :: forall a. GHC.Internal.Types.IO a -> m a qGetPackageRoot :: m GHC.Internal.IO.FilePath qAddDependentFile :: GHC.Internal.IO.FilePath -> m () - qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m [GHC.Internal.IO.FilePath] + qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m () qAddTempFile :: GHC.Internal.Base.String -> m GHC.Internal.IO.FilePath qAddTopDecls :: [Dec] -> m () qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m () @@ -1780,8 +1780,7 @@ module Language.Haskell.TH.Syntax where type VarStrictType :: * type VarStrictType = VarBangType addCorePlugin :: GHC.Internal.Base.String -> Q () - addDependentDirectory :: GHC.Internal.IO.FilePath -> Q [GHC.Internal.IO.FilePath] - addDependentDirectory_ :: GHC.Internal.IO.FilePath -> Q () + addDependentDirectory :: GHC.Internal.IO.FilePath -> Q () addDependentFile :: GHC.Internal.IO.FilePath -> Q () addForeignFile :: ForeignSrcLang -> GHC.Internal.Base.String -> Q () addForeignFilePath :: ForeignSrcLang -> GHC.Internal.IO.FilePath -> Q () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/75856938050c94945fc6ca91c0cf5427... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/75856938050c94945fc6ca91c0cf5427... You're receiving this email because of your account on gitlab.haskell.org.