[Git][ghc/ghc][wip/haanss/depdir] added a test for qAddDependentDirectory

Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC Commits: 5c81a09c by Hassan Al-Awwadi at 2025-07-07T16:39:55+02:00 added a test for qAddDependentDirectory - - - - - 6 changed files: - testsuite/.gitignore - 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/all.T Changes: ===================================== testsuite/.gitignore ===================================== @@ -1523,6 +1523,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk /tests/th/T8633 /tests/th/TH_Depends /tests/th/TH_Depends_external.txt +/tests/th/TH_Depends_external/dummy.txt /tests/th/TH_StringPrimL /tests/th/TH_import_loop/ModuleA.hi-boot /tests/th/TH_import_loop/ModuleA.o-boot ===================================== testsuite/tests/th/Makefile ===================================== @@ -43,6 +43,20 @@ TH_Depends: '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends ./TH_Depends +.PHONY: TH_Depends_Dir +TH_Depends_Dir: + $(RM) TH_Depends_external/dummy.txt + $(RM) TH_Depends TH_Depends.exe + $(RM) TH_Depends.o TH_Depends.hi + $(RM) TH_Depends_External.o TH_Depends_External.hi + + mk_DIR TH_Depends_external + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir + ./TH_Depends_Dir + sleep 2 + echo "dummy" > TH_Depends_external/dummy.txt + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir + ./TH_Depends_Dir T8333: '$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) $(ghcThWayFlags) T8333.hs < /dev/null ===================================== testsuite/tests/th/TH_Depends_Dir.hs ===================================== @@ -0,0 +1,9 @@ + +{-# LANGUAGE TemplateHaskell #-} + +module Main where + +import TH_Depends_External (checkDirectoryContent) + +main :: IO () +main = putStrLn $checkDirectoryContent ===================================== testsuite/tests/th/TH_Depends_Dir.stdout ===================================== @@ -0,0 +1,3 @@ +no files? + +yes files! \ No newline at end of file ===================================== testsuite/tests/th/TH_Depends_External_Dir.hs ===================================== @@ -0,0 +1,18 @@ + +module TH_Depends_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!" + stringE s \ No newline at end of file ===================================== testsuite/tests/th/all.T ===================================== @@ -214,6 +214,7 @@ test('T5434', [], multimod_compile, ['T5434', '-v0 -Wall ' + config.ghc_th_way_flags]) test('T5508', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('TH_Depends', [only_ways(['normal'])], makefile_test, ['TH_Depends']) +test('TH_Depends_Dir', [only_ways(['normal'])], makefile_test, ['TH_Depends_Dir']) test('T5597', [], multimod_compile, ['T5597', '-v0 ' + config.ghc_th_way_flags]) test('T5665', [], multimod_compile, ['T5665', '-v0 ' + config.ghc_th_way_flags]) test('T5700', [], multimod_compile, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c81a09cbaefacac51022d9f484d25f0... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c81a09cbaefacac51022d9f484d25f0... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Hassan Al-Awwadi (@hassan.awwadi)