1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
3 {-# LANGUAGE TupleSections #-}
6 -----------------------------------------------------------------------------
8 -- Module : Distribution.Simple.GHC
9 -- Copyright : Isaac Jones 2003-2007
12 -- Maintainer : cabal-devel@haskell.org
13 -- Portability : portable
15 -- This is a fairly large module. It contains most of the GHC-specific code for
16 -- configuring, building and installing packages. It also exports a function
17 -- for finding out what packages are already installed. Configuring involves
18 -- finding the @ghc@ and @ghc-pkg@ programs, finding what language extensions
19 -- this version of ghc supports and returning a 'Compiler' value.
21 -- 'getInstalledPackages' involves calling the @ghc-pkg@ program to find out
22 -- what packages are installed.
24 -- Building is somewhat complex as there is quite a bit of information to take
25 -- into account. We have to build libs and programs, possibly for profiling and
26 -- shared libs. We have to support building libraries that will be usable by
27 -- GHCi and also ghc's @-split-objs@ feature. We have to compile any C files
28 -- using ghc. Linking, especially for @split-objs@ is remarkably complex,
29 -- partly because there tend to be 1,000's of @.o@ files and this can often be
30 -- more than we can pass to the @ld@ or @ar@ programs in one go.
32 -- Installing for libs and exes involves finding the right files and copying
33 -- them to the right places. One of the more tricky things about this module is
34 -- remembering the layout of files in the build directory (which is not
35 -- explicitly documented) and thus what search dirs are used for various kinds
38 module Distribution
.Simple
.GHC
(
42 getInstalledPackagesMonitorFiles
,
44 buildLib
, buildFLib
, buildExe
,
45 replLib
, replFLib
, replExe
,
47 installLib
, installFLib
, installExe
,
52 componentCcGhcOptions
,
57 -- * Constructing and deconstructing GHC environment files
58 Internal
.GhcEnvironmentFileEntry
(..),
59 Internal
.simpleGhcEnvironmentFile
,
60 Internal
.renderGhcEnvironmentFile
,
61 Internal
.writeGhcEnvironmentFile
,
62 Internal
.ghcPlatformAndVersionString
,
63 readGhcEnvironmentFile
,
64 parseGhcEnvironmentFile
,
66 -- * Version-specific implementation quirks
72 import Distribution
.Compat
.Prelude
74 import qualified Distribution
.Simple
.GHC
.Internal
as Internal
75 import Distribution
.Simple
.GHC
.ImplInfo
76 import Distribution
.Simple
.GHC
.EnvironmentParser
77 import Distribution
.PackageDescription
.Utils
(cabalBug
)
78 import Distribution
.PackageDescription
as PD
79 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
80 import qualified Distribution
.InstalledPackageInfo
as InstalledPackageInfo
81 import Distribution
.Simple
.PackageIndex
(InstalledPackageIndex
)
82 import qualified Distribution
.Simple
.PackageIndex
as PackageIndex
83 import Distribution
.Simple
.LocalBuildInfo
84 import Distribution
.Types
.ComponentLocalBuildInfo
85 import qualified Distribution
.Simple
.Hpc
as Hpc
86 import Distribution
.Simple
.BuildPaths
87 import Distribution
.Simple
.Utils
88 import Distribution
.Package
89 import qualified Distribution
.ModuleName
as ModuleName
90 import Distribution
.ModuleName
(ModuleName
)
91 import Distribution
.Simple
.Program
92 import Distribution
.Simple
.Program
.Builtin
(runghcProgram
)
93 import qualified Distribution
.Simple
.Program
.HcPkg
as HcPkg
94 import qualified Distribution
.Simple
.Program
.Ar
as Ar
95 import qualified Distribution
.Simple
.Program
.Ld
as Ld
96 import qualified Distribution
.Simple
.Program
.Strip
as Strip
97 import Distribution
.Simple
.Program
.GHC
98 import Distribution
.Simple
.Setup
99 import qualified Distribution
.Simple
.Setup
as Cabal
100 import Distribution
.Simple
.Compiler
hiding (Flag
)
101 import Distribution
.Version
102 import Distribution
.System
103 import Distribution
.Verbosity
104 import Distribution
.Text
105 import Distribution
.Types
.ForeignLib
106 import Distribution
.Types
.ForeignLibType
107 import Distribution
.Types
.ForeignLibOption
108 import Distribution
.Types
.UnqualComponentName
109 import Distribution
.Utils
.NubList
110 import Language
.Haskell
.Extension
112 import Control
.Monad
(msum)
113 import Data
.Char (isLower)
114 import qualified Data
.Map
as Map
115 import System
.Directory
116 ( doesFileExist, getAppUserDataDirectory
, createDirectoryIfMissing
117 , canonicalizePath
, removeFile, renameFile )
118 import System
.FilePath ( (</>), (<.>), takeExtension
119 , takeDirectory
, replaceExtension
121 import qualified System
.Info
122 #ifndef mingw32_HOST_OS
123 import System
.Posix
(createSymbolicLink
)
124 #endif
/* mingw32_HOST_OS
*/
126 -- -----------------------------------------------------------------------------
129 configure
:: Verbosity
-> Maybe FilePath -> Maybe FilePath
131 -> IO (Compiler
, Maybe Platform
, ProgramDb
)
132 configure verbosity hcPath hcPkgPath conf0
= do
134 (ghcProg
, ghcVersion
, progdb1
) <-
135 requireProgramVersion verbosity ghcProgram
136 (orLaterVersion
(mkVersion
[7,0,1]))
137 (userMaybeSpecifyPath
"ghc" hcPath conf0
)
138 let implInfo
= ghcVersionImplInfo ghcVersion
140 -- Cabal currently supports ghc >= 7.0.1 && < 8.7
141 unless (ghcVersion
< mkVersion
[8,7]) $
143 "Unknown/unsupported 'ghc' version detected "
144 ++ "(Cabal " ++ display cabalVersion
++ " supports 'ghc' version < 8.7): "
145 ++ programPath ghcProg
++ " is version " ++ display ghcVersion
147 -- This is slightly tricky, we have to configure ghc first, then we use the
148 -- location of ghc to help find ghc-pkg in the case that the user did not
149 -- specify the location of ghc-pkg directly:
150 (ghcPkgProg
, ghcPkgVersion
, progdb2
) <-
151 requireProgramVersion verbosity ghcPkgProgram
{
152 programFindLocation
= guessGhcPkgFromGhcPath ghcProg
154 anyVersion
(userMaybeSpecifyPath
"ghc-pkg" hcPkgPath progdb1
)
156 when (ghcVersion
/= ghcPkgVersion
) $ die
' verbosity
$
157 "Version mismatch between ghc and ghc-pkg: "
158 ++ programPath ghcProg
++ " is version " ++ display ghcVersion
++ " "
159 ++ programPath ghcPkgProg
++ " is version " ++ display ghcPkgVersion
161 -- Likewise we try to find the matching hsc2hs and haddock programs.
162 let hsc2hsProgram
' = hsc2hsProgram
{
163 programFindLocation
= guessHsc2hsFromGhcPath ghcProg
165 haddockProgram
' = haddockProgram
{
166 programFindLocation
= guessHaddockFromGhcPath ghcProg
168 hpcProgram
' = hpcProgram
{
169 programFindLocation
= guessHpcFromGhcPath ghcProg
171 runghcProgram
' = runghcProgram
{
172 programFindLocation
= guessRunghcFromGhcPath ghcProg
174 progdb3
= addKnownProgram haddockProgram
' $
175 addKnownProgram hsc2hsProgram
' $
176 addKnownProgram hpcProgram
' $
177 addKnownProgram runghcProgram
' progdb2
179 languages
<- Internal
.getLanguages verbosity implInfo ghcProg
180 extensions0
<- Internal
.getExtensions verbosity implInfo ghcProg
182 ghcInfo
<- Internal
.getGhcInfo verbosity implInfo ghcProg
183 let ghcInfoMap
= Map
.fromList ghcInfo
184 extensions
= -- workaround https://ghc.haskell.org/ticket/11214
185 filterExt JavaScriptFFI
$
186 -- see 'filterExtTH' comment below
187 filterExtTH
$ extensions0
189 -- starting with GHC 8.0, `TemplateHaskell` will be omitted from
190 -- `--supported-extensions` when it's not available.
191 -- for older GHCs we can use the "Have interpreter" property to
192 -- filter out `TemplateHaskell`
193 filterExtTH | ghcVersion
< mkVersion
[8]
194 , Just
"NO" <- Map
.lookup "Have interpreter" ghcInfoMap
195 = filterExt TemplateHaskell
198 filterExt ext
= filter ((/= EnableExtension ext
) . fst)
200 let comp
= Compiler
{
201 compilerId
= CompilerId GHC ghcVersion
,
202 compilerAbiTag
= NoAbiTag
,
204 compilerLanguages
= languages
,
205 compilerExtensions
= extensions
,
206 compilerProperties
= ghcInfoMap
208 compPlatform
= Internal
.targetPlatform ghcInfo
209 -- configure gcc and ld
210 progdb4
= Internal
.configureToolchain implInfo ghcProg ghcInfoMap progdb3
211 return (comp
, compPlatform
, progdb4
)
213 -- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find
214 -- the corresponding tool; e.g. if the tool is ghc-pkg, we try looking
215 -- for a versioned or unversioned ghc-pkg in the same dir, that is:
217 -- > /usr/local/bin/ghc-pkg-ghc-6.6.1(.exe)
218 -- > /usr/local/bin/ghc-pkg-6.6.1(.exe)
219 -- > /usr/local/bin/ghc-pkg(.exe)
221 guessToolFromGhcPath
:: Program
-> ConfiguredProgram
222 -> Verbosity
-> ProgramSearchPath
223 -> IO (Maybe (FilePath, [FilePath]))
224 guessToolFromGhcPath tool ghcProg verbosity searchpath
225 = do let toolname
= programName tool
226 given_path
= programPath ghcProg
227 given_dir
= takeDirectory given_path
228 real_path
<- canonicalizePath given_path
229 let real_dir
= takeDirectory real_path
230 versionSuffix path
= takeVersionSuffix
(dropExeExtension path
)
231 given_suf
= versionSuffix given_path
232 real_suf
= versionSuffix real_path
233 guessNormal dir
= dir
</> toolname
<.> exeExtension buildPlatform
234 guessGhcVersioned dir suf
= dir
</> (toolname
++ "-ghc" ++ suf
)
235 <.> exeExtension buildPlatform
236 guessVersioned dir suf
= dir
</> (toolname
++ suf
)
237 <.> exeExtension buildPlatform
238 mkGuesses dir suf |
null suf
= [guessNormal dir
]
239 |
otherwise = [guessGhcVersioned dir suf
,
240 guessVersioned dir suf
,
242 guesses
= mkGuesses given_dir given_suf
++
243 if real_path
== given_path
245 else mkGuesses real_dir real_suf
246 info verbosity
$ "looking for tool " ++ toolname
247 ++ " near compiler in " ++ given_dir
248 debug verbosity
$ "candidate locations: " ++ show guesses
249 exists
<- traverse
doesFileExist guesses
250 case [ file |
(file
, True) <- zip guesses exists
] of
251 -- If we can't find it near ghc, fall back to the usual
253 [] -> programFindLocation tool verbosity searchpath
254 (fp
:_
) -> do info verbosity
$ "found " ++ toolname
++ " in " ++ fp
255 let lookedAt
= map fst
256 . takeWhile (\(_file
, exist
) -> not exist
)
258 return (Just
(fp
, lookedAt
))
260 where takeVersionSuffix
:: FilePath -> String
261 takeVersionSuffix
= takeWhileEndLE isSuffixChar
263 isSuffixChar
:: Char -> Bool
264 isSuffixChar c
= isDigit c || c
== '.' || c
== '-'
266 -- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find a
267 -- corresponding ghc-pkg, we try looking for both a versioned and unversioned
268 -- ghc-pkg in the same dir, that is:
270 -- > /usr/local/bin/ghc-pkg-ghc-6.6.1(.exe)
271 -- > /usr/local/bin/ghc-pkg-6.6.1(.exe)
272 -- > /usr/local/bin/ghc-pkg(.exe)
274 guessGhcPkgFromGhcPath
:: ConfiguredProgram
275 -> Verbosity
-> ProgramSearchPath
276 -> IO (Maybe (FilePath, [FilePath]))
277 guessGhcPkgFromGhcPath
= guessToolFromGhcPath ghcPkgProgram
279 -- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find a
280 -- corresponding hsc2hs, we try looking for both a versioned and unversioned
281 -- hsc2hs in the same dir, that is:
283 -- > /usr/local/bin/hsc2hs-ghc-6.6.1(.exe)
284 -- > /usr/local/bin/hsc2hs-6.6.1(.exe)
285 -- > /usr/local/bin/hsc2hs(.exe)
287 guessHsc2hsFromGhcPath
:: ConfiguredProgram
288 -> Verbosity
-> ProgramSearchPath
289 -> IO (Maybe (FilePath, [FilePath]))
290 guessHsc2hsFromGhcPath
= guessToolFromGhcPath hsc2hsProgram
292 -- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find a
293 -- corresponding haddock, we try looking for both a versioned and unversioned
294 -- haddock in the same dir, that is:
296 -- > /usr/local/bin/haddock-ghc-6.6.1(.exe)
297 -- > /usr/local/bin/haddock-6.6.1(.exe)
298 -- > /usr/local/bin/haddock(.exe)
300 guessHaddockFromGhcPath
:: ConfiguredProgram
301 -> Verbosity
-> ProgramSearchPath
302 -> IO (Maybe (FilePath, [FilePath]))
303 guessHaddockFromGhcPath
= guessToolFromGhcPath haddockProgram
305 guessHpcFromGhcPath
:: ConfiguredProgram
306 -> Verbosity
-> ProgramSearchPath
307 -> IO (Maybe (FilePath, [FilePath]))
308 guessHpcFromGhcPath
= guessToolFromGhcPath hpcProgram
310 guessRunghcFromGhcPath
:: ConfiguredProgram
311 -> Verbosity
-> ProgramSearchPath
312 -> IO (Maybe (FilePath, [FilePath]))
313 guessRunghcFromGhcPath
= guessToolFromGhcPath runghcProgram
316 getGhcInfo
:: Verbosity
-> ConfiguredProgram
-> IO [(String, String)]
317 getGhcInfo verbosity ghcProg
= Internal
.getGhcInfo verbosity implInfo ghcProg
319 Just version
= programVersion ghcProg
320 implInfo
= ghcVersionImplInfo version
322 -- | Given a single package DB, return all installed packages.
323 getPackageDBContents
:: Verbosity
-> PackageDB
-> ProgramDb
324 -> IO InstalledPackageIndex
325 getPackageDBContents verbosity packagedb progdb
= do
326 pkgss
<- getInstalledPackages
' verbosity
[packagedb
] progdb
327 toPackageIndex verbosity pkgss progdb
329 -- | Given a package DB stack, return all installed packages.
330 getInstalledPackages
:: Verbosity
-> Compiler
-> PackageDBStack
332 -> IO InstalledPackageIndex
333 getInstalledPackages verbosity comp packagedbs progdb
= do
334 checkPackageDbEnvVar verbosity
335 checkPackageDbStack verbosity comp packagedbs
336 pkgss
<- getInstalledPackages
' verbosity packagedbs progdb
337 index <- toPackageIndex verbosity pkgss progdb
338 return $! hackRtsPackage
index
341 hackRtsPackage
index =
342 case PackageIndex
.lookupPackageName
index (mkPackageName
"rts") of
344 -> PackageIndex
.insert (removeMingwIncludeDir rts
) index
345 _
-> index -- No (or multiple) ghc rts package is registered!!
346 -- Feh, whatever, the ghc test suite does some crazy stuff.
348 -- | Given a list of @(PackageDB, InstalledPackageInfo)@ pairs, produce a
349 -- @PackageIndex@. Helper function used by 'getPackageDBContents' and
350 -- 'getInstalledPackages'.
351 toPackageIndex
:: Verbosity
352 -> [(PackageDB
, [InstalledPackageInfo
])]
354 -> IO InstalledPackageIndex
355 toPackageIndex verbosity pkgss progdb
= do
356 -- On Windows, various fields have $topdir/foo rather than full
357 -- paths. We need to substitute the right value in so that when
358 -- we, for example, call gcc, we have proper paths to give it.
359 topDir
<- getLibDir
' verbosity ghcProg
360 let indices = [ PackageIndex
.fromList
(map (Internal
.substTopDir topDir
) pkgs
)
361 |
(_
, pkgs
) <- pkgss
]
362 return $! mconcat
indices
365 Just ghcProg
= lookupProgram ghcProgram progdb
367 getLibDir
:: Verbosity
-> LocalBuildInfo
-> IO FilePath
368 getLibDir verbosity lbi
=
369 dropWhileEndLE
isSpace `
fmap`
370 getDbProgramOutput verbosity ghcProgram
371 (withPrograms lbi
) ["--print-libdir"]
373 getLibDir
' :: Verbosity
-> ConfiguredProgram
-> IO FilePath
374 getLibDir
' verbosity ghcProg
=
375 dropWhileEndLE
isSpace `
fmap`
376 getProgramOutput verbosity ghcProg
["--print-libdir"]
379 -- | Return the 'FilePath' to the global GHC package database.
380 getGlobalPackageDB
:: Verbosity
-> ConfiguredProgram
-> IO FilePath
381 getGlobalPackageDB verbosity ghcProg
=
382 dropWhileEndLE
isSpace `
fmap`
383 getProgramOutput verbosity ghcProg
["--print-global-package-db"]
385 -- | Return the 'FilePath' to the per-user GHC package database.
386 getUserPackageDB
:: Verbosity
-> ConfiguredProgram
-> Platform
-> NoCallStackIO
FilePath
387 getUserPackageDB _verbosity ghcProg platform
= do
388 -- It's rather annoying that we have to reconstruct this, because ghc
389 -- hides this information from us otherwise. But for certain use cases
390 -- like change monitoring it really can't remain hidden.
391 appdir
<- getAppUserDataDirectory
"ghc"
392 return (appdir
</> platformAndVersion
</> packageConfFileName
)
394 platformAndVersion
= Internal
.ghcPlatformAndVersionString
396 packageConfFileName
= "package.conf.d"
397 Just ghcVersion
= programVersion ghcProg
399 checkPackageDbEnvVar
:: Verbosity
-> IO ()
400 checkPackageDbEnvVar verbosity
=
401 Internal
.checkPackageDbEnvVar verbosity
"GHC" "GHC_PACKAGE_PATH"
403 checkPackageDbStack
:: Verbosity
-> Compiler
-> PackageDBStack
-> IO ()
404 checkPackageDbStack verbosity comp
=
405 if flagPackageConf implInfo
406 then checkPackageDbStackPre76 verbosity
407 else checkPackageDbStackPost76 verbosity
408 where implInfo
= ghcVersionImplInfo
(compilerVersion comp
)
410 checkPackageDbStackPost76
:: Verbosity
-> PackageDBStack
-> IO ()
411 checkPackageDbStackPost76 _
(GlobalPackageDB
:rest
)
412 | GlobalPackageDB `
notElem` rest
= return ()
413 checkPackageDbStackPost76 verbosity rest
414 | GlobalPackageDB `
elem` rest
=
415 die
' verbosity
$ "If the global package db is specified, it must be "
416 ++ "specified first and cannot be specified multiple times"
417 checkPackageDbStackPost76 _ _
= return ()
419 checkPackageDbStackPre76
:: Verbosity
-> PackageDBStack
-> IO ()
420 checkPackageDbStackPre76 _
(GlobalPackageDB
:rest
)
421 | GlobalPackageDB `
notElem` rest
= return ()
422 checkPackageDbStackPre76 verbosity rest
423 | GlobalPackageDB `
notElem` rest
=
424 die
' verbosity
$ "With current ghc versions the global package db is always used "
425 ++ "and must be listed first. This ghc limitation is lifted in GHC 7.6,"
426 ++ "see http://hackage.haskell.org/trac/ghc/ticket/5977"
427 checkPackageDbStackPre76 verbosity _
=
428 die
' verbosity
$ "If the global package db is specified, it must be "
429 ++ "specified first and cannot be specified multiple times"
431 -- GHC < 6.10 put "$topdir/include/mingw" in rts's installDirs. This
432 -- breaks when you want to use a different gcc, so we need to filter
434 removeMingwIncludeDir
:: InstalledPackageInfo
-> InstalledPackageInfo
435 removeMingwIncludeDir pkg
=
436 let ids
= InstalledPackageInfo
.includeDirs pkg
437 ids
' = filter (not . ("mingw" `
isSuffixOf`
)) ids
438 in pkg
{ InstalledPackageInfo
.includeDirs
= ids
' }
440 -- | Get the packages from specific PackageDBs, not cumulative.
442 getInstalledPackages
' :: Verbosity
-> [PackageDB
] -> ProgramDb
443 -> IO [(PackageDB
, [InstalledPackageInfo
])]
444 getInstalledPackages
' verbosity packagedbs progdb
=
446 [ do pkgs
<- HcPkg
.dump
(hcPkgInfo progdb
) verbosity packagedb
447 return (packagedb
, pkgs
)
448 | packagedb
<- packagedbs
]
450 getInstalledPackagesMonitorFiles
:: Verbosity
-> Platform
454 getInstalledPackagesMonitorFiles verbosity platform progdb
=
455 traverse getPackageDBPath
457 getPackageDBPath
:: PackageDB
-> IO FilePath
458 getPackageDBPath GlobalPackageDB
=
459 selectMonitorFile
=<< getGlobalPackageDB verbosity ghcProg
461 getPackageDBPath UserPackageDB
=
462 selectMonitorFile
=<< getUserPackageDB verbosity ghcProg platform
464 getPackageDBPath
(SpecificPackageDB path
) = selectMonitorFile path
466 -- GHC has old style file dbs, and new style directory dbs.
467 -- Note that for dir style dbs, we only need to monitor the cache file, not
468 -- the whole directory. The ghc program itself only reads the cache file
469 -- so it's safe to only monitor this one file.
470 selectMonitorFile path
= do
471 isFileStyle
<- doesFileExist path
472 if isFileStyle
then return path
473 else return (path
</> "package.cache")
475 Just ghcProg
= lookupProgram ghcProgram progdb
478 -- -----------------------------------------------------------------------------
479 -- Building a library
481 buildLib
:: Verbosity
-> Cabal
.Flag
(Maybe Int)
482 -> PackageDescription
-> LocalBuildInfo
483 -> Library
-> ComponentLocalBuildInfo
-> IO ()
484 buildLib
= buildOrReplLib Nothing
486 replLib
:: [String] -> Verbosity
487 -> Cabal
.Flag
(Maybe Int) -> PackageDescription
488 -> LocalBuildInfo
-> Library
489 -> ComponentLocalBuildInfo
-> IO ()
490 replLib
= buildOrReplLib
. Just
492 buildOrReplLib
:: Maybe [String] -> Verbosity
493 -> Cabal
.Flag
(Maybe Int) -> PackageDescription
494 -> LocalBuildInfo
-> Library
495 -> ComponentLocalBuildInfo
-> IO ()
496 buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi
= do
497 let uid
= componentUnitId clbi
498 libTargetDir
= componentBuildDir lbi clbi
499 whenVanillaLib forceVanilla
=
500 when (forceVanilla || withVanillaLib lbi
)
501 whenProfLib
= when (withProfLib lbi
)
502 whenSharedLib forceShared
=
503 when (forceShared || withSharedLib lbi
)
504 whenStaticLib forceStatic
=
505 when (forceStatic || withStaticLib lbi
)
506 whenGHCiLib
= when (withGHCiLib lbi
&& withVanillaLib lbi
)
507 forRepl
= maybe False (const True) mReplFlags
508 ifReplLib
= when forRepl
509 replFlags
= fromMaybe mempty mReplFlags
511 ghcVersion
= compilerVersion comp
512 implInfo
= getImplInfo comp
513 platform
@(Platform _hostArch hostOS
) = hostPlatform lbi
514 has_code
= not (componentIsIndefinite clbi
)
516 (ghcProg
, _
) <- requireProgram verbosity ghcProgram
(withPrograms lbi
)
517 let runGhcProg
= runGHC verbosity ghcProg comp platform
519 let libBi
= libBuildInfo lib
521 let isGhcDynamic
= isDynamic comp
522 dynamicTooSupported
= supportsDynamicToo comp
523 doingTH
= usesTemplateHaskellOrQQ libBi
524 forceVanillaLib
= doingTH
&& not isGhcDynamic
525 forceSharedLib
= doingTH
&& isGhcDynamic
526 -- TH always needs default libs, even when building for profiling
528 -- Determine if program coverage should be enabled and if so, what
529 -- '-hpcdir' should be.
530 let isCoverageEnabled
= libCoverage lbi
531 -- TODO: Historically HPC files have been put into a directory which
532 -- has the package name. I'm going to avoid changing this for
533 -- now, but it would probably be better for this to be the
534 -- component ID instead...
535 pkg_name
= display
(PD
.package pkg_descr
)
536 distPref
= fromFlag
$ configDistPref
$ configFlags lbi
538 | forRepl
= mempty
-- HPC is not supported in ghci
539 | isCoverageEnabled
= toFlag
$ Hpc
.mixDir distPref way pkg_name
542 createDirectoryIfMissingVerbose verbosity
True libTargetDir
543 -- TODO: do we need to put hs-boot files into place for mutually recursive
545 let cLikeFiles
= fromNubListR
$ toNubListR
(cSources libBi
) <> toNubListR
(cxxSources libBi
)
546 cObjs
= map (`replaceExtension` objExtension
) cLikeFiles
547 baseOpts
= componentGhcOptions verbosity lbi libBi clbi libTargetDir
548 vanillaOpts
= baseOpts `mappend` mempty
{
549 ghcOptMode
= toFlag GhcModeMake
,
550 ghcOptNumJobs
= numJobs
,
551 ghcOptInputModules
= toNubListR
$ allLibModules lib clbi
,
552 ghcOptHPCDir
= hpcdir Hpc
.Vanilla
555 profOpts
= vanillaOpts `mappend` mempty
{
556 ghcOptProfilingMode
= toFlag
True,
557 ghcOptProfilingAuto
= Internal
.profDetailLevelFlag
True
558 (withProfLibDetail lbi
),
559 ghcOptHiSuffix
= toFlag
"p_hi",
560 ghcOptObjSuffix
= toFlag
"p_o",
561 ghcOptExtra
= hcProfOptions GHC libBi
,
562 ghcOptHPCDir
= hpcdir Hpc
.Prof
565 sharedOpts
= vanillaOpts `mappend` mempty
{
566 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
567 ghcOptFPic
= toFlag
True,
568 ghcOptHiSuffix
= toFlag
"dyn_hi",
569 ghcOptObjSuffix
= toFlag
"dyn_o",
570 ghcOptExtra
= hcSharedOptions GHC libBi
,
571 ghcOptHPCDir
= hpcdir Hpc
.Dyn
573 linkerOpts
= mempty
{
574 ghcOptLinkOptions
= PD
.ldOptions libBi
,
575 ghcOptLinkLibs
= extraLibs libBi
,
576 ghcOptLinkLibPath
= toNubListR
$ extraLibDirs libBi
,
577 ghcOptLinkFrameworks
= toNubListR
$ PD
.frameworks libBi
,
578 ghcOptLinkFrameworkDirs
= toNubListR
$ PD
.extraFrameworkDirs libBi
,
579 ghcOptInputFiles
= toNubListR
580 [libTargetDir
</> x | x
<- cObjs
]
582 replOpts
= vanillaOpts
{
583 ghcOptExtra
= Internal
.filterGhciFlags
584 (ghcOptExtra vanillaOpts
)
586 ghcOptNumJobs
= mempty
590 ghcOptMode
= toFlag GhcModeInteractive
,
591 ghcOptOptimisation
= toFlag GhcNoOptimisation
594 vanillaSharedOpts
= vanillaOpts `mappend` mempty
{
595 ghcOptDynLinkMode
= toFlag GhcStaticAndDynamic
,
596 ghcOptDynHiSuffix
= toFlag
"dyn_hi",
597 ghcOptDynObjSuffix
= toFlag
"dyn_o",
598 ghcOptHPCDir
= hpcdir Hpc
.Dyn
601 unless (forRepl ||
null (allLibModules lib clbi
)) $
602 do let vanilla
= whenVanillaLib forceVanillaLib
(runGhcProg vanillaOpts
)
603 shared
= whenSharedLib forceSharedLib
(runGhcProg sharedOpts
)
604 useDynToo
= dynamicTooSupported
&&
605 (forceVanillaLib || withVanillaLib lbi
) &&
606 (forceSharedLib || withSharedLib lbi
) &&
607 null (hcSharedOptions GHC libBi
)
613 runGhcProg vanillaSharedOpts
614 case (hpcdir Hpc
.Dyn
, hpcdir Hpc
.Vanilla
) of
615 (Cabal
.Flag dynDir
, Cabal
.Flag vanillaDir
) ->
616 -- When the vanilla and shared library builds are done
617 -- in one pass, only one set of HPC module interfaces
618 -- are generated. This set should suffice for both
619 -- static and dynamically linked executables. We copy
620 -- the modules interfaces so they are available under
622 copyDirectoryRecursive verbosity dynDir vanillaDir
625 then do shared
; vanilla
626 else do vanilla
; shared
627 whenProfLib
(runGhcProg profOpts
)
629 -- Build any C++ sources separately.
630 unless (not has_code ||
null (cxxSources libBi
)) $ do
631 info verbosity
"Building C++ Sources..."
633 [ do let baseCxxOpts
= Internal
.componentCxxGhcOptions verbosity implInfo
634 lbi libBi clbi libTargetDir filename
635 vanillaCxxOpts
= if isGhcDynamic
636 then baseCxxOpts
{ ghcOptFPic
= toFlag
True }
638 profCxxOpts
= vanillaCxxOpts `mappend` mempty
{
639 ghcOptProfilingMode
= toFlag
True,
640 ghcOptObjSuffix
= toFlag
"p_o"
642 sharedCxxOpts
= vanillaCxxOpts `mappend` mempty
{
643 ghcOptFPic
= toFlag
True,
644 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
645 ghcOptObjSuffix
= toFlag
"dyn_o"
647 odir
= fromFlag
(ghcOptObjDir vanillaCxxOpts
)
648 createDirectoryIfMissingVerbose verbosity
True odir
649 let runGhcProgIfNeeded cxxOpts
= do
650 needsRecomp
<- checkNeedsRecompilation filename cxxOpts
651 when needsRecomp
$ runGhcProg cxxOpts
652 runGhcProgIfNeeded vanillaCxxOpts
654 whenSharedLib forceSharedLib
(runGhcProgIfNeeded sharedCxxOpts
)
655 unless forRepl
$ whenProfLib
(runGhcProgIfNeeded profCxxOpts
)
656 | filename
<- cxxSources libBi
]
658 when has_code
. ifReplLib
$ do
659 when (null (allLibModules lib clbi
)) $ warn verbosity
"No exposed modules"
660 ifReplLib
(runGhcProg replOpts
)
662 -- build any C sources
663 -- TODO: Add support for S and CMM files.
664 unless (not has_code ||
null (cSources libBi
)) $ do
665 info verbosity
"Building C Sources..."
667 [ do let baseCcOpts
= Internal
.componentCcGhcOptions verbosity implInfo
668 lbi libBi clbi libTargetDir filename
669 vanillaCcOpts
= if isGhcDynamic
670 -- Dynamic GHC requires C sources to be built
671 -- with -fPIC for REPL to work. See #2207.
672 then baseCcOpts
{ ghcOptFPic
= toFlag
True }
674 profCcOpts
= vanillaCcOpts `mappend` mempty
{
675 ghcOptProfilingMode
= toFlag
True,
676 ghcOptObjSuffix
= toFlag
"p_o"
678 sharedCcOpts
= vanillaCcOpts `mappend` mempty
{
679 ghcOptFPic
= toFlag
True,
680 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
681 ghcOptObjSuffix
= toFlag
"dyn_o"
683 odir
= fromFlag
(ghcOptObjDir vanillaCcOpts
)
684 createDirectoryIfMissingVerbose verbosity
True odir
685 let runGhcProgIfNeeded ccOpts
= do
686 needsRecomp
<- checkNeedsRecompilation filename ccOpts
687 when needsRecomp
$ runGhcProg ccOpts
688 runGhcProgIfNeeded vanillaCcOpts
690 whenSharedLib forceSharedLib
(runGhcProgIfNeeded sharedCcOpts
)
691 unless forRepl
$ whenProfLib
(runGhcProgIfNeeded profCcOpts
)
692 | filename
<- cSources libBi
]
694 -- TODO: problem here is we need the .c files built first, so we can load them
695 -- with ghci, but .c files can depend on .h files generated by ghc by ffi
699 when has_code
. unless forRepl
$ do
700 info verbosity
"Linking..."
701 let cProfObjs
= map (`replaceExtension`
("p_" ++ objExtension
))
702 (cSources libBi
++ cxxSources libBi
)
703 cSharedObjs
= map (`replaceExtension`
("dyn_" ++ objExtension
))
704 (cSources libBi
++ cxxSources libBi
)
705 compiler_id
= compilerId
(compiler lbi
)
706 vanillaLibFilePath
= libTargetDir
</> mkLibName uid
707 profileLibFilePath
= libTargetDir
</> mkProfLibName uid
708 sharedLibFilePath
= libTargetDir
</> mkSharedLibName
(hostPlatform lbi
) compiler_id uid
709 staticLibFilePath
= libTargetDir
</> mkStaticLibName
(hostPlatform lbi
) compiler_id uid
710 ghciLibFilePath
= libTargetDir
</> Internal
.mkGHCiLibName uid
711 libInstallPath
= libdir
$ absoluteComponentInstallDirs pkg_descr lbi uid NoCopyDest
712 sharedLibInstallPath
= libInstallPath
</> mkSharedLibName
(hostPlatform lbi
) compiler_id uid
714 stubObjs
<- catMaybes <$> sequenceA
715 [ findFileWithExtension
[objExtension
] [libTargetDir
]
716 (ModuleName
.toFilePath x
++"_stub")
717 | ghcVersion
< mkVersion
[7,2] -- ghc-7.2+ does not make _stub.o files
718 , x
<- allLibModules lib clbi
]
719 stubProfObjs
<- catMaybes <$> sequenceA
720 [ findFileWithExtension
["p_" ++ objExtension
] [libTargetDir
]
721 (ModuleName
.toFilePath x
++"_stub")
722 | ghcVersion
< mkVersion
[7,2] -- ghc-7.2+ does not make _stub.o files
723 , x
<- allLibModules lib clbi
]
724 stubSharedObjs
<- catMaybes <$> sequenceA
725 [ findFileWithExtension
["dyn_" ++ objExtension
] [libTargetDir
]
726 (ModuleName
.toFilePath x
++"_stub")
727 | ghcVersion
< mkVersion
[7,2] -- ghc-7.2+ does not make _stub.o files
728 , x
<- allLibModules lib clbi
]
730 hObjs
<- Internal
.getHaskellObjects implInfo lib lbi clbi
731 libTargetDir objExtension
True
734 then Internal
.getHaskellObjects implInfo lib lbi clbi
735 libTargetDir
("p_" ++ objExtension
) True
739 then Internal
.getHaskellObjects implInfo lib lbi clbi
740 libTargetDir
("dyn_" ++ objExtension
) False
743 unless (null hObjs
&& null cObjs
&& null stubObjs
) $ do
744 rpaths
<- getRPaths lbi clbi
746 let staticObjectFiles
=
748 ++ map (libTargetDir
</>) cObjs
752 ++ map (libTargetDir
</>) cProfObjs
756 ++ map (libTargetDir
</>) cObjs
760 ++ map (libTargetDir
</>) cSharedObjs
762 -- After the relocation lib is created we invoke ghc -shared
763 -- with the dependencies spelled out as -package arguments
764 -- and ghc invokes the linker with the proper library paths
767 ghcOptShared
= toFlag
True,
768 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
769 ghcOptInputFiles
= toNubListR dynamicObjectFiles
,
770 ghcOptOutputFile
= toFlag sharedLibFilePath
,
771 ghcOptExtra
= hcSharedOptions GHC libBi
,
772 -- For dynamic libs, Mac OS/X needs to know the install location
773 -- at build time. This only applies to GHC < 7.8 - see the
774 -- discussion in #1660.
775 ghcOptDylibName
= if hostOS
== OSX
776 && ghcVersion
< mkVersion
[7,8]
777 then toFlag sharedLibInstallPath
779 ghcOptHideAllPackages
= toFlag
True,
780 ghcOptNoAutoLinkPackages
= toFlag
True,
781 ghcOptPackageDBs
= withPackageDB lbi
,
782 ghcOptThisUnitId
= case clbi
of
783 LibComponentLocalBuildInfo
{ componentCompatPackageKey
= pk
}
786 ghcOptThisComponentId
= case clbi
of
787 LibComponentLocalBuildInfo
{ componentInstantiatedWith
= insts
} ->
790 else toFlag
(componentComponentId clbi
)
792 ghcOptInstantiatedWith
= case clbi
of
793 LibComponentLocalBuildInfo
{ componentInstantiatedWith
= insts
}
796 ghcOptPackages
= toNubListR
$
797 Internal
.mkGhcOptPackages clbi
,
798 ghcOptLinkLibs
= extraLibs libBi
,
799 ghcOptLinkLibPath
= toNubListR
$ extraLibDirs libBi
,
800 ghcOptLinkFrameworks
= toNubListR
$ PD
.frameworks libBi
,
801 ghcOptLinkFrameworkDirs
=
802 toNubListR
$ PD
.extraFrameworkDirs libBi
,
803 ghcOptRPaths
= rpaths
807 ghcOptStaticLib
= toFlag
True,
808 ghcOptInputFiles
= toNubListR staticObjectFiles
,
809 ghcOptOutputFile
= toFlag staticLibFilePath
,
810 ghcOptExtra
= hcStaticOptions GHC libBi
,
811 ghcOptHideAllPackages
= toFlag
True,
812 ghcOptNoAutoLinkPackages
= toFlag
True,
813 ghcOptPackageDBs
= withPackageDB lbi
,
814 ghcOptThisUnitId
= case clbi
of
815 LibComponentLocalBuildInfo
{ componentCompatPackageKey
= pk
}
818 ghcOptThisComponentId
= case clbi
of
819 LibComponentLocalBuildInfo
{ componentInstantiatedWith
= insts
} ->
822 else toFlag
(componentComponentId clbi
)
824 ghcOptInstantiatedWith
= case clbi
of
825 LibComponentLocalBuildInfo
{ componentInstantiatedWith
= insts
}
828 ghcOptPackages
= toNubListR
$
829 Internal
.mkGhcOptPackages clbi
,
830 ghcOptLinkLibs
= extraLibs libBi
,
831 ghcOptLinkLibPath
= toNubListR
$ extraLibDirs libBi
834 info verbosity
(show (ghcOptPackages ghcSharedLinkArgs
))
836 whenVanillaLib
False $
837 Ar
.createArLibArchive verbosity lbi vanillaLibFilePath staticObjectFiles
840 Ar
.createArLibArchive verbosity lbi profileLibFilePath profObjectFiles
843 (ldProg
, _
) <- requireProgram verbosity ldProgram
(withPrograms lbi
)
844 Ld
.combineObjectFiles verbosity lbi ldProg
845 ghciLibFilePath ghciObjFiles
847 whenSharedLib
False $
848 runGhcProg ghcSharedLinkArgs
850 whenStaticLib
False $
851 runGhcProg ghcStaticLinkArgs
853 -- | Start a REPL without loading any source files.
854 startInterpreter
:: Verbosity
-> ProgramDb
-> Compiler
-> Platform
855 -> PackageDBStack
-> IO ()
856 startInterpreter verbosity progdb comp platform packageDBs
= do
857 let replOpts
= mempty
{
858 ghcOptMode
= toFlag GhcModeInteractive
,
859 ghcOptPackageDBs
= packageDBs
861 checkPackageDbStack verbosity comp packageDBs
862 (ghcProg
, _
) <- requireProgram verbosity ghcProgram progdb
863 runGHC verbosity ghcProg comp platform replOpts
865 -- -----------------------------------------------------------------------------
866 -- Building an executable or foreign library
868 -- | Build a foreign library
870 :: Verbosity
-> Cabal
.Flag
(Maybe Int)
871 -> PackageDescription
-> LocalBuildInfo
872 -> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
873 buildFLib v njobs pkg lbi
= gbuild v njobs pkg lbi
. GBuildFLib
876 :: [String] -> Verbosity
877 -> Cabal
.Flag
(Maybe Int) -> PackageDescription
878 -> LocalBuildInfo
-> ForeignLib
879 -> ComponentLocalBuildInfo
-> IO ()
880 replFLib replFlags v njobs pkg lbi
=
881 gbuild v njobs pkg lbi
. GReplFLib replFlags
883 -- | Build an executable with GHC.
886 :: Verbosity
-> Cabal
.Flag
(Maybe Int)
887 -> PackageDescription
-> LocalBuildInfo
888 -> Executable
-> ComponentLocalBuildInfo
-> IO ()
889 buildExe v njobs pkg lbi
= gbuild v njobs pkg lbi
. GBuildExe
892 :: [String] -> Verbosity
893 -> Cabal
.Flag
(Maybe Int) -> PackageDescription
894 -> LocalBuildInfo
-> Executable
895 -> ComponentLocalBuildInfo
-> IO ()
896 replExe replFlags v njobs pkg lbi
=
897 gbuild v njobs pkg lbi
. GReplExe replFlags
899 -- | Building an executable, starting the REPL, and building foreign
900 -- libraries are all very similar and implemented in 'gbuild'. The
901 -- 'GBuildMode' distinguishes between the various kinds of operation.
904 | GReplExe
[String] Executable
905 | GBuildFLib ForeignLib
906 | GReplFLib
[String] ForeignLib
908 gbuildInfo
:: GBuildMode
-> BuildInfo
909 gbuildInfo
(GBuildExe exe
) = buildInfo exe
910 gbuildInfo
(GReplExe _ exe
) = buildInfo exe
911 gbuildInfo
(GBuildFLib flib
) = foreignLibBuildInfo flib
912 gbuildInfo
(GReplFLib _ flib
) = foreignLibBuildInfo flib
914 gbuildName
:: GBuildMode
-> String
915 gbuildName
(GBuildExe exe
) = unUnqualComponentName
$ exeName exe
916 gbuildName
(GReplExe _ exe
) = unUnqualComponentName
$ exeName exe
917 gbuildName
(GBuildFLib flib
) = unUnqualComponentName
$ foreignLibName flib
918 gbuildName
(GReplFLib _ flib
) = unUnqualComponentName
$ foreignLibName flib
920 gbuildTargetName
:: LocalBuildInfo
-> GBuildMode
-> String
921 gbuildTargetName lbi
(GBuildExe exe
) = exeTargetName
(hostPlatform lbi
) exe
922 gbuildTargetName lbi
(GReplExe _ exe
) = exeTargetName
(hostPlatform lbi
) exe
923 gbuildTargetName lbi
(GBuildFLib flib
) = flibTargetName lbi flib
924 gbuildTargetName lbi
(GReplFLib _ flib
) = flibTargetName lbi flib
926 exeTargetName
:: Platform
-> Executable
-> String
927 exeTargetName platform exe
= unUnqualComponentName
(exeName exe
) `withExt` exeExtension platform
929 -- | Target name for a foreign library (the actual file name)
931 -- We do not use mkLibName and co here because the naming for foreign libraries
932 -- is slightly different (we don't use "_p" or compiler version suffices, and we
933 -- don't want the "lib" prefix on Windows).
935 -- TODO: We do use `dllExtension` and co here, but really that's wrong: they
936 -- use the OS used to build cabal to determine which extension to use, rather
937 -- than the target OS (but this is wrong elsewhere in Cabal as well).
938 flibTargetName
:: LocalBuildInfo
-> ForeignLib
-> String
939 flibTargetName lbi flib
=
940 case (os
, foreignLibType flib
) of
941 (Windows
, ForeignLibNativeShared
) -> nm
<.> "dll"
942 (Windows
, ForeignLibNativeStatic
) -> nm
<.> "lib"
943 (Linux
, ForeignLibNativeShared
) -> "lib" ++ nm
<.> versionedExt
944 (_other
, ForeignLibNativeShared
) -> "lib" ++ nm
<.> dllExtension
(hostPlatform lbi
)
945 (_other
, ForeignLibNativeStatic
) -> "lib" ++ nm
<.> staticLibExtension
(hostPlatform lbi
)
946 (_any
, ForeignLibTypeUnknown
) -> cabalBug
"unknown foreign lib type"
949 nm
= unUnqualComponentName
$ foreignLibName flib
952 os
= let (Platform _ os
') = hostPlatform lbi
955 -- If a foreign lib foo has lib-version-info 5:1:2 or
956 -- lib-version-linux 3.2.1, it should be built as libfoo.so.3.2.1
957 -- Libtool's version-info data is translated into library versions in a
958 -- nontrivial way: so refer to libtool documentation.
959 versionedExt
:: String
961 let nums
= foreignLibVersion flib os
962 in foldl (<.>) "so" (map show nums
)
964 -- | Name for the library when building.
966 -- If the `lib-version-info` field or the `lib-version-linux` field of
967 -- a foreign library target is set, we need to incorporate that
968 -- version into the SONAME field.
970 -- If a foreign library foo has lib-version-info 5:1:2, it should be
971 -- built as libfoo.so.3.2.1. We want it to get soname libfoo.so.3.
972 -- However, GHC does not allow overriding soname by setting linker
973 -- options, as it sets a soname of its own (namely the output
974 -- filename), after the user-supplied linker options. Hence, we have
975 -- to compile the library with the soname as its filename. We rename
976 -- the compiled binary afterwards.
978 -- This method allows to adjust the name of the library at build time
979 -- such that the correct soname can be set.
980 flibBuildName
:: LocalBuildInfo
-> ForeignLib
-> String
981 flibBuildName lbi flib
982 -- On linux, if a foreign-library has version data, the first digit is used
983 -- to produce the SONAME.
984 |
(os
, foreignLibType flib
) ==
985 (Linux
, ForeignLibNativeShared
)
986 = let nums
= foreignLibVersion flib os
987 in "lib" ++ nm
<.> foldl (<.>) "so" (map show (take 1 nums
))
988 |
otherwise = flibTargetName lbi flib
991 os
= let (Platform _ os
') = hostPlatform lbi
995 nm
= unUnqualComponentName
$ foreignLibName flib
997 gbuildIsRepl
:: GBuildMode
-> Bool
998 gbuildIsRepl
(GBuildExe _
) = False
999 gbuildIsRepl
(GReplExe _ _
) = True
1000 gbuildIsRepl
(GBuildFLib _
) = False
1001 gbuildIsRepl
(GReplFLib _ _
) = True
1003 gbuildNeedDynamic
:: LocalBuildInfo
-> GBuildMode
-> Bool
1004 gbuildNeedDynamic lbi bm
=
1006 GBuildExe _
-> withDynExe lbi
1007 GReplExe _ _
-> withDynExe lbi
1008 GBuildFLib flib
-> withDynFLib flib
1009 GReplFLib _ flib
-> withDynFLib flib
1012 case foreignLibType flib
of
1013 ForeignLibNativeShared
->
1014 ForeignLibStandalone `
notElem` foreignLibOptions flib
1015 ForeignLibNativeStatic
->
1017 ForeignLibTypeUnknown
->
1018 cabalBug
"unknown foreign lib type"
1020 gbuildModDefFiles
:: GBuildMode
-> [FilePath]
1021 gbuildModDefFiles
(GBuildExe _
) = []
1022 gbuildModDefFiles
(GReplExe _ _
) = []
1023 gbuildModDefFiles
(GBuildFLib flib
) = foreignLibModDefFile flib
1024 gbuildModDefFiles
(GReplFLib _ flib
) = foreignLibModDefFile flib
1026 -- | "Main" module name when overridden by @ghc-options: -main-is ...@
1027 -- or 'Nothing' if no @-main-is@ flag could be found.
1029 -- In case of 'Nothing', 'Distribution.ModuleName.main' can be assumed.
1030 exeMainModuleName
:: Executable
-> Maybe ModuleName
1031 exeMainModuleName Executable
{buildInfo
= bnfo
} =
1032 -- GHC honors the last occurence of a module name updated via -main-is
1034 -- Moreover, -main-is when parsed left-to-right can update either
1035 -- the "Main" module name, or the "main" function name, or both,
1036 -- see also 'decodeMainIsArg'.
1037 msum $ reverse $ map decodeMainIsArg
$ findIsMainArgs ghcopts
1039 ghcopts
= hcOptions GHC bnfo
1041 findIsMainArgs
[] = []
1042 findIsMainArgs
("-main-is":arg
:rest
) = arg
: findIsMainArgs rest
1043 findIsMainArgs
(_
:rest
) = findIsMainArgs rest
1045 -- | Decode argument to '-main-is'
1047 -- Returns 'Nothing' if argument set only the function name.
1049 -- This code has been stolen/refactored from GHC's DynFlags.setMainIs
1050 -- function. The logic here is deliberately imperfect as it is
1051 -- intended to be bug-compatible with GHC's parser. See discussion in
1052 -- https://github.com/haskell/cabal/pull/4539#discussion_r118981753.
1053 decodeMainIsArg
:: String -> Maybe ModuleName
1055 |
not (null main_fn
) && isLower (head main_fn
)
1056 -- The arg looked like "Foo.Bar.baz"
1057 = Just
(ModuleName
.fromString main_mod
)
1058 |
isUpper (head arg
) -- The arg looked like "Foo" or "Foo.Bar"
1059 = Just
(ModuleName
.fromString arg
)
1060 |
otherwise -- The arg looked like "baz"
1063 (main_mod
, main_fn
) = splitLongestPrefix arg
(== '.')
1065 splitLongestPrefix
:: String -> (Char -> Bool) -> (String,String)
1066 splitLongestPrefix str
pred'
1067 |
null r_pre
= (str
, [])
1068 |
otherwise = (reverse (tail r_pre
), reverse r_suf
)
1069 -- 'tail' drops the char satisfying 'pred'
1070 where (r_suf
, r_pre
) = break pred' (reverse str
)
1073 -- | A collection of:
1075 -- * C++ input files
1076 -- * GHC input files
1077 -- * GHC input modules
1079 -- Used to correctly build and link sources.
1080 data BuildSources
= BuildSources
{
1081 cSourcesFiles
:: [FilePath],
1082 cxxSourceFiles
:: [FilePath],
1083 inputSourceFiles
:: [FilePath],
1084 inputSourceModules
:: [ModuleName
]
1087 -- | Locate and return the 'BuildSources' required to build and link.
1088 gbuildSources
:: Verbosity
1089 -> Version
-- ^ specVersion
1093 gbuildSources verbosity specVer tmpDir bm
=
1095 GBuildExe exe
-> exeSources exe
1096 GReplExe _ exe
-> exeSources exe
1097 GBuildFLib flib
-> return $ flibSources flib
1098 GReplFLib _ flib
-> return $ flibSources flib
1100 exeSources
:: Executable
-> IO BuildSources
1101 exeSources exe
@Executable
{buildInfo
= bnfo
, modulePath
= modPath
} = do
1102 main
<- findFile
(tmpDir
: hsSourceDirs bnfo
) modPath
1103 let mainModName
= fromMaybe ModuleName
.main
$ exeMainModuleName exe
1104 otherModNames
= exeModules exe
1108 if specVer
< mkVersion
[2] && (mainModName `
elem` otherModNames
)
1110 -- The cabal manual clearly states that `other-modules` is
1111 -- intended for non-main modules. However, there's at least one
1112 -- important package on Hackage (happy-1.19.5) which
1113 -- violates this. We workaround this here so that we don't
1114 -- invoke GHC with e.g. 'ghc --make Main src/Main.hs' which
1115 -- would result in GHC complaining about duplicate Main
1118 -- Finally, we only enable this workaround for
1119 -- specVersion < 2, as 'cabal-version:>=2.0' cabal files
1120 -- have no excuse anymore to keep doing it wrong... ;-)
1121 warn verbosity
$ "Enabling workaround for Main module '"
1122 ++ display mainModName
1123 ++ "' listed in 'other-modules' illegally!"
1125 return BuildSources
{
1126 cSourcesFiles
= cSources bnfo
,
1127 cxxSourceFiles
= cxxSources bnfo
,
1128 inputSourceFiles
= [main
],
1129 inputSourceModules
= filter (/= mainModName
) $ exeModules exe
1132 else return BuildSources
{
1133 cSourcesFiles
= cSources bnfo
,
1134 cxxSourceFiles
= cxxSources bnfo
,
1135 inputSourceFiles
= [main
],
1136 inputSourceModules
= exeModules exe
1138 else let (csf
, cxxsf
)
1139 | isCxx main
= ( cSources bnfo
, main
: cxxSources bnfo
)
1140 -- if main is not a Haskell source
1141 -- and main is not a C++ source
1142 -- then we assume that it is a C source
1143 |
otherwise = (main
: cSources bnfo
, cxxSources bnfo
)
1145 in return BuildSources
{
1146 cSourcesFiles
= csf
,
1147 cxxSourceFiles
= cxxsf
,
1148 inputSourceFiles
= [],
1149 inputSourceModules
= exeModules exe
1152 flibSources
:: ForeignLib
-> BuildSources
1153 flibSources flib
@ForeignLib
{foreignLibBuildInfo
= bnfo
} =
1155 cSourcesFiles
= cSources bnfo
,
1156 cxxSourceFiles
= cxxSources bnfo
,
1157 inputSourceFiles
= [],
1158 inputSourceModules
= foreignLibModules flib
1161 isHaskell
:: FilePath -> Bool
1162 isHaskell fp
= elem (takeExtension fp
) [".hs", ".lhs"]
1164 isCxx
:: FilePath -> Bool
1165 isCxx fp
= elem (takeExtension fp
) [".cpp", ".cxx", ".c++"]
1167 -- | Generic build function. See comment for 'GBuildMode'.
1168 gbuild
:: Verbosity
-> Cabal
.Flag
(Maybe Int)
1169 -> PackageDescription
-> LocalBuildInfo
1170 -> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
1171 gbuild verbosity numJobs pkg_descr lbi bm clbi
= do
1172 (ghcProg
, _
) <- requireProgram verbosity ghcProgram
(withPrograms lbi
)
1173 let replFlags
= case bm
of
1174 GReplExe flags _
-> flags
1175 GReplFLib flags _
-> flags
1176 GBuildExe
{} -> mempty
1177 GBuildFLib
{} -> mempty
1179 platform
= hostPlatform lbi
1180 implInfo
= getImplInfo comp
1181 runGhcProg
= runGHC verbosity ghcProg comp platform
1183 let (bnfo
, threaded
) = case bm
of
1184 GBuildFLib _
-> popThreadedFlag
(gbuildInfo bm
)
1185 _
-> (gbuildInfo bm
, False)
1187 -- the name that GHC really uses (e.g., with .exe on Windows for executables)
1188 let targetName
= gbuildTargetName lbi bm
1189 let targetDir
= buildDir lbi
</> (gbuildName bm
)
1190 let tmpDir
= targetDir
</> (gbuildName bm
++ "-tmp")
1191 createDirectoryIfMissingVerbose verbosity
True targetDir
1192 createDirectoryIfMissingVerbose verbosity
True tmpDir
1194 -- TODO: do we need to put hs-boot files into place for mutually recursive
1195 -- modules? FIX: what about exeName.hi-boot?
1197 -- Determine if program coverage should be enabled and if so, what
1198 -- '-hpcdir' should be.
1199 let isCoverageEnabled
= exeCoverage lbi
1200 distPref
= fromFlag
$ configDistPref
$ configFlags lbi
1202 | gbuildIsRepl bm
= mempty
-- HPC is not supported in ghci
1203 | isCoverageEnabled
= toFlag
$ Hpc
.mixDir distPref way
(gbuildName bm
)
1204 |
otherwise = mempty
1206 rpaths
<- getRPaths lbi clbi
1207 buildSources
<- gbuildSources verbosity
(specVersion pkg_descr
) tmpDir bm
1209 let cSrcs
= cSourcesFiles buildSources
1210 cxxSrcs
= cxxSourceFiles buildSources
1211 inputFiles
= inputSourceFiles buildSources
1212 inputModules
= inputSourceModules buildSources
1213 isGhcDynamic
= isDynamic comp
1214 dynamicTooSupported
= supportsDynamicToo comp
1215 cObjs
= map (`replaceExtension` objExtension
) cSrcs
1216 cxxObjs
= map (`replaceExtension` objExtension
) cxxSrcs
1217 needDynamic
= gbuildNeedDynamic lbi bm
1218 needProfiling
= withProfExe lbi
1220 -- build executables
1221 baseOpts
= (componentGhcOptions verbosity lbi bnfo clbi tmpDir
)
1223 ghcOptMode
= toFlag GhcModeMake
,
1224 ghcOptInputFiles
= toNubListR inputFiles
,
1225 ghcOptInputModules
= toNubListR inputModules
1227 staticOpts
= baseOpts `mappend` mempty
{
1228 ghcOptDynLinkMode
= toFlag GhcStaticOnly
,
1229 ghcOptHPCDir
= hpcdir Hpc
.Vanilla
1231 profOpts
= baseOpts `mappend` mempty
{
1232 ghcOptProfilingMode
= toFlag
True,
1233 ghcOptProfilingAuto
= Internal
.profDetailLevelFlag
False
1234 (withProfExeDetail lbi
),
1235 ghcOptHiSuffix
= toFlag
"p_hi",
1236 ghcOptObjSuffix
= toFlag
"p_o",
1237 ghcOptExtra
= hcProfOptions GHC bnfo
,
1238 ghcOptHPCDir
= hpcdir Hpc
.Prof
1240 dynOpts
= baseOpts `mappend` mempty
{
1241 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
1242 -- TODO: Does it hurt to set -fPIC for executables?
1243 ghcOptFPic
= toFlag
True,
1244 ghcOptHiSuffix
= toFlag
"dyn_hi",
1245 ghcOptObjSuffix
= toFlag
"dyn_o",
1246 ghcOptExtra
= hcSharedOptions GHC bnfo
,
1247 ghcOptHPCDir
= hpcdir Hpc
.Dyn
1249 dynTooOpts
= staticOpts `mappend` mempty
{
1250 ghcOptDynLinkMode
= toFlag GhcStaticAndDynamic
,
1251 ghcOptDynHiSuffix
= toFlag
"dyn_hi",
1252 ghcOptDynObjSuffix
= toFlag
"dyn_o",
1253 ghcOptHPCDir
= hpcdir Hpc
.Dyn
1255 linkerOpts
= mempty
{
1256 ghcOptLinkOptions
= PD
.ldOptions bnfo
,
1257 ghcOptLinkLibs
= extraLibs bnfo
,
1258 ghcOptLinkLibPath
= toNubListR
$ extraLibDirs bnfo
,
1259 ghcOptLinkFrameworks
= toNubListR
$
1261 ghcOptLinkFrameworkDirs
= toNubListR
$
1262 PD
.extraFrameworkDirs bnfo
,
1263 ghcOptInputFiles
= toNubListR
1264 [tmpDir
</> x | x
<- cObjs
++ cxxObjs
]
1266 dynLinkerOpts
= mempty
{
1267 ghcOptRPaths
= rpaths
1269 replOpts
= baseOpts
{
1270 ghcOptExtra
= Internal
.filterGhciFlags
1271 (ghcOptExtra baseOpts
)
1274 -- For a normal compile we do separate invocations of ghc for
1275 -- compiling as for linking. But for repl we have to do just
1276 -- the one invocation, so that one has to include all the
1277 -- linker stuff too, like -l flags and any .o files from C
1279 `mappend` linkerOpts
1281 ghcOptMode
= toFlag GhcModeInteractive
,
1282 ghcOptOptimisation
= toFlag GhcNoOptimisation
1284 commonOpts | needProfiling
= profOpts
1285 | needDynamic
= dynOpts
1286 |
otherwise = staticOpts
1287 compileOpts | useDynToo
= dynTooOpts
1288 |
otherwise = commonOpts
1289 withStaticExe
= not needProfiling
&& not needDynamic
1291 -- For building exe's that use TH with -prof or -dynamic we actually have
1292 -- to build twice, once without -prof/-dynamic and then again with
1293 -- -prof/-dynamic. This is because the code that TH needs to run at
1294 -- compile time needs to be the vanilla ABI so it can be loaded up and run
1296 -- With dynamic-by-default GHC the TH object files loaded at compile-time
1297 -- need to be .dyn_o instead of .o.
1298 doingTH
= usesTemplateHaskellOrQQ bnfo
1299 -- Should we use -dynamic-too instead of compiling twice?
1300 useDynToo
= dynamicTooSupported
&& isGhcDynamic
1301 && doingTH
&& withStaticExe
1302 && null (hcSharedOptions GHC bnfo
)
1303 compileTHOpts | isGhcDynamic
= dynOpts
1304 |
otherwise = staticOpts
1306 | gbuildIsRepl bm
= False
1308 | isGhcDynamic
= doingTH
&& (needProfiling || withStaticExe
)
1309 |
otherwise = doingTH
&& (needProfiling || needDynamic
)
1311 -- Build static/dynamic object files for TH, if needed.
1313 runGhcProg compileTHOpts
{ ghcOptNoLink
= toFlag
True
1314 , ghcOptNumJobs
= numJobs
}
1316 -- Do not try to build anything if there are no input files.
1317 -- This can happen if the cabal file ends up with only cSrcs
1318 -- but no Haskell modules.
1319 unless ((null inputFiles
&& null inputModules
)
1320 || gbuildIsRepl bm
) $
1321 runGhcProg compileOpts
{ ghcOptNoLink
= toFlag
True
1322 , ghcOptNumJobs
= numJobs
}
1324 -- build any C++ sources
1325 unless (null cxxSrcs
) $ do
1326 info verbosity
"Building C++ Sources..."
1328 [ do let baseCxxOpts
= Internal
.componentCxxGhcOptions verbosity implInfo
1329 lbi bnfo clbi tmpDir filename
1330 vanillaCxxOpts
= if isGhcDynamic
1331 -- Dynamic GHC requires C++ sources to be built
1332 -- with -fPIC for REPL to work. See #2207.
1333 then baseCxxOpts
{ ghcOptFPic
= toFlag
True }
1335 profCxxOpts
= vanillaCxxOpts `mappend` mempty
{
1336 ghcOptProfilingMode
= toFlag
True
1338 sharedCxxOpts
= vanillaCxxOpts `mappend` mempty
{
1339 ghcOptFPic
= toFlag
True,
1340 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1342 opts | needProfiling
= profCxxOpts
1343 | needDynamic
= sharedCxxOpts
1344 |
otherwise = vanillaCxxOpts
1345 -- TODO: Placing all Haskell, C, & C++ objects in a single directory
1346 -- Has the potential for file collisions. In general we would
1347 -- consider this a user error. However, we should strive to
1348 -- add a warning if this occurs.
1349 odir
= fromFlag
(ghcOptObjDir opts
)
1350 createDirectoryIfMissingVerbose verbosity
True odir
1351 needsRecomp
<- checkNeedsRecompilation filename opts
1354 | filename
<- cxxSrcs
]
1356 -- build any C sources
1357 unless (null cSrcs
) $ do
1358 info verbosity
"Building C Sources..."
1360 [ do let baseCcOpts
= Internal
.componentCcGhcOptions verbosity implInfo
1361 lbi bnfo clbi tmpDir filename
1362 vanillaCcOpts
= if isGhcDynamic
1363 -- Dynamic GHC requires C sources to be built
1364 -- with -fPIC for REPL to work. See #2207.
1365 then baseCcOpts
{ ghcOptFPic
= toFlag
True }
1367 profCcOpts
= vanillaCcOpts `mappend` mempty
{
1368 ghcOptProfilingMode
= toFlag
True
1370 sharedCcOpts
= vanillaCcOpts `mappend` mempty
{
1371 ghcOptFPic
= toFlag
True,
1372 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1374 opts | needProfiling
= profCcOpts
1375 | needDynamic
= sharedCcOpts
1376 |
otherwise = vanillaCcOpts
1377 odir
= fromFlag
(ghcOptObjDir opts
)
1378 createDirectoryIfMissingVerbose verbosity
True odir
1379 needsRecomp
<- checkNeedsRecompilation filename opts
1382 | filename
<- cSrcs
]
1384 -- TODO: problem here is we need the .c files built first, so we can load them
1385 -- with ghci, but .c files can depend on .h files generated by ghc by ffi
1388 GReplExe _ _
-> runGhcProg replOpts
1389 GReplFLib _ _
-> runGhcProg replOpts
1391 let linkOpts
= commonOpts
1392 `mappend` linkerOpts
1394 ghcOptLinkNoHsMain
= toFlag
(null inputFiles
)
1396 `mappend`
(if withDynExe lbi
then dynLinkerOpts
else mempty
)
1398 info verbosity
"Linking..."
1399 -- Work around old GHCs not relinking in this
1400 -- situation, see #3294
1401 let target
= targetDir
</> targetName
1402 when (compilerVersion comp
< mkVersion
[7,7]) $ do
1403 e
<- doesFileExist target
1404 when e
(removeFile target
)
1405 runGhcProg linkOpts
{ ghcOptOutputFile
= toFlag target
}
1406 GBuildFLib flib
-> do
1407 let rtsInfo
= extractRtsInfo lbi
1411 then dynRtsThreadedLib
(rtsDynamicInfo rtsInfo
)
1412 else dynRtsVanillaLib
(rtsDynamicInfo rtsInfo
)
1414 then statRtsThreadedLib
(rtsStaticInfo rtsInfo
)
1415 else statRtsVanillaLib
(rtsStaticInfo rtsInfo
)
1417 linkOpts
= case foreignLibType flib
of
1418 ForeignLibNativeShared
->
1420 `mappend` linkerOpts
1421 `mappend` dynLinkerOpts
1423 ghcOptLinkNoHsMain
= toFlag
True,
1424 ghcOptShared
= toFlag
True,
1425 ghcOptLinkLibs
= rtsOptLinkLibs
,
1426 ghcOptLinkLibPath
= toNubListR
$ rtsLibPaths rtsInfo
,
1427 ghcOptFPic
= toFlag
True,
1428 ghcOptLinkModDefFiles
= toNubListR
$ gbuildModDefFiles bm
1431 `mappend` ifNeedsRPathWorkaround lbi mempty
{
1432 ghcOptLinkOptions
= ["-Wl,--no-as-needed"]
1433 , ghcOptLinkLibs
= ["ffi"]
1435 ForeignLibNativeStatic
->
1436 -- this should be caught by buildFLib
1437 -- (and if we do implement tihs, we probably don't even want to call
1438 -- ghc here, but rather Ar.createArLibArchive or something)
1439 cabalBug
"static libraries not yet implemented"
1440 ForeignLibTypeUnknown
->
1441 cabalBug
"unknown foreign lib type"
1442 -- We build under a (potentially) different filename to set a
1443 -- soname on supported platforms. See also the note for
1445 info verbosity
"Linking..."
1446 let buildName
= flibBuildName lbi flib
1447 runGhcProg linkOpts
{ ghcOptOutputFile
= toFlag
(targetDir
</> buildName
) }
1448 renameFile (targetDir
</> buildName
) (targetDir
</> targetName
)
1454 Suppose that the dynamic library depends on `base`, but not (directly) on
1455 `integer-gmp` (which, however, is a dependency of `base`). We will link the
1458 gcc ... -lHSbase-4.7.0.2-ghc7.8.4 -lHSinteger-gmp-0.5.1.0-ghc7.8.4 ...
1460 However, on systems (like Ubuntu) where the linker gets called with `-as-needed`
1461 by default, the linker will notice that `integer-gmp` isn't actually a direct
1462 dependency and hence omit the link.
1464 Then when we attempt to link a C program against this dynamic library, the
1465 _static_ linker will attempt to verify that all symbols can be resolved. The
1466 dynamic library itself does not require any symbols from `integer-gmp`, but
1467 `base` does. In order to verify that the symbols used by `base` can be
1468 resolved, the static linker needs to be able to _find_ integer-gmp.
1470 Finding the `base` dependency is simple, because the dynamic elf header
1471 (`readelf -d`) for the library that we have created looks something like
1473 (NEEDED) Shared library: [libHSbase-4.7.0.2-ghc7.8.4.so]
1474 (RPATH) Library rpath: [/path/to/base-4.7.0.2:...]
1476 However, when it comes to resolving the dependency on `integer-gmp`, it needs
1477 to look at the dynamic header for `base`. On modern ghc (7.8 and higher) this
1478 looks something like
1480 (NEEDED) Shared library: [libHSinteger-gmp-0.5.1.0-ghc7.8.4.so]
1481 (RPATH) Library rpath: [$ORIGIN/../integer-gmp-0.5.1.0:...]
1483 This specifies the location of `integer-gmp` _in terms of_ the location of base
1484 (using the `$ORIGIN`) variable. But here's the crux: when the static linker
1485 attempts to verify that all symbols can be resolved, [**IT DOES NOT RESOLVE
1486 `$ORIGIN`**](http://stackoverflow.com/questions/6323603/ld-using-rpath-origin-inside-a-shared-library-recursive).
1487 As a consequence, it will not be able to resolve the symbols and report the
1488 missing symbols as errors, _even though the dynamic linker **would** be able to
1489 resolve these symbols_. We can tell the static linker not to report these
1490 errors by using `--unresolved-symbols=ignore-all` and all will be fine when we
1491 run the program ([(indeed, this is what the gold linker
1492 does)](https://sourceware.org/ml/binutils/2013-05/msg00038.html), but it makes
1493 the resulting library more difficult to use.
1495 Instead what we can do is make sure that the generated dynamic library has
1496 explicit top-level dependencies on these libraries. This means that the static
1497 linker knows where to find them, and when we have transitive dependencies on
1498 the same libraries the linker will only load them once, so we avoid needing to
1499 look at the `RPATH` of our dependencies. We can do this by passing
1500 `--no-as-needed` to the linker, so that it doesn't omit any libraries.
1502 Note that on older ghc (7.6 and before) the Haskell libraries don't have an
1503 RPATH set at all, which makes it even more important that we make these
1504 top-level dependencies.
1506 Finally, we have to explicitly link against `libffi` for the same reason. For
1507 newer ghc this _happens_ to be unnecessary on many systems because `libffi` is
1508 a library which is not specific to GHC, and when the static linker verifies
1509 that all symbols can be resolved it will find the `libffi` that is globally
1510 installed (completely independent from ghc). Of course, this may well be the
1511 _wrong_ version of `libffi`, but it's quite possible that symbol resolution
1512 happens to work. This is of course the wrong approach, which is why we link
1513 explicitly against `libffi` so that we will find the _right_ version of
1517 -- | Do we need the RPATH workaround?
1519 -- See Note [RPATH].
1520 ifNeedsRPathWorkaround
:: Monoid a
=> LocalBuildInfo
-> a
-> a
1521 ifNeedsRPathWorkaround lbi a
=
1522 case hostPlatform lbi
of
1523 Platform _ Linux
-> a
1524 _otherwise
-> mempty
1526 data DynamicRtsInfo
= DynamicRtsInfo
{
1527 dynRtsVanillaLib
:: FilePath
1528 , dynRtsThreadedLib
:: FilePath
1529 , dynRtsDebugLib
:: FilePath
1530 , dynRtsEventlogLib
:: FilePath
1531 , dynRtsThreadedDebugLib
:: FilePath
1532 , dynRtsThreadedEventlogLib
:: FilePath
1535 data StaticRtsInfo
= StaticRtsInfo
{
1536 statRtsVanillaLib
:: FilePath
1537 , statRtsThreadedLib
:: FilePath
1538 , statRtsDebugLib
:: FilePath
1539 , statRtsEventlogLib
:: FilePath
1540 , statRtsThreadedDebugLib
:: FilePath
1541 , statRtsThreadedEventlogLib
:: FilePath
1542 , statRtsProfilingLib
:: FilePath
1543 , statRtsThreadedProfilingLib
:: FilePath
1546 data RtsInfo
= RtsInfo
{
1547 rtsDynamicInfo
:: DynamicRtsInfo
1548 , rtsStaticInfo
:: StaticRtsInfo
1549 , rtsLibPaths
:: [FilePath]
1552 -- | Extract (and compute) information about the RTS library
1554 -- TODO: This hardcodes the name as @HSrts-ghc<version>@. I don't know if we can
1555 -- find this information somewhere. We can lookup the 'hsLibraries' field of
1556 -- 'InstalledPackageInfo' but it will tell us @["HSrts", "Cffi"]@, which
1557 -- doesn't really help.
1558 extractRtsInfo
:: LocalBuildInfo
-> RtsInfo
1559 extractRtsInfo lbi
=
1560 case PackageIndex
.lookupPackageName
(installedPkgs lbi
) (mkPackageName
"rts") of
1561 [(_
, [rts
])] -> aux rts
1562 _otherwise
-> error "No (or multiple) ghc rts package is registered"
1564 aux
:: InstalledPackageInfo
-> RtsInfo
1566 rtsDynamicInfo
= DynamicRtsInfo
{
1567 dynRtsVanillaLib
= withGhcVersion
"HSrts"
1568 , dynRtsThreadedLib
= withGhcVersion
"HSrts_thr"
1569 , dynRtsDebugLib
= withGhcVersion
"HSrts_debug"
1570 , dynRtsEventlogLib
= withGhcVersion
"HSrts_l"
1571 , dynRtsThreadedDebugLib
= withGhcVersion
"HSrts_thr_debug"
1572 , dynRtsThreadedEventlogLib
= withGhcVersion
"HSrts_thr_l"
1574 , rtsStaticInfo
= StaticRtsInfo
{
1575 statRtsVanillaLib
= "HSrts"
1576 , statRtsThreadedLib
= "HSrts_thr"
1577 , statRtsDebugLib
= "HSrts_debug"
1578 , statRtsEventlogLib
= "HSrts_l"
1579 , statRtsThreadedDebugLib
= "HSrts_thr_debug"
1580 , statRtsThreadedEventlogLib
= "HSrts_thr_l"
1581 , statRtsProfilingLib
= "HSrts_p"
1582 , statRtsThreadedProfilingLib
= "HSrts_thr_p"
1584 , rtsLibPaths
= InstalledPackageInfo
.libraryDirs rts
1586 withGhcVersion
= (++ ("-ghc" ++ display
(compilerVersion
(compiler lbi
))))
1588 -- | Returns True if the modification date of the given source file is newer than
1589 -- the object file we last compiled for it, or if no object file exists yet.
1590 checkNeedsRecompilation
:: FilePath -> GhcOptions
-> NoCallStackIO
Bool
1591 checkNeedsRecompilation filename opts
= filename `moreRecentFile` oname
1592 where oname
= getObjectFileName filename opts
1594 -- | Finds the object file name of the given source file
1595 getObjectFileName
:: FilePath -> GhcOptions
-> FilePath
1596 getObjectFileName filename opts
= oname
1597 where odir
= fromFlag
(ghcOptObjDir opts
)
1598 oext
= fromFlagOrDefault
"o" (ghcOptObjSuffix opts
)
1599 oname
= odir
</> replaceExtension filename oext
1601 -- | Calculate the RPATHs for the component we are building.
1603 -- Calculates relative RPATHs when 'relocatable' is set.
1604 getRPaths
:: LocalBuildInfo
1605 -> ComponentLocalBuildInfo
-- ^ Component we are building
1606 -> NoCallStackIO
(NubListR
FilePath)
1607 getRPaths lbi clbi | supportRPaths hostOS
= do
1608 libraryPaths
<- depLibraryPaths
False (relocatable lbi
) lbi clbi
1609 let hostPref
= case hostOS
of
1610 OSX
-> "@loader_path"
1612 relPath p
= if isRelative p
then hostPref
</> p
else p
1613 rpaths
= toNubListR
(map relPath libraryPaths
)
1616 (Platform _ hostOS
) = hostPlatform lbi
1617 compid
= compilerId
. compiler
$ lbi
1619 -- The list of RPath-supported operating systems below reflects the
1620 -- platforms on which Cabal's RPATH handling is tested. It does _NOT_
1621 -- reflect whether the OS supports RPATH.
1623 -- E.g. when this comment was written, the *BSD operating systems were
1624 -- untested with regards to Cabal RPATH handling, and were hence set to
1625 -- 'False', while those operating systems themselves do support RPATH.
1626 supportRPaths Linux Â
= True
1627 supportRPaths Windows
= False
1628 supportRPaths OSX Â
= True
1629 supportRPaths FreeBSD Â
=
1631 CompilerId GHC ver | ver
>= mkVersion
[7,10,2] -> True
1633 supportRPaths OpenBSD Â
= False
1634 supportRPaths NetBSD Â
= False
1635 supportRPaths DragonFly
= False
1636 supportRPaths Solaris
= False
1637 supportRPaths AIX
= False
1638 supportRPaths HPUX
= False
1639 supportRPaths IRIX
= False
1640 supportRPaths HaLVM
= False
1641 supportRPaths IOS
= False
1642 supportRPaths Android
= False
1643 supportRPaths Ghcjs
= False
1644 supportRPaths Hurd
= False
1645 supportRPaths
(OtherOS _
) = False
1646 -- Do _not_ add a default case so that we get a warning here when a new OS
1649 getRPaths _ _
= return mempty
1651 -- | Remove the "-threaded" flag when building a foreign library, as it has no
1652 -- effect when used with "-shared". Returns the updated 'BuildInfo', along
1653 -- with whether or not the flag was present, so we can use it to link against
1654 -- the appropriate RTS on our own.
1655 popThreadedFlag
:: BuildInfo
-> (BuildInfo
, Bool)
1656 popThreadedFlag bi
=
1657 ( bi
{ options
= filterHcOptions
(/= "-threaded") (options bi
) }
1658 , hasThreaded
(options bi
))
1661 filterHcOptions
:: (String -> Bool)
1662 -> [(CompilerFlavor
, [String])]
1663 -> [(CompilerFlavor
, [String])]
1664 filterHcOptions p hcoptss
=
1665 [ (hc
, if hc
== GHC
then filter p opts
else opts
)
1666 |
(hc
, opts
) <- hcoptss
]
1668 hasThreaded
:: [(CompilerFlavor
, [String])] -> Bool
1669 hasThreaded hcoptss
=
1670 or [ if hc
== GHC
then elem "-threaded" opts
else False
1671 |
(hc
, opts
) <- hcoptss
]
1673 -- | Extracts a String representing a hash of the ABI of a built
1674 -- library. It can fail if the library has not yet been built.
1676 libAbiHash
:: Verbosity
-> PackageDescription
-> LocalBuildInfo
1677 -> Library
-> ComponentLocalBuildInfo
-> IO String
1678 libAbiHash verbosity _pkg_descr lbi lib clbi
= do
1680 libBi
= libBuildInfo lib
1682 platform
= hostPlatform lbi
1684 (componentGhcOptions verbosity lbi libBi clbi
(componentBuildDir lbi clbi
))
1686 ghcOptMode
= toFlag GhcModeAbiHash
,
1687 ghcOptInputModules
= toNubListR
$ exposedModules lib
1690 -- due to a bug in GHC which tries to access the package database
1691 -- in conjunction with data families, backpack and internal libraries
1692 -- we may not modify the package database information. However,
1693 -- we can't bootstrap GHC with this version of Cabal anymore
1696 -- Package DBs unnecessary, and break ghc-cabal. See #3633
1697 -- BUT, put at least the global database so that 7.4 doesn't
1699 -- vanillaArgs0 { ghcOptPackageDBs = [GlobalPackageDB]
1700 -- , ghcOptPackages = mempty }
1701 sharedArgs
= vanillaArgs `mappend` mempty
{
1702 ghcOptDynLinkMode
= toFlag GhcDynamicOnly
,
1703 ghcOptFPic
= toFlag
True,
1704 ghcOptHiSuffix
= toFlag
"dyn_hi",
1705 ghcOptObjSuffix
= toFlag
"dyn_o",
1706 ghcOptExtra
= hcSharedOptions GHC libBi
1708 profArgs
= vanillaArgs `mappend` mempty
{
1709 ghcOptProfilingMode
= toFlag
True,
1710 ghcOptProfilingAuto
= Internal
.profDetailLevelFlag
True
1711 (withProfLibDetail lbi
),
1712 ghcOptHiSuffix
= toFlag
"p_hi",
1713 ghcOptObjSuffix
= toFlag
"p_o",
1714 ghcOptExtra
= hcProfOptions GHC libBi
1717 | withVanillaLib lbi
= vanillaArgs
1718 | withSharedLib lbi
= sharedArgs
1719 | withProfLib lbi
= profArgs
1720 |
otherwise = error "libAbiHash: Can't find an enabled library way"
1722 (ghcProg
, _
) <- requireProgram verbosity ghcProgram
(withPrograms lbi
)
1723 hash
<- getProgramInvocationOutput verbosity
1724 (ghcInvocation ghcProg comp platform ghcArgs
)
1725 return (takeWhile (not . isSpace) hash
)
1727 componentGhcOptions
:: Verbosity
-> LocalBuildInfo
1728 -> BuildInfo
-> ComponentLocalBuildInfo
-> FilePath
1730 componentGhcOptions verbosity lbi
=
1731 Internal
.componentGhcOptions verbosity implInfo lbi
1734 implInfo
= getImplInfo comp
1736 componentCcGhcOptions
:: Verbosity
-> LocalBuildInfo
1737 -> BuildInfo
-> ComponentLocalBuildInfo
1738 -> FilePath -> FilePath
1740 componentCcGhcOptions verbosity lbi
=
1741 Internal
.componentCcGhcOptions verbosity implInfo lbi
1744 implInfo
= getImplInfo comp
1746 -- -----------------------------------------------------------------------------
1749 -- |Install executables for GHC.
1750 installExe
:: Verbosity
1752 -> FilePath -- ^Where to copy the files to
1753 -> FilePath -- ^Build location
1754 -> (FilePath, FilePath) -- ^Executable (prefix,suffix)
1755 -> PackageDescription
1758 installExe verbosity lbi binDir buildPref
1759 (progprefix
, progsuffix
) _pkg exe
= do
1760 createDirectoryIfMissingVerbose verbosity
True binDir
1761 let exeName
' = unUnqualComponentName
$ exeName exe
1762 exeFileName
= exeTargetName
(hostPlatform lbi
) exe
1763 fixedExeBaseName
= progprefix
++ exeName
' ++ progsuffix
1764 installBinary dest
= do
1765 installExecutableFile verbosity
1766 (buildPref
</> exeName
' </> exeFileName
)
1767 (dest
<.> exeExtension
(hostPlatform lbi
))
1768 when (stripExes lbi
) $
1769 Strip
.stripExe verbosity
(hostPlatform lbi
) (withPrograms lbi
)
1770 (dest
<.> exeExtension
(hostPlatform lbi
))
1771 installBinary
(binDir
</> fixedExeBaseName
)
1773 -- |Install foreign library for GHC.
1774 installFLib
:: Verbosity
1776 -> FilePath -- ^install location
1777 -> FilePath -- ^Build location
1778 -> PackageDescription
1781 installFLib verbosity lbi targetDir builtDir _pkg flib
=
1782 install
(foreignLibIsShared flib
)
1785 (flibTargetName lbi flib
)
1787 install isShared srcDir dstDir name
= do
1788 let src
= srcDir
</> name
1789 dst
= dstDir
</> name
1790 createDirectoryIfMissingVerbose verbosity
True targetDir
1791 -- TODO: Should we strip? (stripLibs lbi)
1793 then installExecutableFile verbosity src dst
1794 else installOrdinaryFile verbosity src dst
1795 -- Now install appropriate symlinks if library is versioned
1796 let (Platform _ os
) = hostPlatform lbi
1797 when (not (null (foreignLibVersion flib os
))) $ do
1798 when (os
/= Linux
) $ die
' verbosity
1799 -- It should be impossible to get here.
1800 "Can't install foreign-library symlink on non-Linux OS"
1801 #ifndef mingw32_HOST_OS
1802 -- 'createSymbolicLink file1 file2' creates a symbolic link
1803 -- named 'file2' which points to the file 'file1'.
1804 -- Note that we do want a symlink to 'name' rather than
1805 -- 'dst', because the symlink will be relative to the
1806 -- directory it's created in.
1807 -- Finally, we first create the symlinks in a temporary
1808 -- directory and then rename to simulate 'ln --force'.
1809 withTempDirectory verbosity dstDir nm
$ \tmpDir
-> do
1810 let link1
= flibBuildName lbi flib
1811 link2
= "lib" ++ nm
<.> "so"
1812 createSymbolicLink name
(tmpDir
</> link1
)
1813 renameFile (tmpDir
</> link1
) (dstDir
</> link1
)
1814 createSymbolicLink name
(tmpDir
</> link2
)
1815 renameFile (tmpDir
</> link2
) (dstDir
</> link2
)
1818 nm
= unUnqualComponentName
$ foreignLibName flib
1819 #endif
/* mingw32_HOST_OS
*/
1822 -- |Install for ghc, .hi, .a and, if --with-ghci given, .o
1823 installLib
:: Verbosity
1825 -> FilePath -- ^install location
1826 -> FilePath -- ^install location for dynamic libraries
1827 -> FilePath -- ^Build location
1828 -> PackageDescription
1830 -> ComponentLocalBuildInfo
1832 installLib verbosity lbi targetDir dynlibTargetDir _builtDir _pkg lib clbi
= do
1833 -- copy .hi files over:
1834 whenVanilla
$ copyModuleFiles
"hi"
1835 whenProf
$ copyModuleFiles
"p_hi"
1836 whenShared
$ copyModuleFiles
"dyn_hi"
1838 -- copy the built library files over:
1841 sequence_ [ installOrdinary builtDir targetDir
(mkGenericStaticLibName
(l
++ f
))
1842 | l
<- getHSLibraryName
(componentUnitId clbi
):(extraBundledLibs
(libBuildInfo lib
))
1843 , f
<- "":extraLibFlavours
(libBuildInfo lib
)
1845 whenProf
$ installOrdinary builtDir targetDir profileLibName
1846 whenGHCi
$ installOrdinary builtDir targetDir ghciLibName
1847 whenShared
$ installShared builtDir dynlibTargetDir sharedLibName
1850 builtDir
= componentBuildDir lbi clbi
1852 install isShared srcDir dstDir name
= do
1853 let src
= srcDir
</> name
1854 dst
= dstDir
</> name
1856 createDirectoryIfMissingVerbose verbosity
True dstDir
1859 then installExecutableFile verbosity src dst
1860 else installOrdinaryFile verbosity src dst
1862 when (stripLibs lbi
) $ Strip
.stripLib verbosity
1863 (hostPlatform lbi
) (withPrograms lbi
) dst
1865 installOrdinary
= install
False
1866 installShared
= install
True
1868 copyModuleFiles ext
=
1869 findModuleFiles
[builtDir
] [ext
] (allLibModules lib clbi
)
1870 >>= installOrdinaryFiles verbosity targetDir
1872 compiler_id
= compilerId
(compiler lbi
)
1873 uid
= componentUnitId clbi
1874 profileLibName
= mkProfLibName uid
1875 ghciLibName
= Internal
.mkGHCiLibName uid
1876 sharedLibName
= (mkSharedLibName
(hostPlatform lbi
) compiler_id
) uid
1878 hasLib
= not $ null (allLibModules lib clbi
)
1879 && null (cSources
(libBuildInfo lib
))
1880 && null (cxxSources
(libBuildInfo lib
))
1881 has_code
= not (componentIsIndefinite clbi
)
1882 whenHasCode
= when has_code
1883 whenVanilla
= when (hasLib
&& withVanillaLib lbi
)
1884 whenProf
= when (hasLib
&& withProfLib lbi
&& has_code
)
1885 whenGHCi
= when (hasLib
&& withGHCiLib lbi
&& has_code
)
1886 whenShared
= when (hasLib
&& withSharedLib lbi
&& has_code
)
1888 -- -----------------------------------------------------------------------------
1891 hcPkgInfo
:: ProgramDb
-> HcPkg
.HcPkgInfo
1892 hcPkgInfo progdb
= HcPkg
.HcPkgInfo
{ HcPkg
.hcPkgProgram
= ghcPkgProg
1893 , HcPkg
.noPkgDbStack
= v
< [6,9]
1894 , HcPkg
.noVerboseFlag
= v
< [6,11]
1895 , HcPkg
.flagPackageConf
= v
< [7,5]
1896 , HcPkg
.supportsDirDbs
= v
>= [6,8]
1897 , HcPkg
.requiresDirDbs
= v
>= [7,10]
1898 , HcPkg
.nativeMultiInstance
= v
>= [7,10]
1899 , HcPkg
.recacheMultiInstance
= v
>= [6,12]
1900 , HcPkg
.suppressFilesCheck
= v
>= [6,6]
1903 v
= versionNumbers ver
1904 Just ghcPkgProg
= lookupProgram ghcPkgProgram progdb
1905 Just ver
= programVersion ghcPkgProg
1911 -> InstalledPackageInfo
1912 -> HcPkg
.RegisterOptions
1914 registerPackage verbosity progdb packageDbs installedPkgInfo registerOptions
=
1915 HcPkg
.register
(hcPkgInfo progdb
) verbosity packageDbs
1916 installedPkgInfo registerOptions
1918 pkgRoot
:: Verbosity
-> LocalBuildInfo
-> PackageDB
-> IO FilePath
1919 pkgRoot verbosity lbi
= pkgRoot
'
1921 pkgRoot
' GlobalPackageDB
=
1922 let Just ghcProg
= lookupProgram ghcProgram
(withPrograms lbi
)
1923 in fmap takeDirectory
(getGlobalPackageDB verbosity ghcProg
)
1924 pkgRoot
' UserPackageDB
= do
1925 appDir
<- getAppUserDataDirectory
"ghc"
1926 let ver
= compilerVersion
(compiler lbi
)
1927 subdir
= System
.Info
.arch
++ '-':System
.Info
.os
1929 rootDir
= appDir
</> subdir
1930 -- We must create the root directory for the user package database if it
1931 -- does not yet exists. Otherwise '${pkgroot}' will resolve to a
1932 -- directory at the time of 'ghc-pkg register', and registration will
1934 createDirectoryIfMissing
True rootDir
1936 pkgRoot
' (SpecificPackageDB fp
) = return (takeDirectory fp
)
1938 -- -----------------------------------------------------------------------------
1941 isDynamic
:: Compiler
-> Bool
1942 isDynamic
= Internal
.ghcLookupProperty
"GHC Dynamic"
1944 supportsDynamicToo
:: Compiler
-> Bool
1945 supportsDynamicToo
= Internal
.ghcLookupProperty
"Support dynamic-too"
1947 withExt
:: FilePath -> String -> FilePath
1948 withExt fp ext
= fp
<.> if takeExtension fp
/= ('.':ext
) then ext
else ""