2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE TupleSections #-}
6 module Distribution
.Simple
.GHCJS
10 , getInstalledPackagesMonitorFiles
11 , getPackageDBContents
26 , componentCcGhcOptions
33 -- * Constructing and deconstructing GHC environment files
34 , Internal
.GhcEnvironmentFileEntry
(..)
35 , Internal
.simpleGhcEnvironmentFile
36 , Internal
.renderGhcEnvironmentFile
37 , Internal
.writeGhcEnvironmentFile
38 , Internal
.ghcPlatformAndVersionString
39 , readGhcEnvironmentFile
40 , parseGhcEnvironmentFile
43 -- * Version-specific implementation quirks
48 import Distribution
.Compat
.Prelude
51 import Distribution
.CabalSpecVersion
52 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
53 import qualified Distribution
.InstalledPackageInfo
as InstalledPackageInfo
54 import Distribution
.ModuleName
(ModuleName
)
55 import qualified Distribution
.ModuleName
as ModuleName
56 import Distribution
.Package
57 import Distribution
.PackageDescription
as PD
58 import Distribution
.PackageDescription
.Utils
(cabalBug
)
59 import Distribution
.Pretty
60 import Distribution
.Simple
.BuildPaths
61 import Distribution
.Simple
.Compiler
62 import Distribution
.Simple
.Errors
63 import Distribution
.Simple
.Flag
64 import Distribution
.Simple
.GHC
.EnvironmentParser
65 import Distribution
.Simple
.GHC
.ImplInfo
66 import qualified Distribution
.Simple
.GHC
.Internal
as Internal
67 import qualified Distribution
.Simple
.Hpc
as Hpc
68 import Distribution
.Simple
.LocalBuildInfo
69 import Distribution
.Simple
.PackageIndex
(InstalledPackageIndex
)
70 import qualified Distribution
.Simple
.PackageIndex
as PackageIndex
71 import Distribution
.Simple
.Program
72 import Distribution
.Simple
.Program
.GHC
73 import qualified Distribution
.Simple
.Program
.HcPkg
as HcPkg
74 import qualified Distribution
.Simple
.Program
.Strip
as Strip
75 import Distribution
.Simple
.Setup
.Config
76 import Distribution
.Simple
.Utils
77 import Distribution
.System
78 import Distribution
.Types
.ComponentLocalBuildInfo
79 import Distribution
.Types
.PackageName
.Magic
80 import Distribution
.Types
.ParStrat
81 import Distribution
.Utils
.NubList
82 import Distribution
.Utils
.Path
83 import Distribution
.Verbosity
(Verbosity
)
84 import Distribution
.Version
86 import Control
.Monad
(msum)
87 import Data
.Char (isLower)
88 import qualified Data
.Map
as Map
89 import System
.Directory
91 , createDirectoryIfMissing
93 , getAppUserDataDirectory
97 import System
.FilePath
105 import qualified System
.Info
107 -- -----------------------------------------------------------------------------
115 -> IO (Compiler
, Maybe Platform
, ProgramDb
)
116 configure verbosity hcPath hcPkgPath conf0
= do
117 (ghcjsProg
, ghcjsVersion
, progdb1
) <-
118 requireProgramVersion
121 (orLaterVersion
(mkVersion
[0, 1]))
122 (userMaybeSpecifyPath
"ghcjs" hcPath conf0
)
124 Just ghcjsGhcVersion
<- findGhcjsGhcVersion verbosity
(programPath ghcjsProg
)
125 unless (ghcjsGhcVersion
< mkVersion
[8, 8]) $
127 "Unknown/unsupported 'ghc' version detected "
129 ++ prettyShow cabalVersion
130 ++ " supports 'ghc' version < 8.8): "
131 ++ programPath ghcjsProg
132 ++ " is based on GHC version "
133 ++ prettyShow ghcjsGhcVersion
135 let implInfo
= ghcjsVersionImplInfo ghcjsVersion ghcjsGhcVersion
137 -- This is slightly tricky, we have to configure ghc first, then we use the
138 -- location of ghc to help find ghc-pkg in the case that the user did not
139 -- specify the location of ghc-pkg directly:
140 (ghcjsPkgProg
, ghcjsPkgVersion
, progdb2
) <-
141 requireProgramVersion
144 { programFindLocation
= guessGhcjsPkgFromGhcjsPath ghcjsProg
147 (userMaybeSpecifyPath
"ghcjs-pkg" hcPkgPath progdb1
)
149 Just ghcjsPkgGhcjsVersion
<-
150 findGhcjsPkgGhcjsVersion
152 (programPath ghcjsPkgProg
)
154 when (ghcjsVersion
/= ghcjsPkgGhcjsVersion
) $
155 dieWithException verbosity
$
157 (programPath ghcjsProg
)
159 (programPath ghcjsPkgProg
)
162 when (ghcjsGhcVersion
/= ghcjsPkgVersion
) $
163 dieWithException verbosity
$
164 VersionMismatchGHCJS
(programPath ghcjsProg
) ghcjsGhcVersion
(programPath ghcjsPkgProg
) ghcjsPkgVersion
166 -- Likewise we try to find the matching hsc2hs and haddock programs.
169 { programFindLocation
=
170 guessHsc2hsFromGhcjsPath ghcjsProg
174 { programFindLocation
=
175 guessHaddockFromGhcjsPath ghcjsProg
179 { programFindLocation
= guessHpcFromGhcjsPath ghcjsProg
182 runghcProgram' = runghcProgram {
183 programFindLocation = guessRunghcFromGhcjsPath ghcjsProg
186 addKnownProgram haddockProgram
' $
187 addKnownProgram hsc2hsProgram
' $
188 addKnownProgram hpcProgram
' $
189 {- addKnownProgram runghcProgram' -} progdb2
191 languages
<- Internal
.getLanguages verbosity implInfo ghcjsProg
192 extensions
<- Internal
.getExtensions verbosity implInfo ghcjsProg
194 ghcjsInfo
<- Internal
.getGhcInfo verbosity implInfo ghcjsProg
195 let ghcInfoMap
= Map
.fromList ghcjsInfo
199 { compilerId
= CompilerId GHCJS ghcjsVersion
202 "ghc" ++ intercalate
"_" (map show . versionNumbers
$ ghcjsGhcVersion
)
203 , compilerCompat
= [CompilerId GHC ghcjsGhcVersion
]
204 , compilerLanguages
= languages
205 , compilerExtensions
= extensions
206 , compilerProperties
= ghcInfoMap
208 compPlatform
= Internal
.targetPlatform ghcjsInfo
209 return (comp
, compPlatform
, progdb3
)
211 guessGhcjsPkgFromGhcjsPath
215 -> IO (Maybe (FilePath, [FilePath]))
216 guessGhcjsPkgFromGhcjsPath
= guessToolFromGhcjsPath ghcjsPkgProgram
218 guessHsc2hsFromGhcjsPath
222 -> IO (Maybe (FilePath, [FilePath]))
223 guessHsc2hsFromGhcjsPath
= guessToolFromGhcjsPath hsc2hsProgram
225 guessHaddockFromGhcjsPath
229 -> IO (Maybe (FilePath, [FilePath]))
230 guessHaddockFromGhcjsPath
= guessToolFromGhcjsPath haddockProgram
232 guessHpcFromGhcjsPath
236 -> IO (Maybe (FilePath, [FilePath]))
237 guessHpcFromGhcjsPath
= guessToolFromGhcjsPath hpcProgram
239 guessToolFromGhcjsPath
244 -> IO (Maybe (FilePath, [FilePath]))
245 guessToolFromGhcjsPath tool ghcjsProg verbosity searchpath
=
247 let toolname
= programName tool
248 given_path
= programPath ghcjsProg
249 given_dir
= takeDirectory given_path
250 real_path
<- canonicalizePath given_path
251 let real_dir
= takeDirectory real_path
252 versionSuffix path
= takeVersionSuffix
(dropExeExtension path
)
253 given_suf
= versionSuffix given_path
254 real_suf
= versionSuffix real_path
255 guessNormal dir
= dir
</> toolname
<.> exeExtension buildPlatform
258 </> (toolname
++ "-ghcjs")
259 <.> exeExtension buildPlatform
260 guessGhcjsVersioned dir suf
=
262 </> (toolname
++ "-ghcjs" ++ suf
)
263 <.> exeExtension buildPlatform
264 guessVersioned dir suf
=
266 </> (toolname
++ suf
)
267 <.> exeExtension buildPlatform
269 |
null suf
= [guessGhcjs dir
, guessNormal dir
]
271 [ guessGhcjsVersioned dir suf
272 , guessVersioned dir suf
277 mkGuesses given_dir given_suf
278 ++ if real_path
== given_path
280 else mkGuesses real_dir real_suf
284 ++ " near compiler in "
286 debug verbosity
$ "candidate locations: " ++ show guesses
287 exists
<- traverse
doesFileExist guesses
288 case [file |
(file
, True) <- zip guesses exists
] of
289 -- If we can't find it near ghc, fall back to the usual
291 [] -> programFindLocation tool verbosity searchpath
293 info verbosity
$ "found " ++ toolname
++ " in " ++ fp
296 . takeWhile (\(_file
, exist
) -> not exist
)
298 return (Just
(fp
, lookedAt
))
300 takeVersionSuffix
:: FilePath -> String
301 takeVersionSuffix
= takeWhileEndLE isSuffixChar
303 isSuffixChar
:: Char -> Bool
304 isSuffixChar c
= isDigit c || c
== '.' || c
== '-'
306 getGhcInfo
:: Verbosity
-> ConfiguredProgram
-> IO [(String, String)]
307 getGhcInfo verbosity ghcjsProg
= Internal
.getGhcInfo verbosity implInfo ghcjsProg
309 version
= fromMaybe (error "GHCJS.getGhcInfo: no version") $ programVersion ghcjsProg
310 implInfo
= ghcVersionImplInfo version
312 -- | Given a single package DB, return all installed packages.
317 -> IO InstalledPackageIndex
318 getPackageDBContents verbosity packagedb progdb
= do
319 pkgss
<- getInstalledPackages
' verbosity
[packagedb
] progdb
320 toPackageIndex verbosity pkgss progdb
322 -- | Given a package DB stack, return all installed packages.
327 -> IO InstalledPackageIndex
328 getInstalledPackages verbosity packagedbs progdb
= do
329 checkPackageDbEnvVar verbosity
330 checkPackageDbStack verbosity packagedbs
331 pkgss
<- getInstalledPackages
' verbosity packagedbs progdb
332 index <- toPackageIndex verbosity pkgss progdb
337 -> [(PackageDB
, [InstalledPackageInfo
])]
339 -> IO InstalledPackageIndex
340 toPackageIndex verbosity pkgss progdb
= do
341 -- On Windows, various fields have $topdir/foo rather than full
342 -- paths. We need to substitute the right value in so that when
343 -- we, for example, call gcc, we have proper paths to give it.
344 topDir
<- getLibDir
' verbosity ghcjsProg
346 [ PackageIndex
.fromList
(map (Internal
.substTopDir topDir
) pkgs
)
349 return $! (mconcat
indices)
351 ghcjsProg
= fromMaybe (error "GHCJS.toPackageIndex no ghcjs program") $ lookupProgram ghcjsProgram progdb
353 getLibDir
:: Verbosity
-> LocalBuildInfo
-> IO FilePath
354 getLibDir verbosity lbi
=
355 dropWhileEndLE
isSpace
356 `
fmap` getDbProgramOutput
362 getLibDir
' :: Verbosity
-> ConfiguredProgram
-> IO FilePath
363 getLibDir
' verbosity ghcjsProg
=
364 dropWhileEndLE
isSpace
365 `
fmap` getProgramOutput verbosity ghcjsProg
["--print-libdir"]
367 -- | Return the 'FilePath' to the global GHC package database.
368 getGlobalPackageDB
:: Verbosity
-> ConfiguredProgram
-> IO FilePath
369 getGlobalPackageDB verbosity ghcProg
=
370 dropWhileEndLE
isSpace
371 `
fmap` getProgramOutput verbosity ghcProg
["--print-global-package-db"]
373 -- | Return the 'FilePath' to the per-user GHC package database.
374 getUserPackageDB
:: Verbosity
-> ConfiguredProgram
-> Platform
-> IO FilePath
375 getUserPackageDB _verbosity ghcjsProg platform
= do
376 -- It's rather annoying that we have to reconstruct this, because ghc
377 -- hides this information from us otherwise. But for certain use cases
378 -- like change monitoring it really can't remain hidden.
379 appdir
<- getAppUserDataDirectory
"ghcjs"
380 return (appdir
</> platformAndVersion
</> packageConfFileName
)
383 Internal
.ghcPlatformAndVersionString
386 packageConfFileName
= "package.conf.d"
387 ghcjsVersion
= fromMaybe (error "GHCJS.getUserPackageDB: no version") $ programVersion ghcjsProg
389 checkPackageDbEnvVar
:: Verbosity
-> IO ()
390 checkPackageDbEnvVar verbosity
=
391 Internal
.checkPackageDbEnvVar verbosity
"GHCJS" "GHCJS_PACKAGE_PATH"
393 checkPackageDbStack
:: Verbosity
-> PackageDBStack
-> IO ()
394 checkPackageDbStack _
(GlobalPackageDB
: rest
)
395 | GlobalPackageDB `
notElem` rest
= return ()
396 checkPackageDbStack verbosity rest
397 | GlobalPackageDB `
notElem` rest
=
398 dieWithException verbosity GlobalPackageDBLimitation
399 checkPackageDbStack verbosity _
=
400 dieWithException verbosity GlobalPackageDBSpecifiedFirst
402 getInstalledPackages
'
406 -> IO [(PackageDB
, [InstalledPackageInfo
])]
407 getInstalledPackages
' verbosity packagedbs progdb
=
410 pkgs
<- HcPkg
.dump
(hcPkgInfo progdb
) verbosity packagedb
411 return (packagedb
, pkgs
)
412 | packagedb
<- packagedbs
415 -- | Get the packages from specific PackageDBs, not cumulative.
416 getInstalledPackagesMonitorFiles
422 getInstalledPackagesMonitorFiles verbosity platform progdb
=
423 traverse getPackageDBPath
425 getPackageDBPath
:: PackageDB
-> IO FilePath
426 getPackageDBPath GlobalPackageDB
=
427 selectMonitorFile
=<< getGlobalPackageDB verbosity ghcjsProg
428 getPackageDBPath UserPackageDB
=
429 selectMonitorFile
=<< getUserPackageDB verbosity ghcjsProg platform
430 getPackageDBPath
(SpecificPackageDB path
) = selectMonitorFile path
432 -- GHC has old style file dbs, and new style directory dbs.
433 -- Note that for dir style dbs, we only need to monitor the cache file, not
434 -- the whole directory. The ghc program itself only reads the cache file
435 -- so it's safe to only monitor this one file.
436 selectMonitorFile path
= do
437 isFileStyle
<- doesFileExist path
440 else return (path
</> "package.cache")
442 ghcjsProg
= fromMaybe (error "GHCJS.toPackageIndex no ghcjs program") $ lookupProgram ghcjsProgram progdb
444 toJSLibName
:: String -> String
446 | takeExtension lib `
elem`
[".dll", ".dylib", ".so"] =
447 replaceExtension lib
"js_so"
448 | takeExtension lib
== ".a" = replaceExtension lib
"js_a"
449 |
otherwise = lib
<.> "js_a"
451 -- -----------------------------------------------------------------------------
452 -- Building a library
457 -> PackageDescription
460 -> ComponentLocalBuildInfo
462 buildLib
= buildOrReplLib Nothing
468 -> PackageDescription
471 -> ComponentLocalBuildInfo
473 replLib
= buildOrReplLib
. Just
479 -> PackageDescription
482 -> ComponentLocalBuildInfo
484 buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi
= do
485 let uid
= componentUnitId clbi
486 libTargetDir
= componentBuildDir lbi clbi
487 whenVanillaLib forceVanilla
=
488 when (forceVanilla || withVanillaLib lbi
)
489 whenProfLib
= when (withProfLib lbi
)
490 whenSharedLib forceShared
=
491 when (forceShared || withSharedLib lbi
)
492 whenStaticLib forceStatic
=
493 when (forceStatic || withStaticLib lbi
)
494 -- whenGHCiLib = when (withGHCiLib lbi)
495 forRepl
= maybe False (const True) mReplFlags
496 -- ifReplLib = when forRepl
498 implInfo
= getImplInfo comp
499 platform
@(Platform _hostArch _hostOS
) = hostPlatform lbi
500 has_code
= not (componentIsIndefinite clbi
)
502 (ghcjsProg
, _
) <- requireProgram verbosity ghcjsProgram
(withPrograms lbi
)
503 let runGhcjsProg
= runGHC verbosity ghcjsProg comp platform
505 let libBi
= libBuildInfo lib
507 -- fixme flags shouldn't depend on ghcjs being dynamic or not
508 let isGhcjsDynamic
= isDynamic comp
509 dynamicTooSupported
= supportsDynamicToo comp
510 doingTH
= usesTemplateHaskellOrQQ libBi
511 forceVanillaLib
= doingTH
&& not isGhcjsDynamic
512 forceSharedLib
= doingTH
&& isGhcjsDynamic
513 -- TH always needs default libs, even when building for profiling
515 -- Determine if program coverage should be enabled and if so, what
516 -- '-hpcdir' should be.
517 let isCoverageEnabled
= libCoverage lbi
518 -- TODO: Historically HPC files have been put into a directory which
519 -- has the package name. I'm going to avoid changing this for
520 -- now, but it would probably be better for this to be the
521 -- component ID instead...
522 pkg_name
= prettyShow
(PD
.package pkg_descr
)
523 distPref
= fromFlag
$ configDistPref
$ configFlags lbi
525 | forRepl
= mempty
-- HPC is not supported in ghci
526 | isCoverageEnabled
= toFlag
$ Hpc
.mixDir distPref way pkg_name
529 createDirectoryIfMissingVerbose verbosity
True libTargetDir
530 -- TODO: do we need to put hs-boot files into place for mutually recursive
532 let cLikeFiles
= fromNubListR
$ toNubListR
(cSources libBi
) <> toNubListR
(cxxSources libBi
)
533 jsSrcs
= jsSources libBi
534 cObjs
= map (`replaceExtension` objExtension
) cLikeFiles
535 baseOpts
= componentGhcOptions verbosity lbi libBi clbi libTargetDir
540 , getHSLibraryName uid
541 , "-js-lib-outputdir"
549 { ghcOptMode
= toFlag GhcModeMake
550 , ghcOptNumJobs
= numJobs
551 , ghcOptInputModules
= toNubListR
$ allLibModules lib clbi
552 , ghcOptHPCDir
= hpcdir Hpc
.Vanilla
554 vanillaOpts
= vanillaOptsNoJsLib `mappend` linkJsLibOpts
557 adjustExts
"p_hi" "p_o" vanillaOpts
559 { ghcOptProfilingMode
= toFlag
True
560 , ghcOptProfilingAuto
=
561 Internal
.profDetailLevelFlag
563 (withProfLibDetail lbi
)
564 , -- ghcOptHiSuffix = toFlag "p_hi",
565 -- ghcOptObjSuffix = toFlag "p_o",
566 ghcOptExtra
= hcProfOptions GHC libBi
567 , ghcOptHPCDir
= hpcdir Hpc
.Prof
571 adjustExts
"dyn_hi" "dyn_o" vanillaOpts
573 { ghcOptDynLinkMode
= toFlag GhcDynamicOnly
574 , ghcOptFPic
= toFlag
True
575 , -- ghcOptHiSuffix = toFlag "dyn_hi",
576 -- ghcOptObjSuffix = toFlag "dyn_o",
577 ghcOptExtra
= hcSharedOptions GHC libBi
578 , ghcOptHPCDir
= hpcdir Hpc
.Dyn
584 { ghcOptDynLinkMode
= toFlag GhcStaticAndDynamic
585 , ghcOptDynHiSuffix
= toFlag
"js_dyn_hi"
586 , ghcOptDynObjSuffix
= toFlag
"js_dyn_o"
587 , ghcOptHPCDir
= hpcdir Hpc
.Dyn
590 unless (forRepl ||
null (allLibModules lib clbi
) && null jsSrcs
&& null cObjs
) $
592 let vanilla
= whenVanillaLib forceVanillaLib
(runGhcjsProg vanillaOpts
)
593 shared
= whenSharedLib forceSharedLib
(runGhcjsProg sharedOpts
)
596 && (forceVanillaLib || withVanillaLib lbi
)
597 && (forceSharedLib || withSharedLib lbi
)
598 && null (hcSharedOptions GHC libBi
)
604 runGhcjsProg vanillaSharedOpts
605 case (hpcdir Hpc
.Dyn
, hpcdir Hpc
.Vanilla
) of
606 (Flag dynDir
, Flag vanillaDir
) ->
607 -- When the vanilla and shared library builds are done
608 -- in one pass, only one set of HPC module interfaces
609 -- are generated. This set should suffice for both
610 -- static and dynamically linked executables. We copy
611 -- the modules interfaces so they are available under
613 copyDirectoryRecursive verbosity dynDir vanillaDir
617 then do shared
; vanilla
618 else do vanilla
; shared
619 whenProfLib
(runGhcjsProg profOpts
)
621 -- Build any C++ sources separately.
623 unless (not has_code || null (cxxSources libBi) || not nativeToo) $ do
624 info verbosity "Building C++ Sources..."
626 [ do let baseCxxOpts = Internal.componentCxxGhcOptions verbosity implInfo
627 lbi libBi clbi libTargetDir filename
628 vanillaCxxOpts = if isGhcjsDynamic
629 then baseCxxOpts { ghcOptFPic = toFlag True }
631 profCxxOpts = vanillaCxxOpts `mappend` mempty {
632 ghcOptProfilingMode = toFlag True,
633 ghcOptObjSuffix = toFlag "p_o"
635 sharedCxxOpts = vanillaCxxOpts `mappend` mempty {
636 ghcOptFPic = toFlag True,
637 ghcOptDynLinkMode = toFlag GhcDynamicOnly,
638 ghcOptObjSuffix = toFlag "dyn_o"
640 odir = fromFlag (ghcOptObjDir vanillaCxxOpts)
641 createDirectoryIfMissingVerbose verbosity True odir
642 let runGhcProgIfNeeded cxxOpts = do
643 needsRecomp <- checkNeedsRecompilation filename cxxOpts
644 when needsRecomp $ runGhcjsProg cxxOpts
645 runGhcProgIfNeeded vanillaCxxOpts
647 whenSharedLib forceSharedLib (runGhcProgIfNeeded sharedCxxOpts)
648 unless forRepl $ whenProfLib (runGhcProgIfNeeded profCxxOpts)
649 | filename <- cxxSources libBi]
652 when (null (allLibModules lib clbi)) $ warn verbosity "No exposed modules"
653 ifReplLib (runGhcjsProg replOpts)
655 -- build any C sources
656 -- TODO: Add support for S and CMM files.
658 unless (not has_code || null (cSources libBi) || not nativeToo) $ do
659 info verbosity "Building C Sources..."
661 [ do let baseCcOpts = Internal.componentCcGhcOptions verbosity implInfo
662 lbi libBi clbi libTargetDir filename
663 vanillaCcOpts = if isGhcjsDynamic
664 -- Dynamic GHC requires C sources to be built
665 -- with -fPIC for REPL to work. See #2207.
666 then baseCcOpts { ghcOptFPic = toFlag True }
668 profCcOpts = vanillaCcOpts `mappend` mempty {
669 ghcOptProfilingMode = toFlag True,
670 ghcOptObjSuffix = toFlag "p_o"
672 sharedCcOpts = vanillaCcOpts `mappend` mempty {
673 ghcOptFPic = toFlag True,
674 ghcOptDynLinkMode = toFlag GhcDynamicOnly,
675 ghcOptObjSuffix = toFlag "dyn_o"
677 odir = fromFlag (ghcOptObjDir vanillaCcOpts)
678 createDirectoryIfMissingVerbose verbosity True odir
679 let runGhcProgIfNeeded ccOpts = do
680 needsRecomp <- checkNeedsRecompilation filename ccOpts
681 when needsRecomp $ runGhcjsProg ccOpts
682 runGhcProgIfNeeded vanillaCcOpts
684 whenSharedLib forceSharedLib (runGhcProgIfNeeded sharedCcOpts)
685 unless forRepl $ whenProfLib (runGhcProgIfNeeded profCcOpts)
686 | filename <- cSources libBi]
688 -- TODO: problem here is we need the .c files built first, so we can load them
689 -- with ghci, but .c files can depend on .h files generated by ghc by ffi
694 when has_code
. when False {- fixme nativeToo -} . unless forRepl
$ do
695 info verbosity
"Linking..."
698 (`replaceExtension`
("dyn_" ++ objExtension
))
699 (cSources libBi
++ cxxSources libBi
)
700 compiler_id
= compilerId
(compiler lbi
)
701 sharedLibFilePath
= libTargetDir
</> mkSharedLibName
(hostPlatform lbi
) compiler_id uid
702 staticLibFilePath
= libTargetDir
</> mkStaticLibName
(hostPlatform lbi
) compiler_id uid
708 stubObjs <- catMaybes <$> sequenceA
709 [ findFileWithExtension [objExtension] [libTargetDir]
710 (ModuleName.toFilePath x ++"_stub")
711 | ghcVersion < mkVersion [7,2] -- ghc-7.2+ does not make _stub.o files
712 , x <- allLibModules lib clbi ]
713 stubProfObjs <- catMaybes <$> sequenceA
714 [ findFileWithExtension ["p_" ++ objExtension] [libTargetDir]
715 (ModuleName.toFilePath x ++"_stub")
716 | ghcVersion < mkVersion [7,2] -- ghc-7.2+ does not make _stub.o files
717 , x <- allLibModules lib clbi ]
718 stubSharedObjs <- catMaybes <$> sequenceA
719 [ findFileWithExtension ["dyn_" ++ objExtension] [libTargetDir]
720 (ModuleName.toFilePath x ++"_stub")
721 | ghcVersion < mkVersion [7,2] -- ghc-7.2+ does not make _stub.o files
722 , x <- allLibModules lib clbi ]
725 Internal
.getHaskellObjects
736 Internal
.getHaskellObjects
742 ("dyn_" ++ objExtension
)
746 unless (null hObjs
&& null cObjs
&& null stubObjs
) $ do
747 rpaths
<- getRPaths lbi clbi
749 let staticObjectFiles
=
751 ++ map (libTargetDir
</>) cObjs
755 ++ map (libTargetDir
</>) cSharedObjs
757 -- After the relocation lib is created we invoke ghc -shared
758 -- with the dependencies spelled out as -package arguments
759 -- and ghc invokes the linker with the proper library paths
762 { ghcOptShared
= toFlag
True
763 , ghcOptDynLinkMode
= toFlag GhcDynamicOnly
764 , ghcOptInputFiles
= toNubListR dynamicObjectFiles
765 , ghcOptOutputFile
= toFlag sharedLibFilePath
766 , ghcOptExtra
= hcSharedOptions GHC libBi
767 , -- For dynamic libs, Mac OS/X needs to know the install location
768 -- at build time. This only applies to GHC < 7.8 - see the
769 -- discussion in #1660.
771 ghcOptDylibName = if hostOS == OSX
772 && ghcVersion < mkVersion [7,8]
773 then toFlag sharedLibInstallPath
775 ghcOptHideAllPackages
= toFlag
True
776 , ghcOptNoAutoLinkPackages
= toFlag
True
777 , ghcOptPackageDBs
= withPackageDB lbi
778 , ghcOptThisUnitId
= case clbi
of
779 LibComponentLocalBuildInfo
{componentCompatPackageKey
= pk
} ->
782 , ghcOptThisComponentId
= case clbi
of
783 LibComponentLocalBuildInfo
{componentInstantiatedWith
= insts
} ->
786 else toFlag
(componentComponentId clbi
)
788 , ghcOptInstantiatedWith
= case clbi
of
789 LibComponentLocalBuildInfo
{componentInstantiatedWith
= insts
} ->
794 Internal
.mkGhcOptPackages mempty clbi
795 , ghcOptLinkLibs
= extraLibs libBi
796 , ghcOptLinkLibPath
= toNubListR
$ extraLibDirs libBi
797 , ghcOptLinkFrameworks
= toNubListR
$ PD
.frameworks libBi
798 , ghcOptLinkFrameworkDirs
=
799 toNubListR
$ PD
.extraFrameworkDirs libBi
800 , ghcOptRPaths
= rpaths
804 { ghcOptStaticLib
= toFlag
True
805 , ghcOptInputFiles
= toNubListR staticObjectFiles
806 , ghcOptOutputFile
= toFlag staticLibFilePath
807 , ghcOptExtra
= hcStaticOptions GHC libBi
808 , ghcOptHideAllPackages
= toFlag
True
809 , ghcOptNoAutoLinkPackages
= toFlag
True
810 , ghcOptPackageDBs
= withPackageDB lbi
811 , ghcOptThisUnitId
= case clbi
of
812 LibComponentLocalBuildInfo
{componentCompatPackageKey
= pk
} ->
815 , ghcOptThisComponentId
= case clbi
of
816 LibComponentLocalBuildInfo
{componentInstantiatedWith
= insts
} ->
819 else toFlag
(componentComponentId clbi
)
821 , ghcOptInstantiatedWith
= case clbi
of
822 LibComponentLocalBuildInfo
{componentInstantiatedWith
= insts
} ->
827 Internal
.mkGhcOptPackages mempty clbi
828 , ghcOptLinkLibs
= extraLibs libBi
829 , ghcOptLinkLibPath
= toNubListR
$ extraLibDirs libBi
832 info verbosity
(show (ghcOptPackages ghcSharedLinkArgs
))
834 whenVanillaLib False $ do
835 Ar.createArLibArchive verbosity lbi vanillaLibFilePath staticObjectFiles
837 (ldProg, _) <- requireProgram verbosity ldProgram (withPrograms lbi)
838 Ld.combineObjectFiles verbosity lbi ldProg
839 ghciLibFilePath staticObjectFiles
843 Ar.createArLibArchive verbosity lbi profileLibFilePath profObjectFiles
845 (ldProg, _) <- requireProgram verbosity ldProgram (withPrograms lbi)
846 Ld.combineObjectFiles verbosity lbi ldProg
847 ghciProfLibFilePath profObjectFiles
849 whenSharedLib
False $
850 runGhcjsProg ghcSharedLinkArgs
852 whenStaticLib
False $
853 runGhcjsProg ghcStaticLinkArgs
855 -- | Start a REPL without loading any source files.
863 startInterpreter verbosity progdb comp platform packageDBs
= do
866 { ghcOptMode
= toFlag GhcModeInteractive
867 , ghcOptPackageDBs
= packageDBs
869 checkPackageDbStack verbosity packageDBs
870 (ghcjsProg
, _
) <- requireProgram verbosity ghcjsProgram progdb
871 runGHC verbosity ghcjsProg comp platform replOpts
873 -- -----------------------------------------------------------------------------
874 -- Building an executable or foreign library
876 -- | Build a foreign library
880 -> PackageDescription
883 -> ComponentLocalBuildInfo
885 buildFLib v njobs pkg lbi
= gbuild v njobs pkg lbi
. GBuildFLib
891 -> PackageDescription
894 -> ComponentLocalBuildInfo
896 replFLib replFlags v njobs pkg lbi
=
897 gbuild v njobs pkg lbi
. GReplFLib replFlags
899 -- | Build an executable with GHC.
903 -> PackageDescription
906 -> ComponentLocalBuildInfo
908 buildExe v njobs pkg lbi
= gbuild v njobs pkg lbi
. GBuildExe
914 -> PackageDescription
917 -> ComponentLocalBuildInfo
919 replExe replFlags v njobs pkg lbi
=
920 gbuild v njobs pkg lbi
. GReplExe replFlags
922 -- | Building an executable, starting the REPL, and building foreign
923 -- libraries are all very similar and implemented in 'gbuild'. The
924 -- 'GBuildMode' distinguishes between the various kinds of operation.
926 = GBuildExe Executable
927 | GReplExe
[String] Executable
928 | GBuildFLib ForeignLib
929 | GReplFLib
[String] ForeignLib
931 gbuildInfo
:: GBuildMode
-> BuildInfo
932 gbuildInfo
(GBuildExe exe
) = buildInfo exe
933 gbuildInfo
(GReplExe _ exe
) = buildInfo exe
934 gbuildInfo
(GBuildFLib flib
) = foreignLibBuildInfo flib
935 gbuildInfo
(GReplFLib _ flib
) = foreignLibBuildInfo flib
937 gbuildName
:: GBuildMode
-> String
938 gbuildName
(GBuildExe exe
) = unUnqualComponentName
$ exeName exe
939 gbuildName
(GReplExe _ exe
) = unUnqualComponentName
$ exeName exe
940 gbuildName
(GBuildFLib flib
) = unUnqualComponentName
$ foreignLibName flib
941 gbuildName
(GReplFLib _ flib
) = unUnqualComponentName
$ foreignLibName flib
943 gbuildTargetName
:: LocalBuildInfo
-> GBuildMode
-> String
944 gbuildTargetName lbi
(GBuildExe exe
) = exeTargetName
(hostPlatform lbi
) exe
945 gbuildTargetName lbi
(GReplExe _ exe
) = exeTargetName
(hostPlatform lbi
) exe
946 gbuildTargetName lbi
(GBuildFLib flib
) = flibTargetName lbi flib
947 gbuildTargetName lbi
(GReplFLib _ flib
) = flibTargetName lbi flib
949 exeTargetName
:: Platform
-> Executable
-> String
950 exeTargetName platform exe
= unUnqualComponentName
(exeName exe
) `withExt` exeExtension platform
952 -- | Target name for a foreign library (the actual file name)
954 -- We do not use mkLibName and co here because the naming for foreign libraries
955 -- is slightly different (we don't use "_p" or compiler version suffices, and we
956 -- don't want the "lib" prefix on Windows).
958 -- TODO: We do use `dllExtension` and co here, but really that's wrong: they
959 -- use the OS used to build cabal to determine which extension to use, rather
960 -- than the target OS (but this is wrong elsewhere in Cabal as well).
961 flibTargetName
:: LocalBuildInfo
-> ForeignLib
-> String
962 flibTargetName lbi flib
=
963 case (os
, foreignLibType flib
) of
964 (Windows
, ForeignLibNativeShared
) -> nm
<.> "dll"
965 (Windows
, ForeignLibNativeStatic
) -> nm
<.> "lib"
966 (Linux
, ForeignLibNativeShared
) -> "lib" ++ nm
<.> versionedExt
967 (_other
, ForeignLibNativeShared
) -> "lib" ++ nm
<.> dllExtension
(hostPlatform lbi
)
968 (_other
, ForeignLibNativeStatic
) -> "lib" ++ nm
<.> staticLibExtension
(hostPlatform lbi
)
969 (_any
, ForeignLibTypeUnknown
) -> cabalBug
"unknown foreign lib type"
972 nm
= unUnqualComponentName
$ foreignLibName flib
976 let (Platform _ os
') = hostPlatform lbi
979 -- If a foreign lib foo has lib-version-info 5:1:2 or
980 -- lib-version-linux 3.2.1, it should be built as libfoo.so.3.2.1
981 -- Libtool's version-info data is translated into library versions in a
982 -- nontrivial way: so refer to libtool documentation.
983 versionedExt
:: String
985 let nums
= foreignLibVersion flib os
986 in foldl (<.>) "so" (map show nums
)
988 -- | Name for the library when building.
990 -- If the `lib-version-info` field or the `lib-version-linux` field of
991 -- a foreign library target is set, we need to incorporate that
992 -- version into the SONAME field.
994 -- If a foreign library foo has lib-version-info 5:1:2, it should be
995 -- built as libfoo.so.3.2.1. We want it to get soname libfoo.so.3.
996 -- However, GHC does not allow overriding soname by setting linker
997 -- options, as it sets a soname of its own (namely the output
998 -- filename), after the user-supplied linker options. Hence, we have
999 -- to compile the library with the soname as its filename. We rename
1000 -- the compiled binary afterwards.
1002 -- This method allows to adjust the name of the library at build time
1003 -- such that the correct soname can be set.
1004 flibBuildName
:: LocalBuildInfo
-> ForeignLib
-> String
1005 flibBuildName lbi flib
1006 -- On linux, if a foreign-library has version data, the first digit is used
1007 -- to produce the SONAME.
1008 |
(os
, foreignLibType flib
)
1009 == (Linux
, ForeignLibNativeShared
) =
1010 let nums
= foreignLibVersion flib os
1011 in "lib" ++ nm
<.> foldl (<.>) "so" (map show (take 1 nums
))
1012 |
otherwise = flibTargetName lbi flib
1016 let (Platform _ os
') = hostPlatform lbi
1020 nm
= unUnqualComponentName
$ foreignLibName flib
1022 gbuildIsRepl
:: GBuildMode
-> Bool
1023 gbuildIsRepl
(GBuildExe _
) = False
1024 gbuildIsRepl
(GReplExe _ _
) = True
1025 gbuildIsRepl
(GBuildFLib _
) = False
1026 gbuildIsRepl
(GReplFLib _ _
) = True
1028 gbuildNeedDynamic
:: LocalBuildInfo
-> GBuildMode
-> Bool
1029 gbuildNeedDynamic lbi bm
=
1031 GBuildExe _
-> withDynExe lbi
1032 GReplExe _ _
-> withDynExe lbi
1033 GBuildFLib flib
-> withDynFLib flib
1034 GReplFLib _ flib
-> withDynFLib flib
1037 case foreignLibType flib
of
1038 ForeignLibNativeShared
->
1039 ForeignLibStandalone `
notElem` foreignLibOptions flib
1040 ForeignLibNativeStatic
->
1042 ForeignLibTypeUnknown
->
1043 cabalBug
"unknown foreign lib type"
1045 gbuildModDefFiles
:: GBuildMode
-> [FilePath]
1046 gbuildModDefFiles
(GBuildExe _
) = []
1047 gbuildModDefFiles
(GReplExe _ _
) = []
1048 gbuildModDefFiles
(GBuildFLib flib
) = foreignLibModDefFile flib
1049 gbuildModDefFiles
(GReplFLib _ flib
) = foreignLibModDefFile flib
1051 -- | "Main" module name when overridden by @ghc-options: -main-is ...@
1052 -- or 'Nothing' if no @-main-is@ flag could be found.
1054 -- In case of 'Nothing', 'Distribution.ModuleName.main' can be assumed.
1055 exeMainModuleName
:: Executable
-> Maybe ModuleName
1056 exeMainModuleName Executable
{buildInfo
= bnfo
} =
1057 -- GHC honors the last occurrence of a module name updated via -main-is
1059 -- Moreover, -main-is when parsed left-to-right can update either
1060 -- the "Main" module name, or the "main" function name, or both,
1061 -- see also 'decodeMainIsArg'.
1062 msum $ reverse $ map decodeMainIsArg
$ findIsMainArgs ghcopts
1064 ghcopts
= hcOptions GHC bnfo
1066 findIsMainArgs
[] = []
1067 findIsMainArgs
("-main-is" : arg
: rest
) = arg
: findIsMainArgs rest
1068 findIsMainArgs
(_
: rest
) = findIsMainArgs rest
1070 -- | Decode argument to '-main-is'
1072 -- Returns 'Nothing' if argument set only the function name.
1074 -- This code has been stolen/refactored from GHC's DynFlags.setMainIs
1075 -- function. The logic here is deliberately imperfect as it is
1076 -- intended to be bug-compatible with GHC's parser. See discussion in
1077 -- https://github.com/haskell/cabal/pull/4539#discussion_r118981753.
1078 decodeMainIsArg
:: String -> Maybe ModuleName
1080 | headOf main_fn
isLower =
1081 -- The arg looked like "Foo.Bar.baz"
1082 Just
(ModuleName
.fromString main_mod
)
1083 | headOf arg
isUpper -- The arg looked like "Foo" or "Foo.Bar"
1085 Just
(ModuleName
.fromString arg
)
1086 |
otherwise -- The arg looked like "baz"
1090 headOf
:: String -> (Char -> Bool) -> Bool
1091 headOf str
pred' = any pred' (safeHead str
)
1093 (main_mod
, main_fn
) = splitLongestPrefix arg
(== '.')
1095 splitLongestPrefix
:: String -> (Char -> Bool) -> (String, String)
1096 splitLongestPrefix str
pred'
1097 |
null r_pre
= (str
, [])
1098 |
otherwise = (reverse (safeTail r_pre
), reverse r_suf
)
1100 -- 'safeTail' drops the char satisfying 'pred'
1101 (r_suf
, r_pre
) = break pred' (reverse str
)
1103 -- | A collection of:
1105 -- * C++ input files
1106 -- * GHC input files
1107 -- * GHC input modules
1109 -- Used to correctly build and link sources.
1110 data BuildSources
= BuildSources
1111 { cSourcesFiles
:: [FilePath]
1112 , cxxSourceFiles
:: [FilePath]
1113 , inputSourceFiles
:: [FilePath]
1114 , inputSourceModules
:: [ModuleName
]
1117 -- | Locate and return the 'BuildSources' required to build and link.
1125 gbuildSources verbosity pkgId specVer tmpDir bm
=
1127 GBuildExe exe
-> exeSources exe
1128 GReplExe _ exe
-> exeSources exe
1129 GBuildFLib flib
-> return $ flibSources flib
1130 GReplFLib _ flib
-> return $ flibSources flib
1132 exeSources
:: Executable
-> IO BuildSources
1133 exeSources exe
@Executable
{buildInfo
= bnfo
, modulePath
= modPath
} = do
1134 main
<- findFileEx verbosity
(tmpDir
: map getSymbolicPath
(hsSourceDirs bnfo
)) modPath
1135 let mainModName
= fromMaybe ModuleName
.main
$ exeMainModuleName exe
1136 otherModNames
= exeModules exe
1138 -- Scripts have fakePackageId and are always Haskell but can have any extension.
1139 if isHaskell main || pkgId
== fakePackageId
1141 if specVer
< CabalSpecV2_0
&& (mainModName `
elem` otherModNames
)
1143 -- The cabal manual clearly states that `other-modules` is
1144 -- intended for non-main modules. However, there's at least one
1145 -- important package on Hackage (happy-1.19.5) which
1146 -- violates this. We workaround this here so that we don't
1147 -- invoke GHC with e.g. 'ghc --make Main src/Main.hs' which
1148 -- would result in GHC complaining about duplicate Main
1151 -- Finally, we only enable this workaround for
1152 -- specVersion < 2, as 'cabal-version:>=2.0' cabal files
1153 -- have no excuse anymore to keep doing it wrong... ;-)
1155 "Enabling workaround for Main module '"
1156 ++ prettyShow mainModName
1157 ++ "' listed in 'other-modules' illegally!"
1161 { cSourcesFiles
= cSources bnfo
1162 , cxxSourceFiles
= cxxSources bnfo
1163 , inputSourceFiles
= [main
]
1164 , inputSourceModules
= filter (/= mainModName
) $ exeModules exe
1169 { cSourcesFiles
= cSources bnfo
1170 , cxxSourceFiles
= cxxSources bnfo
1171 , inputSourceFiles
= [main
]
1172 , inputSourceModules
= exeModules exe
1176 | isCxx main
= (cSources bnfo
, main
: cxxSources bnfo
)
1177 -- if main is not a Haskell source
1178 -- and main is not a C++ source
1179 -- then we assume that it is a C source
1180 |
otherwise = (main
: cSources bnfo
, cxxSources bnfo
)
1183 { cSourcesFiles
= csf
1184 , cxxSourceFiles
= cxxsf
1185 , inputSourceFiles
= []
1186 , inputSourceModules
= exeModules exe
1189 flibSources
:: ForeignLib
-> BuildSources
1190 flibSources flib
@ForeignLib
{foreignLibBuildInfo
= bnfo
} =
1192 { cSourcesFiles
= cSources bnfo
1193 , cxxSourceFiles
= cxxSources bnfo
1194 , inputSourceFiles
= []
1195 , inputSourceModules
= foreignLibModules flib
1198 isCxx
:: FilePath -> Bool
1199 isCxx fp
= elem (takeExtension fp
) [".cpp", ".cxx", ".c++"]
1201 -- | FilePath has a Haskell extension: .hs or .lhs
1202 isHaskell
:: FilePath -> Bool
1203 isHaskell fp
= elem (takeExtension fp
) [".hs", ".lhs"]
1205 -- | Generic build function. See comment for 'GBuildMode'.
1209 -> PackageDescription
1212 -> ComponentLocalBuildInfo
1214 gbuild verbosity numJobs pkg_descr lbi bm clbi
= do
1215 (ghcjsProg
, _
) <- requireProgram verbosity ghcjsProgram
(withPrograms lbi
)
1216 let replFlags
= case bm
of
1217 GReplExe flags _
-> flags
1218 GReplFLib flags _
-> flags
1219 GBuildExe
{} -> mempty
1220 GBuildFLib
{} -> mempty
1222 platform
= hostPlatform lbi
1223 implInfo
= getImplInfo comp
1224 runGhcProg
= runGHC verbosity ghcjsProg comp platform
1226 let (bnfo
, threaded
) = case bm
of
1227 GBuildFLib _
-> popThreadedFlag
(gbuildInfo bm
)
1228 _
-> (gbuildInfo bm
, False)
1230 -- the name that GHC really uses (e.g., with .exe on Windows for executables)
1231 let targetName
= gbuildTargetName lbi bm
1232 let targetDir
= buildDir lbi
</> (gbuildName bm
)
1233 let tmpDir
= targetDir
</> (gbuildName bm
++ "-tmp")
1234 createDirectoryIfMissingVerbose verbosity
True targetDir
1235 createDirectoryIfMissingVerbose verbosity
True tmpDir
1237 -- TODO: do we need to put hs-boot files into place for mutually recursive
1238 -- modules? FIX: what about exeName.hi-boot?
1240 -- Determine if program coverage should be enabled and if so, what
1241 -- '-hpcdir' should be.
1242 let isCoverageEnabled
= exeCoverage lbi
1243 distPref
= fromFlag
$ configDistPref
$ configFlags lbi
1245 | gbuildIsRepl bm
= mempty
-- HPC is not supported in ghci
1246 | isCoverageEnabled
= toFlag
$ Hpc
.mixDir distPref way
(gbuildName bm
)
1247 |
otherwise = mempty
1249 rpaths
<- getRPaths lbi clbi
1250 buildSources
<- gbuildSources verbosity
(package pkg_descr
) (specVersion pkg_descr
) tmpDir bm
1252 let cSrcs
= cSourcesFiles buildSources
1253 cxxSrcs
= cxxSourceFiles buildSources
1254 inputFiles
= inputSourceFiles buildSources
1255 inputModules
= inputSourceModules buildSources
1256 isGhcDynamic
= isDynamic comp
1257 dynamicTooSupported
= supportsDynamicToo comp
1258 cObjs
= map (`replaceExtension` objExtension
) cSrcs
1259 cxxObjs
= map (`replaceExtension` objExtension
) cxxSrcs
1260 needDynamic
= gbuildNeedDynamic lbi bm
1261 needProfiling
= withProfExe lbi
1263 -- build executables
1264 buildRunner
= case clbi
of
1265 LibComponentLocalBuildInfo
{} -> False
1266 FLibComponentLocalBuildInfo
{} -> False
1267 ExeComponentLocalBuildInfo
{} -> True
1268 TestComponentLocalBuildInfo
{} -> True
1269 BenchComponentLocalBuildInfo
{} -> True
1271 (componentGhcOptions verbosity lbi bnfo clbi tmpDir
)
1273 { ghcOptMode
= toFlag GhcModeMake
1274 , ghcOptInputFiles
=
1276 if package pkg_descr
== fakePackageId
1277 then filter isHaskell inputFiles
1279 , ghcOptInputScripts
=
1281 if package pkg_descr
== fakePackageId
1282 then filter (not . isHaskell
) inputFiles
1284 , ghcOptInputModules
= toNubListR inputModules
1285 , -- for all executable components (exe/test/bench),
1286 -- GHCJS must be passed the "-build-runner" option
1289 then ["-build-runner"]
1295 { ghcOptDynLinkMode
= toFlag GhcStaticOnly
1296 , ghcOptHPCDir
= hpcdir Hpc
.Vanilla
1301 { ghcOptProfilingMode
= toFlag
True
1302 , ghcOptProfilingAuto
=
1303 Internal
.profDetailLevelFlag
1305 (withProfExeDetail lbi
)
1306 , ghcOptHiSuffix
= toFlag
"p_hi"
1307 , ghcOptObjSuffix
= toFlag
"p_o"
1308 , ghcOptExtra
= hcProfOptions GHC bnfo
1309 , ghcOptHPCDir
= hpcdir Hpc
.Prof
1314 { ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1315 , -- TODO: Does it hurt to set -fPIC for executables?
1316 ghcOptFPic
= toFlag
True
1317 , ghcOptHiSuffix
= toFlag
"dyn_hi"
1318 , ghcOptObjSuffix
= toFlag
"dyn_o"
1319 , ghcOptExtra
= hcSharedOptions GHC bnfo
1320 , ghcOptHPCDir
= hpcdir Hpc
.Dyn
1325 { ghcOptDynLinkMode
= toFlag GhcStaticAndDynamic
1326 , ghcOptDynHiSuffix
= toFlag
"dyn_hi"
1327 , ghcOptDynObjSuffix
= toFlag
"dyn_o"
1328 , ghcOptHPCDir
= hpcdir Hpc
.Dyn
1332 { ghcOptLinkOptions
= PD
.ldOptions bnfo
1333 , ghcOptLinkLibs
= extraLibs bnfo
1334 , ghcOptLinkLibPath
= toNubListR
$ extraLibDirs bnfo
1335 , ghcOptLinkFrameworks
=
1338 , ghcOptLinkFrameworkDirs
=
1340 PD
.extraFrameworkDirs bnfo
1341 , ghcOptInputFiles
=
1343 [tmpDir
</> x | x
<- cObjs
++ cxxObjs
]
1347 { ghcOptRPaths
= rpaths
1352 Internal
.filterGhciFlags
1353 (ghcOptExtra baseOpts
)
1356 -- For a normal compile we do separate invocations of ghc for
1357 -- compiling as for linking. But for repl we have to do just
1358 -- the one invocation, so that one has to include all the
1359 -- linker stuff too, like -l flags and any .o files from C
1361 `mappend` linkerOpts
1363 { ghcOptMode
= toFlag GhcModeInteractive
1364 , ghcOptOptimisation
= toFlag GhcNoOptimisation
1367 | needProfiling
= profOpts
1368 | needDynamic
= dynOpts
1369 |
otherwise = staticOpts
1371 | useDynToo
= dynTooOpts
1372 |
otherwise = commonOpts
1373 withStaticExe
= not needProfiling
&& not needDynamic
1375 -- For building exe's that use TH with -prof or -dynamic we actually have
1376 -- to build twice, once without -prof/-dynamic and then again with
1377 -- -prof/-dynamic. This is because the code that TH needs to run at
1378 -- compile time needs to be the vanilla ABI so it can be loaded up and run
1380 -- With dynamic-by-default GHC the TH object files loaded at compile-time
1381 -- need to be .dyn_o instead of .o.
1382 doingTH
= usesTemplateHaskellOrQQ bnfo
1383 -- Should we use -dynamic-too instead of compiling twice?
1389 && null (hcSharedOptions GHC bnfo
)
1391 | isGhcDynamic
= dynOpts
1392 |
otherwise = staticOpts
1394 | gbuildIsRepl bm
= False
1396 | isGhcDynamic
= doingTH
&& (needProfiling || withStaticExe
)
1397 |
otherwise = doingTH
&& (needProfiling || needDynamic
)
1399 -- Build static/dynamic object files for TH, if needed.
1403 { ghcOptNoLink
= toFlag
True
1404 , ghcOptNumJobs
= numJobs
1407 -- Do not try to build anything if there are no input files.
1408 -- This can happen if the cabal file ends up with only cSrcs
1409 -- but no Haskell modules.
1411 ( (null inputFiles
&& null inputModules
)
1416 { ghcOptNoLink
= toFlag
True
1417 , ghcOptNumJobs
= numJobs
1420 -- build any C++ sources
1421 unless (null cxxSrcs
) $ do
1422 info verbosity
"Building C++ Sources..."
1426 Internal
.componentCxxGhcOptions
1436 then -- Dynamic GHC requires C++ sources to be built
1437 -- with -fPIC for REPL to work. See #2207.
1438 baseCxxOpts
{ghcOptFPic
= toFlag
True}
1443 { ghcOptProfilingMode
= toFlag
True
1448 { ghcOptFPic
= toFlag
True
1449 , ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1452 | needProfiling
= profCxxOpts
1453 | needDynamic
= sharedCxxOpts
1454 |
otherwise = vanillaCxxOpts
1455 -- TODO: Placing all Haskell, C, & C++ objects in a single directory
1456 -- Has the potential for file collisions. In general we would
1457 -- consider this a user error. However, we should strive to
1458 -- add a warning if this occurs.
1459 odir
= fromFlag
(ghcOptObjDir opts
)
1460 createDirectoryIfMissingVerbose verbosity
True odir
1461 needsRecomp
<- checkNeedsRecompilation filename opts
1464 | filename
<- cxxSrcs
1467 -- build any C sources
1468 unless (null cSrcs
) $ do
1469 info verbosity
"Building C Sources..."
1473 Internal
.componentCcGhcOptions
1483 then -- Dynamic GHC requires C sources to be built
1484 -- with -fPIC for REPL to work. See #2207.
1485 baseCcOpts
{ghcOptFPic
= toFlag
True}
1490 { ghcOptProfilingMode
= toFlag
True
1495 { ghcOptFPic
= toFlag
True
1496 , ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1499 | needProfiling
= profCcOpts
1500 | needDynamic
= sharedCcOpts
1501 |
otherwise = vanillaCcOpts
1502 odir
= fromFlag
(ghcOptObjDir opts
)
1503 createDirectoryIfMissingVerbose verbosity
True odir
1504 needsRecomp
<- checkNeedsRecompilation filename opts
1510 -- TODO: problem here is we need the .c files built first, so we can load them
1511 -- with ghci, but .c files can depend on .h files generated by ghc by ffi
1514 GReplExe _ _
-> runGhcProg replOpts
1515 GReplFLib _ _
-> runGhcProg replOpts
1519 `mappend` linkerOpts
1521 { ghcOptLinkNoHsMain
= toFlag
(null inputFiles
)
1523 `mappend`
(if withDynExe lbi
then dynLinkerOpts
else mempty
)
1525 info verbosity
"Linking..."
1526 -- Work around old GHCs not relinking in this
1527 -- situation, see #3294
1528 let target
= targetDir
</> targetName
1529 when (compilerVersion comp
< mkVersion
[7, 7]) $ do
1530 e
<- doesFileExist target
1531 when e
(removeFile target
)
1532 runGhcProg linkOpts
{ghcOptOutputFile
= toFlag target
}
1533 GBuildFLib flib
-> do
1534 let rtsInfo
= extractRtsInfo lbi
1539 then dynRtsThreadedLib
(rtsDynamicInfo rtsInfo
)
1540 else dynRtsVanillaLib
(rtsDynamicInfo rtsInfo
)
1543 then statRtsThreadedLib
(rtsStaticInfo rtsInfo
)
1544 else statRtsVanillaLib
(rtsStaticInfo rtsInfo
)
1546 linkOpts
= case foreignLibType flib
of
1547 ForeignLibNativeShared
->
1549 `mappend` linkerOpts
1550 `mappend` dynLinkerOpts
1552 { ghcOptLinkNoHsMain
= toFlag
True
1553 , ghcOptShared
= toFlag
True
1554 , ghcOptLinkLibs
= rtsOptLinkLibs
1555 , ghcOptLinkLibPath
= toNubListR
$ rtsLibPaths rtsInfo
1556 , ghcOptFPic
= toFlag
True
1557 , ghcOptLinkModDefFiles
= toNubListR
$ gbuildModDefFiles bm
1559 ForeignLibNativeStatic
->
1560 -- this should be caught by buildFLib
1561 -- (and if we do implement this, we probably don't even want to call
1562 -- ghc here, but rather Ar.createArLibArchive or something)
1563 cabalBug
"static libraries not yet implemented"
1564 ForeignLibTypeUnknown
->
1565 cabalBug
"unknown foreign lib type"
1566 -- We build under a (potentially) different filename to set a
1567 -- soname on supported platforms. See also the note for
1569 info verbosity
"Linking..."
1570 let buildName
= flibBuildName lbi flib
1571 runGhcProg linkOpts
{ghcOptOutputFile
= toFlag
(targetDir
</> buildName
)}
1572 renameFile (targetDir
</> buildName
) (targetDir
</> targetName
)
1574 data DynamicRtsInfo
= DynamicRtsInfo
1575 { dynRtsVanillaLib
:: FilePath
1576 , dynRtsThreadedLib
:: FilePath
1577 , dynRtsDebugLib
:: FilePath
1578 , dynRtsEventlogLib
:: FilePath
1579 , dynRtsThreadedDebugLib
:: FilePath
1580 , dynRtsThreadedEventlogLib
:: FilePath
1583 data StaticRtsInfo
= StaticRtsInfo
1584 { statRtsVanillaLib
:: FilePath
1585 , statRtsThreadedLib
:: FilePath
1586 , statRtsDebugLib
:: FilePath
1587 , statRtsEventlogLib
:: FilePath
1588 , statRtsThreadedDebugLib
:: FilePath
1589 , statRtsThreadedEventlogLib
:: FilePath
1590 , statRtsProfilingLib
:: FilePath
1591 , statRtsThreadedProfilingLib
:: FilePath
1594 data RtsInfo
= RtsInfo
1595 { rtsDynamicInfo
:: DynamicRtsInfo
1596 , rtsStaticInfo
:: StaticRtsInfo
1597 , rtsLibPaths
:: [FilePath]
1600 -- | Extract (and compute) information about the RTS library
1602 -- TODO: This hardcodes the name as @HSrts-ghc<version>@. I don't know if we can
1603 -- find this information somewhere. We can lookup the 'hsLibraries' field of
1604 -- 'InstalledPackageInfo' but it will tell us @["HSrts", "Cffi"]@, which
1605 -- doesn't really help.
1606 extractRtsInfo
:: LocalBuildInfo
-> RtsInfo
1607 extractRtsInfo lbi
=
1608 case PackageIndex
.lookupPackageName
(installedPkgs lbi
) (mkPackageName
"rts") of
1609 [(_
, [rts
])] -> aux rts
1610 _otherwise
-> error "No (or multiple) ghc rts package is registered"
1612 aux
:: InstalledPackageInfo
-> RtsInfo
1617 { dynRtsVanillaLib
= withGhcVersion
"HSrts"
1618 , dynRtsThreadedLib
= withGhcVersion
"HSrts_thr"
1619 , dynRtsDebugLib
= withGhcVersion
"HSrts_debug"
1620 , dynRtsEventlogLib
= withGhcVersion
"HSrts_l"
1621 , dynRtsThreadedDebugLib
= withGhcVersion
"HSrts_thr_debug"
1622 , dynRtsThreadedEventlogLib
= withGhcVersion
"HSrts_thr_l"
1626 { statRtsVanillaLib
= "HSrts"
1627 , statRtsThreadedLib
= "HSrts_thr"
1628 , statRtsDebugLib
= "HSrts_debug"
1629 , statRtsEventlogLib
= "HSrts_l"
1630 , statRtsThreadedDebugLib
= "HSrts_thr_debug"
1631 , statRtsThreadedEventlogLib
= "HSrts_thr_l"
1632 , statRtsProfilingLib
= "HSrts_p"
1633 , statRtsThreadedProfilingLib
= "HSrts_thr_p"
1635 , rtsLibPaths
= InstalledPackageInfo
.libraryDirs rts
1637 withGhcVersion
= (++ ("-ghc" ++ prettyShow
(compilerVersion
(compiler lbi
))))
1639 -- | Returns True if the modification date of the given source file is newer than
1640 -- the object file we last compiled for it, or if no object file exists yet.
1641 checkNeedsRecompilation
:: FilePath -> GhcOptions
-> IO Bool
1642 checkNeedsRecompilation filename opts
= filename `moreRecentFile` oname
1644 oname
= getObjectFileName filename opts
1646 -- | Finds the object file name of the given source file
1647 getObjectFileName
:: FilePath -> GhcOptions
-> FilePath
1648 getObjectFileName filename opts
= oname
1650 odir
= fromFlag
(ghcOptObjDir opts
)
1651 oext
= fromFlagOrDefault
"o" (ghcOptObjSuffix opts
)
1652 oname
= odir
</> replaceExtension filename oext
1654 -- | Calculate the RPATHs for the component we are building.
1656 -- Calculates relative RPATHs when 'relocatable' is set.
1659 -> ComponentLocalBuildInfo
1660 -- ^ Component we are building
1661 -> IO (NubListR
FilePath)
1662 getRPaths lbi clbi | supportRPaths hostOS
= do
1663 libraryPaths
<- depLibraryPaths
False (relocatable lbi
) lbi clbi
1664 let hostPref
= case hostOS
of
1665 OSX
-> "@loader_path"
1667 relPath p
= if isRelative p
then hostPref
</> p
else p
1668 rpaths
= toNubListR
(map relPath libraryPaths
)
1671 (Platform _ hostOS
) = hostPlatform lbi
1672 compid
= compilerId
. compiler
$ lbi
1674 -- The list of RPath-supported operating systems below reflects the
1675 -- platforms on which Cabal's RPATH handling is tested. It does _NOT_
1676 -- reflect whether the OS supports RPATH.
1678 -- E.g. when this comment was written, the *BSD operating systems were
1679 -- untested with regards to Cabal RPATH handling, and were hence set to
1680 -- 'False', while those operating systems themselves do support RPATH.
1681 supportRPaths Linux
= True
1682 supportRPaths Windows
= False
1683 supportRPaths OSX
= True
1684 supportRPaths FreeBSD
=
1686 CompilerId GHC ver | ver
>= mkVersion
[7, 10, 2] -> True
1688 supportRPaths OpenBSD
= False
1689 supportRPaths NetBSD
= False
1690 supportRPaths DragonFly
= False
1691 supportRPaths Solaris
= False
1692 supportRPaths AIX
= False
1693 supportRPaths HPUX
= False
1694 supportRPaths IRIX
= False
1695 supportRPaths HaLVM
= False
1696 supportRPaths IOS
= False
1697 supportRPaths Android
= False
1698 supportRPaths Ghcjs
= False
1699 supportRPaths Wasi
= False
1700 supportRPaths Hurd
= False
1701 supportRPaths Haiku
= False
1702 supportRPaths
(OtherOS _
) = False
1703 -- Do _not_ add a default case so that we get a warning here when a new OS
1706 getRPaths _ _
= return mempty
1708 -- | Remove the "-threaded" flag when building a foreign library, as it has no
1709 -- effect when used with "-shared". Returns the updated 'BuildInfo', along
1710 -- with whether or not the flag was present, so we can use it to link against
1711 -- the appropriate RTS on our own.
1712 popThreadedFlag
:: BuildInfo
-> (BuildInfo
, Bool)
1713 popThreadedFlag bi
=
1714 ( bi
{options
= filterHcOptions
(/= "-threaded") (options bi
)}
1715 , hasThreaded
(options bi
)
1720 -> PerCompilerFlavor
[String]
1721 -> PerCompilerFlavor
[String]
1722 filterHcOptions p
(PerCompilerFlavor ghc ghcjs
) =
1723 PerCompilerFlavor
(filter p ghc
) ghcjs
1725 hasThreaded
:: PerCompilerFlavor
[String] -> Bool
1726 hasThreaded
(PerCompilerFlavor ghc _
) = elem "-threaded" ghc
1728 -- | Extracts a String representing a hash of the ABI of a built
1729 -- library. It can fail if the library has not yet been built.
1732 -> PackageDescription
1735 -> ComponentLocalBuildInfo
1737 libAbiHash verbosity _pkg_descr lbi lib clbi
= do
1739 libBi
= libBuildInfo lib
1741 platform
= hostPlatform lbi
1743 (componentGhcOptions verbosity lbi libBi clbi
(componentBuildDir lbi clbi
))
1745 { ghcOptMode
= toFlag GhcModeAbiHash
1746 , ghcOptInputModules
= toNubListR
$ exposedModules lib
1749 -- Package DBs unnecessary, and break ghc-cabal. See #3633
1750 -- BUT, put at least the global database so that 7.4 doesn't
1753 { ghcOptPackageDBs
= [GlobalPackageDB
]
1754 , ghcOptPackages
= mempty
1759 { ghcOptDynLinkMode
= toFlag GhcDynamicOnly
1760 , ghcOptFPic
= toFlag
True
1761 , ghcOptHiSuffix
= toFlag
"js_dyn_hi"
1762 , ghcOptObjSuffix
= toFlag
"js_dyn_o"
1763 , ghcOptExtra
= hcSharedOptions GHC libBi
1768 { ghcOptProfilingMode
= toFlag
True
1769 , ghcOptProfilingAuto
=
1770 Internal
.profDetailLevelFlag
1772 (withProfLibDetail lbi
)
1773 , ghcOptHiSuffix
= toFlag
"js_p_hi"
1774 , ghcOptObjSuffix
= toFlag
"js_p_o"
1775 , ghcOptExtra
= hcProfOptions GHC libBi
1778 | withVanillaLib lbi
= vanillaArgs
1779 | withSharedLib lbi
= sharedArgs
1780 | withProfLib lbi
= profArgs
1781 |
otherwise = error "libAbiHash: Can't find an enabled library way"
1783 (ghcjsProg
, _
) <- requireProgram verbosity ghcjsProgram
(withPrograms lbi
)
1785 getProgramInvocationOutput
1787 (ghcInvocation ghcjsProg comp platform ghcArgs
)
1788 return (takeWhile (not . isSpace) hash
)
1794 -> ComponentLocalBuildInfo
1797 componentGhcOptions verbosity lbi bi clbi odir
=
1798 let opts
= Internal
.componentGhcOptions verbosity implInfo lbi bi clbi odir
1800 implInfo
= getImplInfo comp
1802 { ghcOptExtra
= ghcOptExtra opts `mappend` hcOptions GHCJS bi
1805 componentCcGhcOptions
1809 -> ComponentLocalBuildInfo
1813 componentCcGhcOptions verbosity lbi
=
1814 Internal
.componentCcGhcOptions verbosity implInfo lbi
1817 implInfo
= getImplInfo comp
1819 -- -----------------------------------------------------------------------------
1822 -- | Install executables for GHCJS.
1827 -- ^ Where to copy the files to
1830 -> (FilePath, FilePath)
1831 -- ^ Executable (prefix,suffix)
1832 -> PackageDescription
1840 (progprefix
, progsuffix
)
1843 createDirectoryIfMissingVerbose verbosity
True binDir
1844 let exeName
' = unUnqualComponentName
$ exeName exe
1845 exeFileName
= exeName
'
1846 fixedExeBaseName
= progprefix
++ exeName
' ++ progsuffix
1847 installBinary dest
= do
1848 runDbProgram verbosity ghcjsProgram
(withPrograms lbi
) $
1849 [ "--install-executable"
1850 , buildPref
</> exeName
' </> exeFileName
1854 ++ case (stripExes lbi
, lookupProgram stripProgram
$ withPrograms lbi
) of
1855 (True, Just strip
) -> ["-strip-program", programPath strip
]
1857 installBinary
(binDir
</> fixedExeBaseName
)
1859 -- | Install foreign library for GHC.
1864 -- ^ install location
1867 -> PackageDescription
1870 installFLib verbosity lbi targetDir builtDir _pkg flib
=
1872 (foreignLibIsShared flib
)
1875 (flibTargetName lbi flib
)
1877 install _isShared srcDir dstDir name
= do
1878 let src
= srcDir
</> name
1879 dst
= dstDir
</> name
1880 createDirectoryIfMissingVerbose verbosity
True targetDir
1881 installOrdinaryFile verbosity src dst
1883 -- | Install for ghc, .hi, .a and, if --with-ghci given, .o
1888 -- ^ install location
1890 -- ^ install location for dynamic libraries
1893 -> PackageDescription
1895 -> ComponentLocalBuildInfo
1897 installLib verbosity lbi targetDir dynlibTargetDir _builtDir _pkg lib clbi
= do
1898 whenVanilla
$ copyModuleFiles
"js_hi"
1899 whenProf
$ copyModuleFiles
"js_p_hi"
1900 whenShared
$ copyModuleFiles
"js_dyn_hi"
1902 -- whenVanilla $ installOrdinary builtDir targetDir $ toJSLibName vanillaLibName
1903 -- whenProf $ installOrdinary builtDir targetDir $ toJSLibName profileLibName
1904 -- whenShared $ installShared builtDir dynlibTargetDir $ toJSLibName sharedLibName
1905 -- fixme do these make the correct lib names?
1909 [ installOrdinary builtDir
' targetDir
(toJSLibName
$ mkGenericStaticLibName
(l
++ f
))
1910 | l
<- getHSLibraryName
(componentUnitId clbi
) : (extraBundledLibs
(libBuildInfo lib
))
1911 , f
<- "" : extraLibFlavours
(libBuildInfo lib
)
1913 -- whenGHCi $ installOrdinary builtDir targetDir (toJSLibName ghciLibName)
1915 installOrdinary builtDir
' targetDir
(toJSLibName profileLibName
)
1916 -- whenGHCi $ installOrdinary builtDir targetDir (toJSLibName ghciProfLibName)
1922 (toJSLibName
$ mkGenericSharedLibName platform compiler_id
(l
++ f
))
1923 | l
<- getHSLibraryName uid
: extraBundledLibs
(libBuildInfo lib
)
1924 , f
<- "" : extraDynLibFlavours
(libBuildInfo lib
)
1927 builtDir
' = componentBuildDir lbi clbi
1929 install isShared isJS srcDir dstDir name
= do
1930 let src
= srcDir
</> name
1931 dst
= dstDir
</> name
1932 createDirectoryIfMissingVerbose verbosity
True dstDir
1935 then installExecutableFile verbosity src dst
1936 else installOrdinaryFile verbosity src dst
1938 when (stripLibs lbi
&& not isJS
) $
1945 installOrdinary
= install
False True
1946 installShared
= install
True True
1948 copyModuleFiles ext
=
1949 findModuleFilesEx verbosity
[builtDir
'] [ext
] (allLibModules lib clbi
)
1950 >>= installOrdinaryFiles verbosity targetDir
1952 compiler_id
= compilerId
(compiler lbi
)
1953 platform
= hostPlatform lbi
1954 uid
= componentUnitId clbi
1955 -- vanillaLibName = mkLibName uid
1956 profileLibName
= mkProfLibName uid
1957 -- sharedLibName = (mkSharedLibName (hostPlatform lbi) compiler_id) uid
1961 null (allLibModules lib clbi
)
1962 && null (cSources
(libBuildInfo lib
))
1963 && null (cxxSources
(libBuildInfo lib
))
1964 && null (jsSources
(libBuildInfo lib
))
1965 has_code
= not (componentIsIndefinite clbi
)
1966 whenHasCode
= when has_code
1967 whenVanilla
= when (hasLib
&& withVanillaLib lbi
)
1968 whenProf
= when (hasLib
&& withProfLib lbi
&& has_code
)
1969 -- whenGHCi = when (hasLib && withGHCiLib lbi && has_code)
1970 whenShared
= when (hasLib
&& withSharedLib lbi
&& has_code
)
1972 adjustExts
:: String -> String -> GhcOptions
-> GhcOptions
1973 adjustExts hiSuf objSuf opts
=
1976 { ghcOptHiSuffix
= toFlag hiSuf
1977 , ghcOptObjSuffix
= toFlag objSuf
1980 isDynamic
:: Compiler
-> Bool
1981 isDynamic
= Internal
.ghcLookupProperty
"GHC Dynamic"
1983 supportsDynamicToo
:: Compiler
-> Bool
1984 supportsDynamicToo
= Internal
.ghcLookupProperty
"Support dynamic-too"
1986 withExt
:: FilePath -> String -> FilePath
1987 withExt fp ext
= fp
<.> if takeExtension fp
/= ('.' : ext
) then ext
else ""
1989 findGhcjsGhcVersion
:: Verbosity
-> FilePath -> IO (Maybe Version
)
1990 findGhcjsGhcVersion verbosity pgm
=
1991 findProgramVersion
"--numeric-ghc-version" id verbosity pgm
1993 findGhcjsPkgGhcjsVersion
:: Verbosity
-> FilePath -> IO (Maybe Version
)
1994 findGhcjsPkgGhcjsVersion verbosity pgm
=
1995 findProgramVersion
"--numeric-ghcjs-version" id verbosity pgm
1997 -- -----------------------------------------------------------------------------
2000 hcPkgInfo
:: ProgramDb
-> HcPkg
.HcPkgInfo
2003 { HcPkg
.hcPkgProgram
= ghcjsPkgProg
2004 , HcPkg
.noPkgDbStack
= False
2005 , HcPkg
.noVerboseFlag
= False
2006 , HcPkg
.flagPackageConf
= False
2007 , HcPkg
.supportsDirDbs
= True
2008 , HcPkg
.requiresDirDbs
= ver
>= v7_10
2009 , HcPkg
.nativeMultiInstance
= ver
>= v7_10
2010 , HcPkg
.recacheMultiInstance
= True
2011 , HcPkg
.suppressFilesCheck
= True
2014 v7_10
= mkVersion
[7, 10]
2015 ghcjsPkgProg
= fromMaybe (error "GHCJS.hcPkgInfo no ghcjs program") $ lookupProgram ghcjsPkgProgram progdb
2016 ver
= fromMaybe (error "GHCJS.hcPkgInfo no ghcjs version") $ programVersion ghcjsPkgProg
2022 -> InstalledPackageInfo
2023 -> HcPkg
.RegisterOptions
2025 registerPackage verbosity progdb packageDbs installedPkgInfo registerOptions
=
2033 pkgRoot
:: Verbosity
-> LocalBuildInfo
-> PackageDB
-> IO FilePath
2034 pkgRoot verbosity lbi
= pkgRoot
'
2036 pkgRoot
' GlobalPackageDB
=
2037 let ghcjsProg
= fromMaybe (error "GHCJS.pkgRoot: no ghcjs program") $ lookupProgram ghcjsProgram
(withPrograms lbi
)
2038 in fmap takeDirectory
(getGlobalPackageDB verbosity ghcjsProg
)
2039 pkgRoot
' UserPackageDB
= do
2040 appDir
<- getAppUserDataDirectory
"ghcjs"
2041 -- fixme correct this version
2042 let ver
= compilerVersion
(compiler lbi
)
2049 rootDir
= appDir
</> subdir
2050 -- We must create the root directory for the user package database if it
2051 -- does not yet exists. Otherwise '${pkgroot}' will resolve to a
2052 -- directory at the time of 'ghc-pkg register', and registration will
2054 createDirectoryIfMissing
True rootDir
2056 pkgRoot
' (SpecificPackageDB fp
) = return (takeDirectory fp
)
2058 -- | Get the JavaScript file name and command and arguments to run a
2059 -- program compiled by GHCJS
2060 -- the exe should be the base program name without exe extension
2064 -> (FilePath, FilePath, [String])
2067 , programPath ghcjsProg
2068 , programDefaultArgs ghcjsProg
++ programOverrideArgs ghcjsProg
++ ["--run"]
2071 script
= exe
<.> "jsexe" </> "all" <.> "js"
2072 ghcjsProg
= fromMaybe (error "GHCJS.runCmd: no ghcjs program") $ lookupProgram ghcjsProgram progdb