5
5
{-# LANGUAGE RankNTypes #-}
6
6
{-# LANGUAGE TupleSections #-}
7
7
8
- module Distribution.Simple.GHC.Build.Modules (buildHaskellModules , BuildWay (.. ), buildWayPrefix ) where
8
+ module Distribution.Simple.GHC.Build.Modules
9
+ ( buildHaskellModules
10
+ , BuildWay (.. )
11
+ , buildWayPrefix
12
+ , componentInputs
13
+ ) where
9
14
10
15
import Control.Monad.IO.Class
11
16
import Distribution.Compat.Prelude
@@ -98,8 +103,10 @@ buildHaskellModules
98
103
-- ^ The parallelism strategy (e.g. num of jobs)
99
104
-> ConfiguredProgram
100
105
-- ^ The GHC configured program
101
- -> PD. PackageDescription
102
- -- ^ The package description
106
+ -> Maybe (SymbolicPath Pkg File )
107
+ -- ^ Optional path to a Haskell Main file to build
108
+ -> [ModuleName ]
109
+ -- ^ The Haskell modules to build
103
110
-> SymbolicPath Pkg ('Dir Artifacts )
104
111
-- ^ The path to the build directory for this target, which
105
112
-- has already been created.
@@ -112,7 +119,7 @@ buildHaskellModules
112
119
-- invocation used to compile the component in that 'BuildWay'.
113
120
-- This can be useful in, eg, a linker invocation, in which we want to use the
114
121
-- same options and list the same inputs as those used for building.
115
- buildHaskellModules numJobs ghcProg pkg_descr buildTargetDir neededLibWays pbci = do
122
+ buildHaskellModules numJobs ghcProg mbMainFile inputModules buildTargetDir neededLibWays pbci = do
116
123
-- See Note [Building Haskell Modules accounting for TH]
117
124
118
125
let
@@ -141,13 +148,14 @@ buildHaskellModules numJobs ghcProg pkg_descr buildTargetDir neededLibWays pbci
141
148
| isCoverageEnabled = Flag $ Hpc. mixDir (coerceSymbolicPath $ coerceSymbolicPath buildTargetDir </> extraCompilationArtifacts) way
142
149
| otherwise = mempty
143
150
144
- (inputFiles, inputModules) <- componentInputs buildTargetDir pkg_descr pbci
145
-
146
151
let
147
152
mbWorkDir = mbWorkDirLBI lbi
148
153
runGhcProg = runGHC verbosity ghcProg comp platform mbWorkDir
149
154
platform = hostPlatform lbi
150
155
156
+ (hsMains, scriptMains) =
157
+ partition (isHaskell . getSymbolicPath) (maybeToList mbMainFile)
158
+
151
159
-- We define the base opts which are shared across different build ways in
152
160
-- 'buildHaskellModules'
153
161
baseOpts way =
@@ -161,16 +169,8 @@ buildHaskellModules numJobs ghcProg pkg_descr buildTargetDir neededLibWays pbci
161
169
ghcOptNoLink = if isLib then NoFlag else toFlag True
162
170
, ghcOptNumJobs = numJobs
163
171
, ghcOptInputModules = toNubListR inputModules
164
- , ghcOptInputFiles =
165
- toNubListR $
166
- if PD. package pkg_descr == fakePackageId
167
- then filter (isHaskell . getSymbolicPath) inputFiles
168
- else inputFiles
169
- , ghcOptInputScripts =
170
- toNubListR $
171
- if PD. package pkg_descr == fakePackageId
172
- then filter (not . isHaskell . getSymbolicPath) inputFiles
173
- else []
172
+ , ghcOptInputFiles = toNubListR hsMains
173
+ , ghcOptInputScripts = toNubListR scriptMains
174
174
, ghcOptExtra = buildWayExtraHcOptions way GHC bi
175
175
, ghcOptHiSuffix = optSuffixFlag (buildWayPrefix way) " hi"
176
176
, ghcOptObjSuffix = optSuffixFlag (buildWayPrefix way) " o"
@@ -248,7 +248,7 @@ buildHaskellModules numJobs ghcProg pkg_descr buildTargetDir neededLibWays pbci
248
248
ProfDynWay -> profDynOpts
249
249
250
250
-- If there aren't modules, or if we're loading the modules in repl, don't build.
251
- unless (forRepl || (null inputFiles && null inputModules)) $ liftIO $ do
251
+ unless (forRepl || (isNothing mbMainFile && null inputModules)) $ liftIO $ do
252
252
-- See Note [Building Haskell Modules accounting for TH]
253
253
let
254
254
neededLibWaysSet = Set. fromList neededLibWays
@@ -348,25 +348,26 @@ buildWayExtraHcOptions = \case
348
348
DynWay -> hcSharedOptions
349
349
ProfDynWay -> hcProfSharedOptions
350
350
351
- -- | Returns a pair of the Haskell input files and Haskell modules of the
352
- -- component being built.
351
+ -- | Returns a pair of the main file and Haskell modules of the component being
352
+ -- built. The main file is not necessarily a Haskell file. It could also be
353
+ -- e.g. a C source, or, a Haskell repl script (that does not necessarily have
354
+ -- an extension).
353
355
--
354
- -- The "input files" are either the path to the main Haskell module, or a repl
355
- -- script (that does not necessarily have an extension).
356
+ -- The main file is Nothing if the component is not executable.
356
357
componentInputs
357
358
:: SymbolicPath Pkg (Dir Artifacts )
358
359
-- ^ Target build dir
359
360
-> PD. PackageDescription
360
361
-> PreBuildComponentInputs
361
362
-- ^ The context and component being built in it.
362
- -> IO ([ SymbolicPath Pkg File ] , [ModuleName ])
363
- -- ^ The Haskell input files , and the Haskell modules
363
+ -> IO (Maybe ( SymbolicPath Pkg File ) , [ModuleName ])
364
+ -- ^ The main input file , and the Haskell modules
364
365
componentInputs buildTargetDir pkg_descr pbci =
365
366
case component of
366
367
CLib lib ->
367
- pure ([] , allLibModules lib clbi)
368
+ pure (Nothing , allLibModules lib clbi)
368
369
CFLib flib ->
369
- pure ([] , foreignLibModules flib)
370
+ pure (Nothing , foreignLibModules flib)
370
371
CExe Executable {buildInfo = bi', modulePath} ->
371
372
exeLikeInputs bi' modulePath
372
373
CTest TestSuite {testBuildInfo = bi', testInterface = TestSuiteExeV10 _ mainFile} ->
@@ -405,6 +406,6 @@ componentInputs buildTargetDir pkg_descr pbci =
405
406
" Enabling workaround for Main module '"
406
407
++ prettyShow mainModName
407
408
++ " ' listed in 'other-modules' illegally!"
408
- return ([ main] , filter (/= mainModName) otherModNames)
409
- else return ([ main] , otherModNames)
410
- else return ([] , otherModNames)
409
+ return (Just main, filter (/= mainModName) otherModNames)
410
+ else return (Just main, otherModNames)
411
+ else return (Just main , otherModNames)
0 commit comments