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
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:
... | ... | @@ -1523,6 +1523,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk |
1523 | 1523 | /tests/th/T8633
|
1524 | 1524 | /tests/th/TH_Depends
|
1525 | 1525 | /tests/th/TH_Depends_external.txt
|
1526 | +/tests/th/TH_Depends_external/dummy.txt
|
|
1526 | 1527 | /tests/th/TH_StringPrimL
|
1527 | 1528 | /tests/th/TH_import_loop/ModuleA.hi-boot
|
1528 | 1529 | /tests/th/TH_import_loop/ModuleA.o-boot
|
... | ... | @@ -43,6 +43,20 @@ TH_Depends: |
43 | 43 | '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends
|
44 | 44 | ./TH_Depends
|
45 | 45 | |
46 | +.PHONY: TH_Depends_Dir
|
|
47 | +TH_Depends_Dir:
|
|
48 | + $(RM) TH_Depends_external/dummy.txt
|
|
49 | + $(RM) TH_Depends TH_Depends.exe
|
|
50 | + $(RM) TH_Depends.o TH_Depends.hi
|
|
51 | + $(RM) TH_Depends_External.o TH_Depends_External.hi
|
|
52 | +
|
|
53 | + mk_DIR TH_Depends_external
|
|
54 | + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
|
|
55 | + ./TH_Depends_Dir
|
|
56 | + sleep 2
|
|
57 | + echo "dummy" > TH_Depends_external/dummy.txt
|
|
58 | + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
|
|
59 | + ./TH_Depends_Dir
|
|
46 | 60 | |
47 | 61 | T8333:
|
48 | 62 | '$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) $(ghcThWayFlags) T8333.hs < /dev/null
|
1 | + |
|
2 | +{-# LANGUAGE TemplateHaskell #-}
|
|
3 | + |
|
4 | +module Main where
|
|
5 | + |
|
6 | +import TH_Depends_External (checkDirectoryContent)
|
|
7 | + |
|
8 | +main :: IO ()
|
|
9 | +main = putStrLn $checkDirectoryContent |
1 | +no files?
|
|
2 | + |
|
3 | +yes files! |
|
\ No newline at end of file |
1 | + |
|
2 | +module TH_Depends_External where
|
|
3 | + |
|
4 | +import Language.Haskell.TH.Syntax
|
|
5 | +import Language.Haskell.TH.Lib
|
|
6 | +import System.Directory (listDirectory)
|
|
7 | +import Control.Monad.IO.Class (liftIO)
|
|
8 | + |
|
9 | +checkDirectoryContent :: Q Exp
|
|
10 | +checkDirectoryContent = do
|
|
11 | + let externalDependency = "TH_Depends_external"
|
|
12 | + qAddDependentDirectory externalDependency
|
|
13 | + files <- liftIO $ listDirectory externalDependency
|
|
14 | + |
|
15 | + let s = case files
|
|
16 | + [] -> "no files?"
|
|
17 | + _ -> "yes files!"
|
|
18 | + stringE s |
|
\ No newline at end of file |
... | ... | @@ -214,6 +214,7 @@ test('T5434', [], multimod_compile, |
214 | 214 | ['T5434', '-v0 -Wall ' + config.ghc_th_way_flags])
|
215 | 215 | test('T5508', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
|
216 | 216 | test('TH_Depends', [only_ways(['normal'])], makefile_test, ['TH_Depends'])
|
217 | +test('TH_Depends_Dir', [only_ways(['normal'])], makefile_test, ['TH_Depends_Dir'])
|
|
217 | 218 | test('T5597', [], multimod_compile, ['T5597', '-v0 ' + config.ghc_th_way_flags])
|
218 | 219 | test('T5665', [], multimod_compile, ['T5665', '-v0 ' + config.ghc_th_way_flags])
|
219 | 220 | test('T5700', [], multimod_compile,
|