summaryrefslogtreecommitdiff
path: root/hadrian/src/Rules/Test.hs
blob: f5d0dd53b67ae99d00cc827518a6d4e3d7c63751 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
module Rules.Test (testRules) where

import System.Environment

import Base
import CommandLine
import Expression
import Flavour
import Oracles.Setting
import Oracles.TestSettings
import Packages
import Settings
import Settings.Default
import Settings.Builders.RunTest
import Target
import Utilities

ghcConfigHsPath :: FilePath
ghcConfigHsPath = "testsuite/mk/ghc-config.hs"

ghcConfigProgPath :: FilePath
ghcConfigProgPath = "test/bin/ghc-config" <.> exe

checkPprProgPath, checkPprSourcePath :: FilePath
checkPprProgPath = "test/bin/check-ppr" <.> exe
checkPprSourcePath = "utils/check-ppr/Main.hs"

checkApiAnnotationsProgPath, checkApiAnnotationsSourcePath :: FilePath
checkApiAnnotationsProgPath = "test/bin/check-api-annotations" <.> exe
checkApiAnnotationsSourcePath = "utils/check-api-annotations/Main.hs"

checkPrograms :: [(FilePath, FilePath)]
checkPrograms =
    [ (checkPprProgPath, checkPprSourcePath)
    , (checkApiAnnotationsProgPath, checkApiAnnotationsSourcePath)
    ]

ghcConfigPath :: FilePath
ghcConfigPath = "test/ghcconfig"

-- TODO: clean up after testing
testRules :: Rules ()
testRules = do
    root <- buildRootRules

    -- Using program shipped with testsuite to generate ghcconfig file.
    root -/- ghcConfigProgPath %> \_ -> do
        ghc0Path <- (<.> exe) <$> getCompilerPath "stage0"
        cmd [ghc0Path] [ghcConfigHsPath, "-o" , root -/- ghcConfigProgPath]

    -- Rules for building check-ppr and check-ppr-annotations with the compiler
    -- we are going to test (in-tree or out-of-tree).
    forM_ checkPrograms $ \(progPath, sourcePath) ->
        root -/- progPath %> \path -> do
            testGhc <- testCompiler <$> userSetting defaultTestArgs
            top <- topDirectory
            when (testGhc `elem` ["stage1", "stage2", "stage3"]) $ do
                let stg = stageOf testGhc
                need . (:[]) =<< programPath (Context stg ghc vanilla)
            bindir <- getBinaryDirectory testGhc
            cmd [bindir </> "ghc" <.> exe]
                ["-package", "ghc", "-o", top -/- path, top -/- sourcePath]

    root -/- ghcConfigPath %> \_ -> do
        args <- userSetting defaultTestArgs
        let testGhc = testCompiler args
            stg = stageOf testGhc
        ghcPath <- getCompilerPath testGhc
        when (testGhc `elem` ["stage1", "stage2", "stage3"]) $
            need . (:[]) =<< programPath (Context stg ghc vanilla)
        need [root -/- ghcConfigProgPath]
        cmd [FileStdout $ root -/- ghcConfigPath] (root -/- ghcConfigProgPath)
            [ghcPath]

    root -/- timeoutPath %> \_ -> timeoutProgBuilder

    "test" ~> do
        needTestBuilders

        -- TODO : Should we remove the previosly generated config file?
        -- Prepare Ghc configuration file for input compiler.
        need [root -/- ghcConfigPath, root -/- timeoutPath]

        args <- userSetting defaultTestArgs
        ghcPath <- getCompilerPath (testCompiler args)

        -- TODO This approach doesn't work.
        -- Set environment variables for test's Makefile.
        env <- sequence
            [ builderEnvironment "MAKE" $ Make ""
            , builderEnvironment "TEST_HC" $ Ghc CompileHs Stage2
            , AddEnv "TEST_HC_OPTS" <$> runTestGhcFlags ]

        makePath        <- builderPath $ Make ""
        top             <- topDirectory
        ghcFlags        <- runTestGhcFlags
        let ghciFlags = ghcFlags ++ unwords
              [ "--interactive", "-v0", "-ignore-dot-ghci"
              , "-fno-ghci-history"
              ]

        pythonPath      <- builderPath Python
        need [ root -/- checkPprProgPath, root -/- checkApiAnnotationsProgPath ]

        -- Set environment variables for test's Makefile.
        -- TODO: Ideally we would define all those env vars in 'env', so that
        --       Shake can keep track of them, but it is not as easy as it seems
        --       to get that to work.
        liftIO $ do
            -- Many of those env vars are used by Makefiles in the
            -- test infrastructure, or from tests or their
            -- Makefiles.
            setEnv "MAKE" makePath
            setEnv "PYTHON" pythonPath
            setEnv "TEST_HC" ghcPath
            setEnv "TEST_HC_OPTS" ghcFlags
            setEnv "TEST_HC_OPTS_INTERACTIVE" ghciFlags
            setEnv "CHECK_PPR" (top -/- root -/- checkPprProgPath)
            setEnv "CHECK_API_ANNOTATIONS"
                   (top -/- root -/- checkApiAnnotationsProgPath)

            -- This lets us bypass the need to generate a config
            -- through Make, which happens in testsuite/mk/boilerplate.mk
            -- which is in turn included by all test 'Makefile's.
            setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath)

        -- Execute the test target.
        -- We override the verbosity setting to make sure the user can see
        -- the test output: https://gitlab.haskell.org/ghc/ghc/issues/15951.
        withVerbosity Loud $ buildWithCmdOptions env $
            target (vanillaContext Stage2 compiler) RunTest [] []

-- | Build the timeout program.
-- See: https://github.com/ghc/ghc/blob/master/testsuite/timeout/Makefile#L23
timeoutProgBuilder :: Action ()
timeoutProgBuilder = do
    root    <- buildRoot
    windows <- windowsHost
    if windows
        then do
            prog <- programPath =<< programContext Stage1 timeout
            copyFile prog (root -/- timeoutPath)
        else do
            python <- builderPath Python
            copyFile "testsuite/timeout/timeout.py" (root -/- timeoutPath <.> "py")
            let script = unlines
                    [ "#!/usr/bin/env sh"
                    , "exec " ++ python ++ " $0.py \"$@\"" ]
            writeFile' (root -/- timeoutPath) script
            makeExecutable (root -/- timeoutPath)

needTestBuilders :: Action ()
needTestBuilders = do
    testGhc <- testCompiler <$> userSetting defaultTestArgs
    when (testGhc `elem` ["stage1", "stage2", "stage3"]) needTestsuitePackages

-- | Build extra programs and libraries required by testsuite
needTestsuitePackages :: Action ()
needTestsuitePackages = do
    testGhc <- testCompiler <$> userSetting defaultTestArgs
    when (testGhc `elem` ["stage1", "stage2", "stage3"]) $ do
        let stg = stageOf testGhc
        allpkgs   <- packages <$> flavour
        stgpkgs   <- allpkgs (succ stg)
        testpkgs  <- testsuitePackages
        targets <- mapM (needFile stg) (stgpkgs ++ testpkgs)
        needIservBins
        need targets

-- stage 1 ghc lives under stage0/bin,
-- stage 2 ghc lives under stage1/bin, etc
stageOf :: String -> Stage
stageOf "stage1" = Stage0
stageOf "stage2" = Stage1
stageOf "stage3" = Stage2
stageOf _ = error "unexpected stage argument"

needIservBins :: Action ()
needIservBins = do
    -- iserv is not supported under Windows
    windows <- windowsHost
    when (not windows) $ do
        testGhc <- testCompiler <$> userSetting defaultTestArgs
        let stg = stageOf testGhc
        rtsways <- interpretInContext (vanillaContext stg ghc) getRtsWays
        need =<< traverse programPath
            [ Context stg iserv w
            | w <- [vanilla, profiling, dynamic]
            , w `elem` rtsways
            ]

needFile :: Stage -> Package -> Action FilePath
needFile stage pkg
    | isLibrary pkg = pkgConfFile (Context stage pkg profilingDynamic)
    | otherwise     = programPath =<< programContext stage pkg