
Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC Commits: b8746ad6 by Hassan Al-Awwadi at 2025-07-09T16:05:24+02:00 qAddDependentDirectory and addDependentDirectory now return a list of files too. addDependentDirectory_ adds the dependencies and ignores the output. - - - - - 1bbd9943 by Hassan Al-Awwadi at 2025-07-09T16:20:23+02:00 interface test changed to include addDependentDirectory_ - - - - - d12c1e73 by Hassan Al-Awwadi at 2025-07-09T17:00:04+02:00 fixed test case for qAddDependentDirectory. At least, it works locally, so hopefully it works in the pipeline... - - - - - 9 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 - testsuite/tests/th/Makefile - testsuite/tests/th/TH_Depends_Dir.hs - testsuite/tests/th/TH_Depends_Dir.stdout - testsuite/tests/th/TH_Depends_External_Dir.hs → testsuite/tests/th/TH_Depends_Dir_External.hs Changes: ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -169,7 +169,7 @@ import GHC.Parser.HaddockLex (lexHsDoc) import GHC.Parser (parseIdentifier) import GHC.Rename.Doc (rnHsDoc) - +import System.Directory(listDirectory) {- Note [Template Haskell state diagram] @@ -1524,6 +1524,13 @@ 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 () + qAddDependentDirectory :: FilePath -> m [FilePath] -- | See 'addTempFile'. qAddTempFile :: String -> m FilePath @@ -836,9 +836,26 @@ getPackageRoot = Q qGetPackageRoot -- -- * ghc -M does not know about these dependencies - it does not execute TH. -- --- * The dependency is shallow, just a hash of its direct contents -addDependentDirectory :: FilePath -> Q () -addDependentDirectory dp = Q (qAddDependentDirectory dp) +-- * 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 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 ()) + AddDependentDirectory :: FilePath -> THMessage (THResult [FilePath]) AddTempFile :: String -> THMessage (THResult FilePath) AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ()) AddCorePlugin :: String -> THMessage (THResult ()) ===================================== libraries/template-haskell/Language/Haskell/TH/Syntax.hs ===================================== @@ -33,6 +33,7 @@ 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 () + qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m [GHC.Internal.IO.FilePath] qAddTempFile :: GHC.Internal.Base.String -> m GHC.Internal.IO.FilePath qAddTopDecls :: [Dec] -> m () qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m () @@ -1780,7 +1780,8 @@ module Language.Haskell.TH.Syntax where type VarStrictType :: * type VarStrictType = VarBangType addCorePlugin :: GHC.Internal.Base.String -> Q () - addDependentDirectory :: GHC.Internal.IO.FilePath -> Q () + addDependentDirectory :: GHC.Internal.IO.FilePath -> Q [GHC.Internal.IO.FilePath] + 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 () ===================================== testsuite/tests/th/Makefile ===================================== @@ -46,9 +46,9 @@ TH_Depends: .PHONY: TH_Depends_Dir TH_Depends_Dir: rm -rf TH_Depends_external - $(RM) TH_Depends TH_Depends.exe - $(RM) TH_Depends.o TH_Depends.hi - $(RM) TH_Depends_External.o TH_Depends_External.hi + $(RM) TH_Depends_Dir TH_Depends_Dir.exe + $(RM) TH_Depends_Dir.o TH_Depends_Dir.hi + $(RM) TH_Depends_Dir_External.o TH_Depends_Dir_External.hi mkdir TH_Depends_external '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir ===================================== testsuite/tests/th/TH_Depends_Dir.hs ===================================== @@ -3,7 +3,7 @@ module Main where -import TH_Depends_External (checkDirectoryContent) +import TH_Depends_Dir_External (checkDirectoryContent) main :: IO () -main = putStrLn $checkDirectoryContent +main = putStrLn $checkDirectoryContent \ No newline at end of file ===================================== testsuite/tests/th/TH_Depends_Dir.stdout ===================================== @@ -1,3 +1,2 @@ no files? - yes files! \ No newline at end of file ===================================== testsuite/tests/th/TH_Depends_External_Dir.hs → testsuite/tests/th/TH_Depends_Dir_External.hs ===================================== @@ -1,18 +1,15 @@ -module TH_Depends_External where +module TH_Depends_Dir_External where import Language.Haskell.TH.Syntax import Language.Haskell.TH.Lib import System.Directory (listDirectory) -import Control.Monad.IO.Class (liftIO) checkDirectoryContent :: Q Exp checkDirectoryContent = do - let externalDependency = "TH_Depends_external" - qAddDependentDirectory externalDependency - files <- liftIO $ listDirectory externalDependency - - let s = case files - [] -> "no files?" - _ -> "yes files!" + qAddDependentDirectory "TH_Depends_external" + l <- qRunIO $ listDirectory "TH_Depends_external" + let s = case l of + [] -> "no files?" + _ -> "yes files!" stringE s \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4ae1992198aea378e5c0fefae1b66f... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4ae1992198aea378e5c0fefae1b66f... You're receiving this email because of your account on gitlab.haskell.org.