{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
module Distribution.Simple.GHCJS
( getGhcInfo
, configure
, getInstalledPackages
, getInstalledPackagesMonitorFiles
, getPackageDBContents
, buildLib
, buildFLib
, buildExe
, replLib
, replFLib
, replExe
, startInterpreter
, installLib
, installFLib
, installExe
, libAbiHash
, hcPkgInfo
, registerPackage
, componentGhcOptions
, Internal.componentCcGhcOptions
, getLibDir
, isDynamic
, getGlobalPackageDB
, pkgRoot
, runCmd
, Internal.GhcEnvironmentFileEntry (..)
, Internal.simpleGhcEnvironmentFile
, Internal.renderGhcEnvironmentFile
, Internal.writeGhcEnvironmentFile
, Internal.ghcPlatformAndVersionString
, readGhcEnvironmentFile
, parseGhcEnvironmentFile
, ParseErrorExc (..)
, getImplInfo
, GhcImplInfo (..)
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Package
import Distribution.PackageDescription as PD
import Distribution.PackageDescription.Utils (cabalBug)
import Distribution.Pretty
import Distribution.Simple.BuildPaths
import Distribution.Simple.Compiler
import Distribution.Simple.Errors
import Distribution.Simple.Flag
import Distribution.Simple.GHC.EnvironmentParser
import Distribution.Simple.GHC.ImplInfo
import qualified Distribution.Simple.GHC.Internal as Internal
import qualified Distribution.Simple.Hpc as Hpc
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.PackageIndex (InstalledPackageIndex)
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PreProcess.Types
import Distribution.Simple.Program
import Distribution.Simple.Program.GHC
import qualified Distribution.Simple.Program.HcPkg as HcPkg
import qualified Distribution.Simple.Program.Strip as Strip
import Distribution.Simple.Setup.Common
import Distribution.Simple.Utils
import Distribution.System
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.PackageName.Magic
import Distribution.Types.ParStrat
import Distribution.Utils.NubList
import Distribution.Utils.Path
import Distribution.Verbosity (Verbosity)
import Distribution.Version
import Control.Arrow ((***))
import Control.Monad (msum)
import Data.Char (isLower)
import qualified Data.Map as Map
import System.Directory
( canonicalizePath
, createDirectoryIfMissing
, doesFileExist
, getAppUserDataDirectory
, removeFile
, renameFile
)
import System.FilePath
( isRelative
, replaceExtension
, takeDirectory
, takeExtension
)
import qualified System.Info
configure
:: Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramDb
-> IO (Compiler, Maybe Platform, ProgramDb)
configure :: Verbosity
-> Maybe FilePath
-> Maybe FilePath
-> ProgramDb
-> IO (Compiler, Maybe Platform, ProgramDb)
configure Verbosity
verbosity Maybe FilePath
hcPath Maybe FilePath
hcPkgPath ProgramDb
conf0 = do
(ghcjsProg, ghcjsVersion, progdb1) <-
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion
Verbosity
verbosity
Program
ghcjsProgram
(Version -> VersionRange
orLaterVersion ([Int] -> Version
mkVersion [Int
0, Int
1]))
(FilePath -> Maybe FilePath -> ProgramDb -> ProgramDb
userMaybeSpecifyPath FilePath
"ghcjs" Maybe FilePath
hcPath ProgramDb
conf0)
Just ghcjsGhcVersion <- findGhcjsGhcVersion verbosity (programPath ghcjsProg)
unless (ghcjsGhcVersion < mkVersion [8, 8]) $
warn verbosity $
"Unknown/unsupported 'ghc' version detected "
++ "(Cabal "
++ prettyShow cabalVersion
++ " supports 'ghc' version < 8.8): "
++ programPath ghcjsProg
++ " is based on GHC version "
++ prettyShow ghcjsGhcVersion
let implInfo = Version -> Version -> GhcImplInfo
ghcjsVersionImplInfo Version
ghcjsVersion Version
ghcjsGhcVersion
(ghcjsPkgProg, ghcjsPkgVersion, progdb2) <-
requireProgramVersion
verbosity
ghcjsPkgProgram
{ programFindLocation = guessGhcjsPkgFromGhcjsPath ghcjsProg
}
anyVersion
(userMaybeSpecifyPath "ghcjs-pkg" hcPkgPath progdb1)
Just ghcjsPkgGhcjsVersion <-
findGhcjsPkgGhcjsVersion
verbosity
(programPath ghcjsPkgProg)
when (ghcjsVersion /= ghcjsPkgGhcjsVersion) $
dieWithException verbosity $
VersionMismatchJS
(programPath ghcjsProg)
ghcjsVersion
(programPath ghcjsPkgProg)
ghcjsPkgGhcjsVersion
when (ghcjsGhcVersion /= ghcjsPkgVersion) $
dieWithException verbosity $
VersionMismatchGHCJS (programPath ghcjsProg) ghcjsGhcVersion (programPath ghcjsPkgProg) ghcjsPkgVersion
let hsc2hsProgram' =
Program
hsc2hsProgram
{ programFindLocation =
guessHsc2hsFromGhcjsPath ghcjsProg
}
haddockProgram' =
Program
haddockProgram
{ programFindLocation =
guessHaddockFromGhcjsPath ghcjsProg
}
hpcProgram' =
Program
hpcProgram
{ programFindLocation = guessHpcFromGhcjsPath ghcjsProg
}
progdb3 =
Program -> ProgramDb -> ProgramDb
addKnownProgram Program
haddockProgram' (ProgramDb -> ProgramDb) -> ProgramDb -> ProgramDb
forall a b. (a -> b) -> a -> b
$
Program -> ProgramDb -> ProgramDb
addKnownProgram Program
hsc2hsProgram' (ProgramDb -> ProgramDb) -> ProgramDb -> ProgramDb
forall a b. (a -> b) -> a -> b
$
Program -> ProgramDb -> ProgramDb
addKnownProgram Program
hpcProgram' (ProgramDb -> ProgramDb) -> ProgramDb -> ProgramDb
forall a b. (a -> b) -> a -> b
$
ProgramDb
progdb2
languages <- Internal.getLanguages verbosity implInfo ghcjsProg
extensions <- Internal.getExtensions verbosity implInfo ghcjsProg
ghcjsInfo <- Internal.getGhcInfo verbosity implInfo ghcjsProg
let ghcInfoMap = [(FilePath, FilePath)] -> Map FilePath FilePath
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(FilePath, FilePath)]
ghcjsInfo
let comp =
Compiler
{ compilerId :: CompilerId
compilerId = CompilerFlavor -> Version -> CompilerId
CompilerId CompilerFlavor
GHCJS Version
ghcjsVersion
, compilerAbiTag :: AbiTag
compilerAbiTag =
FilePath -> AbiTag
AbiTag (FilePath -> AbiTag) -> FilePath -> AbiTag
forall a b. (a -> b) -> a -> b
$
FilePath
"ghc" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"_" ((Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Int -> FilePath
forall a. Show a => a -> FilePath
show ([Int] -> [FilePath])
-> (Version -> [Int]) -> Version -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> [Int]
versionNumbers (Version -> [FilePath]) -> Version -> [FilePath]
forall a b. (a -> b) -> a -> b
$ Version
ghcjsGhcVersion)
, compilerCompat :: [CompilerId]
compilerCompat = [CompilerFlavor -> Version -> CompilerId
CompilerId CompilerFlavor
GHC Version
ghcjsGhcVersion]
, compilerLanguages :: [(Language, FilePath)]
compilerLanguages = [(Language, FilePath)]
languages
, compilerExtensions :: [(Extension, Maybe FilePath)]
compilerExtensions = [(Extension, Maybe FilePath)]
extensions
, compilerProperties :: Map FilePath FilePath
compilerProperties = Map FilePath FilePath
ghcInfoMap
}
compPlatform = [(FilePath, FilePath)] -> Maybe Platform
Internal.targetPlatform [(FilePath, FilePath)]
ghcjsInfo
return (comp, compPlatform, progdb3)
guessGhcjsPkgFromGhcjsPath
:: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessGhcjsPkgFromGhcjsPath :: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessGhcjsPkgFromGhcjsPath = Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath Program
ghcjsPkgProgram
guessHsc2hsFromGhcjsPath
:: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHsc2hsFromGhcjsPath :: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHsc2hsFromGhcjsPath = Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath Program
hsc2hsProgram
guessHaddockFromGhcjsPath
:: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHaddockFromGhcjsPath :: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHaddockFromGhcjsPath = Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath Program
haddockProgram
guessHpcFromGhcjsPath
:: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHpcFromGhcjsPath :: ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessHpcFromGhcjsPath = Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath Program
hpcProgram
guessToolFromGhcjsPath
:: Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath :: Program
-> ConfiguredProgram
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
guessToolFromGhcjsPath Program
tool ConfiguredProgram
ghcjsProg Verbosity
verbosity ProgramSearchPath
searchpath =
do
let toolname :: FilePath
toolname = Program -> FilePath
programName Program
tool
given_path :: FilePath
given_path = ConfiguredProgram -> FilePath
programPath ConfiguredProgram
ghcjsProg
given_dir :: FilePath
given_dir = FilePath -> FilePath
takeDirectory FilePath
given_path
real_path <- FilePath -> IO FilePath
canonicalizePath FilePath
given_path
let real_dir = FilePath -> FilePath
takeDirectory FilePath
real_path
versionSuffix FilePath
path = FilePath -> FilePath
takeVersionSuffix (FilePath -> FilePath
dropExeExtension FilePath
path)
given_suf = FilePath -> FilePath
versionSuffix FilePath
given_path
real_suf = FilePath -> FilePath
versionSuffix FilePath
real_path
guessNormal p
dir = p
dir p -> FilePath -> r
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
toolname FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
exeExtension Platform
buildPlatform
guessGhcjs p
dir =
p
dir
p -> FilePath -> r
forall p q r. PathLike p q r => p -> q -> r
</> (FilePath
toolname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-ghcjs")
FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
exeExtension Platform
buildPlatform
guessGhcjsVersioned p
dir FilePath
suf =
p
dir
p -> FilePath -> r
forall p q r. PathLike p q r => p -> q -> r
</> (FilePath
toolname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-ghcjs" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
suf)
FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
exeExtension Platform
buildPlatform
guessVersioned p
dir FilePath
suf =
p
dir
p -> FilePath -> r
forall p q r. PathLike p q r => p -> q -> r
</> (FilePath
toolname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
suf)
FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
exeExtension Platform
buildPlatform
mkGuesses p
dir FilePath
suf
| FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
suf = [p -> a
forall {p} {r}. PathLike p FilePath r => p -> r
guessGhcjs p
dir, p -> a
forall {p} {r}. PathLike p FilePath r => p -> r
guessNormal p
dir]
| Bool
otherwise =
[ p -> FilePath -> a
forall {p} {r}. PathLike p FilePath r => p -> FilePath -> r
guessGhcjsVersioned p
dir FilePath
suf
, p -> FilePath -> a
forall {p} {r}. PathLike p FilePath r => p -> FilePath -> r
guessVersioned p
dir FilePath
suf
, p -> a
forall {p} {r}. PathLike p FilePath r => p -> r
guessGhcjs p
dir
, p -> a
forall {p} {r}. PathLike p FilePath r => p -> r
guessNormal p
dir
]
guesses =
FilePath -> FilePath -> [FilePath]
forall {p} {a}. PathLike p FilePath a => p -> FilePath -> [a]
mkGuesses FilePath
given_dir FilePath
given_suf
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ if FilePath
real_path FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
given_path
then []
else FilePath -> FilePath -> [FilePath]
forall {p} {a}. PathLike p FilePath a => p -> FilePath -> [a]
mkGuesses FilePath
real_dir FilePath
real_suf
info verbosity $
"looking for tool "
++ toolname
++ " near compiler in "
++ given_dir
debug verbosity $ "candidate locations: " ++ show guesses
exists <- traverse doesFileExist guesses
case [file | (file, True) <- zip guesses exists] of
[] -> Program
-> Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
programFindLocation Program
tool Verbosity
verbosity ProgramSearchPath
searchpath
(FilePath
fp : [FilePath]
_) -> do
Verbosity -> FilePath -> IO ()
info Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"found " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
toolname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
fp
let lookedAt :: [FilePath]
lookedAt =
((FilePath, Bool) -> FilePath) -> [(FilePath, Bool)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath, Bool) -> FilePath
forall a b. (a, b) -> a
fst
([(FilePath, Bool)] -> [FilePath])
-> ([(FilePath, Bool)] -> [(FilePath, Bool)])
-> [(FilePath, Bool)]
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FilePath, Bool) -> Bool)
-> [(FilePath, Bool)] -> [(FilePath, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (\(FilePath
_file, Bool
exist) -> Bool -> Bool
not Bool
exist)
([(FilePath, Bool)] -> [FilePath])
-> [(FilePath, Bool)] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [Bool] -> [(FilePath, Bool)]
forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
guesses [Bool]
exists
Maybe (FilePath, [FilePath]) -> IO (Maybe (FilePath, [FilePath]))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((FilePath, [FilePath]) -> Maybe (FilePath, [FilePath])
forall a. a -> Maybe a
Just (FilePath
fp, [FilePath]
lookedAt))
where
takeVersionSuffix :: FilePath -> String
takeVersionSuffix :: FilePath -> FilePath
takeVersionSuffix = (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
takeWhileEndLE Char -> Bool
isSuffixChar
isSuffixChar :: Char -> Bool
isSuffixChar :: Char -> Bool
isSuffixChar Char
c = Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'
getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)]
getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(FilePath, FilePath)]
getGhcInfo Verbosity
verbosity ConfiguredProgram
ghcjsProg = Verbosity
-> GhcImplInfo -> ConfiguredProgram -> IO [(FilePath, FilePath)]
Internal.getGhcInfo Verbosity
verbosity GhcImplInfo
implInfo ConfiguredProgram
ghcjsProg
where
version :: Version
version = Version -> Maybe Version -> Version
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> Version
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.getGhcInfo: no version") (Maybe Version -> Version) -> Maybe Version -> Version
forall a b. (a -> b) -> a -> b
$ ConfiguredProgram -> Maybe Version
programVersion ConfiguredProgram
ghcjsProg
implInfo :: GhcImplInfo
implInfo = Version -> GhcImplInfo
ghcVersionImplInfo Version
version
getPackageDBContents
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir from))
-> PackageDBX (SymbolicPath from (Dir PkgDB))
-> ProgramDb
-> IO InstalledPackageIndex
getPackageDBContents :: forall from.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBX (SymbolicPath from ('Dir PkgDB))
-> ProgramDb
-> IO InstalledPackageIndex
getPackageDBContents Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir PackageDBX (SymbolicPath from ('Dir PkgDB))
packagedb ProgramDb
progdb = do
pkgss <- Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> [PackageDBX (SymbolicPath from ('Dir PkgDB))]
-> ProgramDb
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
forall from.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> [PackageDBX (SymbolicPath from ('Dir PkgDB))]
-> ProgramDb
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
getInstalledPackages' Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir [PackageDBX (SymbolicPath from ('Dir PkgDB))
packagedb] ProgramDb
progdb
toPackageIndex verbosity pkgss progdb
getInstalledPackages
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir from))
-> PackageDBStackX (SymbolicPath from (Dir PkgDB))
-> ProgramDb
-> IO InstalledPackageIndex
getInstalledPackages :: forall from.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBStackX (SymbolicPath from ('Dir PkgDB))
-> ProgramDb
-> IO InstalledPackageIndex
getInstalledPackages Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir PackageDBStackX (SymbolicPath from ('Dir PkgDB))
packagedbs ProgramDb
progdb = do
Verbosity -> IO ()
checkPackageDbEnvVar Verbosity
verbosity
Verbosity
-> PackageDBStackX (SymbolicPath from ('Dir PkgDB)) -> IO ()
forall fp. Eq fp => Verbosity -> PackageDBStackX fp -> IO ()
checkPackageDbStack Verbosity
verbosity PackageDBStackX (SymbolicPath from ('Dir PkgDB))
packagedbs
pkgss <- Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBStackX (SymbolicPath from ('Dir PkgDB))
-> ProgramDb
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
forall from.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> [PackageDBX (SymbolicPath from ('Dir PkgDB))]
-> ProgramDb
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
getInstalledPackages' Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir PackageDBStackX (SymbolicPath from ('Dir PkgDB))
packagedbs ProgramDb
progdb
index <- toPackageIndex verbosity pkgss progdb
return $! index
toPackageIndex
:: Verbosity
-> [(PackageDBX a, [InstalledPackageInfo])]
-> ProgramDb
-> IO InstalledPackageIndex
toPackageIndex :: forall a.
Verbosity
-> [(PackageDBX a, [InstalledPackageInfo])]
-> ProgramDb
-> IO InstalledPackageIndex
toPackageIndex Verbosity
verbosity [(PackageDBX a, [InstalledPackageInfo])]
pkgss ProgramDb
progdb = do
topDir <- Verbosity -> ConfiguredProgram -> IO FilePath
getLibDir' Verbosity
verbosity ConfiguredProgram
ghcjsProg
let indices =
[ [InstalledPackageInfo] -> InstalledPackageIndex
PackageIndex.fromList ((InstalledPackageInfo -> InstalledPackageInfo)
-> [InstalledPackageInfo] -> [InstalledPackageInfo]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> InstalledPackageInfo -> InstalledPackageInfo
Internal.substTopDir FilePath
topDir) [InstalledPackageInfo]
pkgs)
| (PackageDBX a
_, [InstalledPackageInfo]
pkgs) <- [(PackageDBX a, [InstalledPackageInfo])]
pkgss
]
return $! (mconcat indices)
where
ghcjsProg :: ConfiguredProgram
ghcjsProg = ConfiguredProgram -> Maybe ConfiguredProgram -> ConfiguredProgram
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ConfiguredProgram
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.toPackageIndex no ghcjs program") (Maybe ConfiguredProgram -> ConfiguredProgram)
-> Maybe ConfiguredProgram -> ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
ghcjsProgram ProgramDb
progdb
getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath
getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath
getLibDir Verbosity
verbosity LocalBuildInfo
lbi =
(Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEndLE Char -> Bool
isSpace
(FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Verbosity -> Program -> ProgramDb -> [FilePath] -> IO FilePath
getDbProgramOutput
Verbosity
verbosity
Program
ghcjsProgram
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
[FilePath
"--print-libdir"]
getLibDir' :: Verbosity -> ConfiguredProgram -> IO FilePath
getLibDir' :: Verbosity -> ConfiguredProgram -> IO FilePath
getLibDir' Verbosity
verbosity ConfiguredProgram
ghcjsProg =
(Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEndLE Char -> Bool
isSpace
(FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Verbosity -> ConfiguredProgram -> [FilePath] -> IO FilePath
getProgramOutput Verbosity
verbosity ConfiguredProgram
ghcjsProg [FilePath
"--print-libdir"]
getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath
getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath
getGlobalPackageDB Verbosity
verbosity ConfiguredProgram
ghcProg =
(Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEndLE Char -> Bool
isSpace
(FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Verbosity -> ConfiguredProgram -> [FilePath] -> IO FilePath
getProgramOutput Verbosity
verbosity ConfiguredProgram
ghcProg [FilePath
"--print-global-package-db"]
getUserPackageDB :: Verbosity -> ConfiguredProgram -> Platform -> IO FilePath
getUserPackageDB :: Verbosity -> ConfiguredProgram -> Platform -> IO FilePath
getUserPackageDB Verbosity
_verbosity ConfiguredProgram
ghcjsProg Platform
platform = do
appdir <- FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"ghcjs"
return (appdir </> platformAndVersion </> packageConfFileName)
where
platformAndVersion :: FilePath
platformAndVersion =
Platform -> Version -> FilePath
Internal.ghcPlatformAndVersionString
Platform
platform
Version
ghcjsVersion
packageConfFileName :: FilePath
packageConfFileName = FilePath
"package.conf.d"
ghcjsVersion :: Version
ghcjsVersion = Version -> Maybe Version -> Version
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> Version
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.getUserPackageDB: no version") (Maybe Version -> Version) -> Maybe Version -> Version
forall a b. (a -> b) -> a -> b
$ ConfiguredProgram -> Maybe Version
programVersion ConfiguredProgram
ghcjsProg
checkPackageDbEnvVar :: Verbosity -> IO ()
checkPackageDbEnvVar :: Verbosity -> IO ()
checkPackageDbEnvVar Verbosity
verbosity =
Verbosity -> FilePath -> FilePath -> IO ()
Internal.checkPackageDbEnvVar Verbosity
verbosity FilePath
"GHCJS" FilePath
"GHCJS_PACKAGE_PATH"
checkPackageDbStack :: Eq fp => Verbosity -> PackageDBStackX fp -> IO ()
checkPackageDbStack :: forall fp. Eq fp => Verbosity -> PackageDBStackX fp -> IO ()
checkPackageDbStack Verbosity
_ (PackageDBX fp
GlobalPackageDB : [PackageDBX fp]
rest)
| PackageDBX fp
forall fp. PackageDBX fp
GlobalPackageDB PackageDBX fp -> [PackageDBX fp] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [PackageDBX fp]
rest = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkPackageDbStack Verbosity
verbosity [PackageDBX fp]
rest
| PackageDBX fp
forall fp. PackageDBX fp
GlobalPackageDB PackageDBX fp -> [PackageDBX fp] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [PackageDBX fp]
rest =
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalException
GlobalPackageDBLimitation
checkPackageDbStack Verbosity
verbosity [PackageDBX fp]
_ =
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity CabalException
GlobalPackageDBSpecifiedFirst
getInstalledPackages'
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir from))
-> [PackageDBX (SymbolicPath from (Dir PkgDB))]
-> ProgramDb
-> IO [(PackageDBX (SymbolicPath from (Dir PkgDB)), [InstalledPackageInfo])]
getInstalledPackages' :: forall from.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> [PackageDBX (SymbolicPath from ('Dir PkgDB))]
-> ProgramDb
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
getInstalledPackages' Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir [PackageDBX (SymbolicPath from ('Dir PkgDB))]
packagedbs ProgramDb
progdb =
[IO
(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
-> IO
[(PackageDBX (SymbolicPath from ('Dir PkgDB)),
[InstalledPackageInfo])]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA
[ do
pkgs <- HcPkgInfo
-> Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBX (SymbolicPath from ('Dir PkgDB))
-> IO [InstalledPackageInfo]
forall from.
HcPkgInfo
-> Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBX (SymbolicPath from ('Dir PkgDB))
-> IO [InstalledPackageInfo]
HcPkg.dump (ProgramDb -> HcPkgInfo
hcPkgInfo ProgramDb
progdb) Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir PackageDBX (SymbolicPath from ('Dir PkgDB))
packagedb
return (packagedb, pkgs)
| PackageDBX (SymbolicPath from ('Dir PkgDB))
packagedb <- [PackageDBX (SymbolicPath from ('Dir PkgDB))]
packagedbs
]
getInstalledPackagesMonitorFiles
:: Verbosity
-> Platform
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> ProgramDb
-> [PackageDB]
-> IO [FilePath]
getInstalledPackagesMonitorFiles :: Verbosity
-> Platform
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> ProgramDb
-> [PackageDB]
-> IO [FilePath]
getInstalledPackagesMonitorFiles Verbosity
verbosity Platform
platform Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir ProgramDb
progdb =
(PackageDB -> IO FilePath) -> [PackageDB] -> IO [FilePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse PackageDB -> IO FilePath
getPackageDBPath
where
getPackageDBPath :: PackageDB -> IO FilePath
getPackageDBPath :: PackageDB -> IO FilePath
getPackageDBPath PackageDB
GlobalPackageDB =
FilePath -> IO FilePath
selectMonitorFile (FilePath -> IO FilePath) -> IO FilePath -> IO FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> ConfiguredProgram -> IO FilePath
getGlobalPackageDB Verbosity
verbosity ConfiguredProgram
ghcjsProg
getPackageDBPath PackageDB
UserPackageDB =
FilePath -> IO FilePath
selectMonitorFile (FilePath -> IO FilePath) -> IO FilePath -> IO FilePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Verbosity -> ConfiguredProgram -> Platform -> IO FilePath
getUserPackageDB Verbosity
verbosity ConfiguredProgram
ghcjsProg Platform
platform
getPackageDBPath (SpecificPackageDB SymbolicPath Pkg ('Dir PkgDB)
path) = FilePath -> IO FilePath
selectMonitorFile (Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir PkgDB) -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir PkgDB)
path)
selectMonitorFile :: FilePath -> IO FilePath
selectMonitorFile FilePath
path0 = do
let path :: FilePath
path =
if FilePath -> Bool
isRelative FilePath
path0
then Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX 'OnlyRelative Pkg (ZonkAny 12) -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir (FilePath -> SymbolicPathX 'OnlyRelative Pkg (ZonkAny 12)
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx FilePath
path0)
else FilePath
path0
isFileStyle <- FilePath -> IO Bool
doesFileExist FilePath
path
if isFileStyle
then return path
else return (path </> "package.cache")
ghcjsProg :: ConfiguredProgram
ghcjsProg = ConfiguredProgram -> Maybe ConfiguredProgram -> ConfiguredProgram
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ConfiguredProgram
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.toPackageIndex no ghcjs program") (Maybe ConfiguredProgram -> ConfiguredProgram)
-> Maybe ConfiguredProgram -> ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
ghcjsProgram ProgramDb
progdb
toJSLibName :: String -> String
toJSLibName :: FilePath -> FilePath
toJSLibName FilePath
lib
| FilePath -> FilePath
takeExtension FilePath
lib FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath
".dll", FilePath
".dylib", FilePath
".so"] =
FilePath -> FilePath -> FilePath
replaceExtension FilePath
lib FilePath
"js_so"
| FilePath -> FilePath
takeExtension FilePath
lib FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".a" = FilePath -> FilePath -> FilePath
replaceExtension FilePath
lib FilePath
"js_a"
| Bool
otherwise = FilePath
lib FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"js_a"
buildLib
:: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildLib :: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildLib = Maybe [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildOrReplLib Maybe [FilePath]
forall a. Maybe a
Nothing
replLib
:: [String]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
replLib :: [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
replLib = Maybe [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildOrReplLib (Maybe [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ())
-> ([FilePath] -> Maybe [FilePath])
-> [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> Maybe [FilePath]
forall a. a -> Maybe a
Just
buildOrReplLib
:: Maybe [String]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildOrReplLib :: Maybe [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO ()
buildOrReplLib Maybe [FilePath]
mReplFlags Verbosity
verbosity Flag ParStrat
numJobs PackageDescription
_pkg_descr LocalBuildInfo
lbi Library
lib ComponentLocalBuildInfo
clbi = do
let uid :: UnitId
uid = ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi
libTargetDir :: SymbolicPath Pkg ('Dir Build)
libTargetDir = LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
whenVanillaLib :: Bool -> f () -> f ()
whenVanillaLib Bool
forceVanilla =
Bool -> f () -> f ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
forceVanilla Bool -> Bool -> Bool
|| LocalBuildInfo -> Bool
withVanillaLib LocalBuildInfo
lbi)
whenProfLib :: IO () -> IO ()
whenProfLib = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (LocalBuildInfo -> Bool
withProfLib LocalBuildInfo
lbi)
whenSharedLib :: Bool -> f () -> f ()
whenSharedLib Bool
forceShared =
Bool -> f () -> f ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
forceShared Bool -> Bool -> Bool
|| LocalBuildInfo -> Bool
withSharedLib LocalBuildInfo
lbi)
whenStaticLib :: Bool -> f () -> f ()
whenStaticLib Bool
forceStatic =
Bool -> f () -> f ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
forceStatic Bool -> Bool -> Bool
|| LocalBuildInfo -> Bool
withStaticLib LocalBuildInfo
lbi)
forRepl :: Bool
forRepl = Bool -> ([FilePath] -> Bool) -> Maybe [FilePath] -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> [FilePath] -> Bool
forall a b. a -> b -> a
const Bool
True) Maybe [FilePath]
mReplFlags
comp :: Compiler
comp = LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi
implInfo :: GhcImplInfo
implInfo = Compiler -> GhcImplInfo
getImplInfo Compiler
comp
platform :: Platform
platform@(Platform Arch
_hostArch OS
_hostOS) = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
has_code :: Bool
has_code = Bool -> Bool
not (ComponentLocalBuildInfo -> Bool
componentIsIndefinite ComponentLocalBuildInfo
clbi)
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi
u :: SymbolicPathX allowAbs Pkg to -> FilePath
u :: forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
u = SymbolicPathX allowAbs Pkg to -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath
(ghcjsProg, _) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
ghcjsProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
let runGhcjsProg = Verbosity
-> ConfiguredProgram
-> Compiler
-> Platform
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> GhcOptions
-> IO ()
runGHC Verbosity
verbosity ConfiguredProgram
ghcjsProg Compiler
comp Platform
platform Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
let libBi = Library -> BuildInfo
libBuildInfo Library
lib
let isGhcjsDynamic = Compiler -> Bool
isDynamic Compiler
comp
dynamicTooSupported = Compiler -> Bool
supportsDynamicToo Compiler
comp
doingTH = BuildInfo -> Bool
usesTemplateHaskellOrQQ BuildInfo
libBi
forceVanillaLib = Bool
doingTH Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
isGhcjsDynamic
forceSharedLib = Bool
doingTH Bool -> Bool -> Bool
&& Bool
isGhcjsDynamic
let isCoverageEnabled = LocalBuildInfo -> Bool
libCoverage LocalBuildInfo
lbi
hpcdir Way
way
| Bool
forRepl = Flag (SymbolicPath Pkg ('Dir Mix))
forall a. Monoid a => a
mempty
| Bool
isCoverageEnabled = SymbolicPath Pkg ('Dir Mix) -> Flag (SymbolicPath Pkg ('Dir Mix))
forall a. a -> Flag a
toFlag (SymbolicPath Pkg ('Dir Mix) -> Flag (SymbolicPath Pkg ('Dir Mix)))
-> SymbolicPath Pkg ('Dir Mix)
-> Flag (SymbolicPath Pkg ('Dir Mix))
forall a b. (a -> b) -> a -> b
$ SymbolicPath Pkg ('Dir Dist) -> Way -> SymbolicPath Pkg ('Dir Mix)
Hpc.mixDir (SymbolicPath Pkg ('Dir Build) -> SymbolicPath Pkg ('Dir Build)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPath Pkg ('Dir Build)
libTargetDir SymbolicPath Pkg ('Dir Build)
-> SymbolicPathX 'OnlyRelative Build ('Dir Dist)
-> SymbolicPath Pkg ('Dir Dist)
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative Build ('Dir Artifacts)
-> SymbolicPathX 'OnlyRelative Build ('Dir Dist)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPathX 'OnlyRelative Build ('Dir Artifacts)
extraCompilationArtifacts) Way
way
| Bool
otherwise = Flag (SymbolicPath Pkg ('Dir Mix))
forall a. Monoid a => a
mempty
createDirectoryIfMissingVerbose verbosity True $ i libTargetDir
let cLikeFiles = NubListR (SymbolicPath Pkg 'File) -> [SymbolicPath Pkg 'File]
forall a. NubListR a -> [a]
fromNubListR (NubListR (SymbolicPath Pkg 'File) -> [SymbolicPath Pkg 'File])
-> NubListR (SymbolicPath Pkg 'File) -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> a -> b
$ [SymbolicPath Pkg 'File] -> NubListR (SymbolicPath Pkg 'File)
forall a. Ord a => [a] -> NubListR a
toNubListR (BuildInfo -> [SymbolicPath Pkg 'File]
cSources BuildInfo
libBi) NubListR (SymbolicPath Pkg 'File)
-> NubListR (SymbolicPath Pkg 'File)
-> NubListR (SymbolicPath Pkg 'File)
forall a. Semigroup a => a -> a -> a
<> [SymbolicPath Pkg 'File] -> NubListR (SymbolicPath Pkg 'File)
forall a. Ord a => [a] -> NubListR a
toNubListR (BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources BuildInfo
libBi)
jsSrcs = BuildInfo -> [SymbolicPath Pkg 'File]
jsSources BuildInfo
libBi
cObjs = (SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map ((SymbolicPath Pkg 'File -> FilePath -> SymbolicPath Pkg 'File
forall (allowAbsolute :: AllowAbsolute) from.
SymbolicPathX allowAbsolute from 'File
-> FilePath -> SymbolicPathX allowAbsolute from 'File
`replaceExtensionSymbolicPath` FilePath
objExtension)) [SymbolicPath Pkg 'File]
cLikeFiles
baseOpts = Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir Build)
-> GhcOptions
forall build.
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
componentGhcOptions Verbosity
verbosity LocalBuildInfo
lbi BuildInfo
libBi ComponentLocalBuildInfo
clbi SymbolicPath Pkg ('Dir Build)
libTargetDir
linkJsLibOpts =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptExtra =
[ "-link-js-lib"
, getHSLibraryName uid
, "-js-lib-outputdir"
, u libTargetDir
]
++ map u jsSrcs
}
vanillaOptsNoJsLib =
GhcOptions
baseOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptMode = toFlag GhcModeMake
, ghcOptNumJobs = numJobs
, ghcOptInputModules = toNubListR $ allLibModules lib clbi
, ghcOptHPCDir = hpcdir Hpc.Vanilla
}
vanillaOpts = GhcOptions
vanillaOptsNoJsLib GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
linkJsLibOpts
profOpts =
FilePath -> FilePath -> GhcOptions -> GhcOptions
adjustExts FilePath
"p_hi" FilePath
"p_o" GhcOptions
vanillaOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptProfilingMode = toFlag True
, ghcOptProfilingAuto =
Internal.profDetailLevelFlag
True
(withProfLibDetail lbi)
,
ghcOptExtra = hcProfOptions GHC libBi
, ghcOptHPCDir = hpcdir Hpc.Prof
}
sharedOpts =
FilePath -> FilePath -> GhcOptions -> GhcOptions
adjustExts FilePath
"dyn_hi" FilePath
"dyn_o" GhcOptions
vanillaOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcDynamicOnly
, ghcOptFPic = toFlag True
,
ghcOptExtra = hcOptions GHC libBi ++ hcSharedOptions GHC libBi
, ghcOptHPCDir = hpcdir Hpc.Dyn
}
vanillaSharedOpts =
GhcOptions
vanillaOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcStaticAndDynamic
, ghcOptDynHiSuffix = toFlag "js_dyn_hi"
, ghcOptDynObjSuffix = toFlag "js_dyn_o"
, ghcOptHPCDir = hpcdir Hpc.Dyn
}
unless (forRepl || null (allLibModules lib clbi) && null jsSrcs && null cObjs) $
do
let vanilla = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenVanillaLib Bool
forceVanillaLib (GhcOptions -> IO ()
runGhcjsProg GhcOptions
vanillaOpts)
shared = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
whenSharedLib Bool
forceSharedLib (GhcOptions -> IO ()
runGhcjsProg GhcOptions
sharedOpts)
useDynToo =
Bool
dynamicTooSupported
Bool -> Bool -> Bool
&& (Bool
forceVanillaLib Bool -> Bool -> Bool
|| LocalBuildInfo -> Bool
withVanillaLib LocalBuildInfo
lbi)
Bool -> Bool -> Bool
&& (Bool
forceSharedLib Bool -> Bool -> Bool
|| LocalBuildInfo -> Bool
withSharedLib LocalBuildInfo
lbi)
Bool -> Bool -> Bool
&& [FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (CompilerFlavor -> BuildInfo -> [FilePath]
hcSharedOptions CompilerFlavor
GHC BuildInfo
libBi)
if not has_code
then vanilla
else
if useDynToo
then do
runGhcjsProg vanillaSharedOpts
case (hpcdir Hpc.Dyn, hpcdir Hpc.Vanilla) of
(Flag SymbolicPath Pkg ('Dir Mix)
dynDir, Flag SymbolicPath Pkg ('Dir Mix)
vanillaDir) ->
Verbosity -> FilePath -> FilePath -> IO ()
copyDirectoryRecursive Verbosity
verbosity (SymbolicPath Pkg ('Dir Mix) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPath Pkg ('Dir Mix)
dynDir) (SymbolicPath Pkg ('Dir Mix) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPath Pkg ('Dir Mix)
vanillaDir)
(Flag (SymbolicPath Pkg ('Dir Mix)),
Flag (SymbolicPath Pkg ('Dir Mix)))
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else
if isGhcjsDynamic
then do shared; vanilla
else do vanilla; shared
whenProfLib (runGhcjsProg profOpts)
when has_code . when False . unless forRepl $ do
info verbosity "Linking..."
let cSharedObjs =
(SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map
((SymbolicPath Pkg 'File -> FilePath -> SymbolicPath Pkg 'File
forall (allowAbsolute :: AllowAbsolute) from.
SymbolicPathX allowAbsolute from 'File
-> FilePath -> SymbolicPathX allowAbsolute from 'File
`replaceExtensionSymbolicPath` (FilePath
"dyn_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
objExtension)))
(BuildInfo -> [SymbolicPath Pkg 'File]
cSources BuildInfo
libBi [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources BuildInfo
libBi)
compiler_id = Compiler -> CompilerId
compilerId (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
sharedLibFilePath = SymbolicPath Pkg ('Dir Build)
libTargetDir SymbolicPath Pkg ('Dir Build)
-> RelativePath Build c3 -> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath Build c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx (Platform -> CompilerId -> UnitId -> FilePath
mkSharedLibName (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi) CompilerId
compiler_id UnitId
uid)
staticLibFilePath = SymbolicPath Pkg ('Dir Build)
libTargetDir SymbolicPath Pkg ('Dir Build)
-> RelativePath Build c3 -> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath Build c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx (Platform -> CompilerId -> UnitId -> FilePath
mkStaticLibName (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi) CompilerId
compiler_id UnitId
uid)
let stubObjs = []
stubSharedObjs = []
hObjs <-
Internal.getHaskellObjects
implInfo
lib
lbi
clbi
(coerceSymbolicPath libTargetDir)
objExtension
True
hSharedObjs <-
if withSharedLib lbi
then
Internal.getHaskellObjects
implInfo
lib
lbi
clbi
(coerceSymbolicPath libTargetDir)
("dyn_" ++ objExtension)
False
else return []
unless (null hObjs && null cObjs && null stubObjs) $ do
rpaths <- getRPaths lbi clbi
let staticObjectFiles =
[SymbolicPath Pkg 'File]
hObjs
[SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a. [a] -> [a] -> [a]
++ (SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SymbolicPath Pkg 'File
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath (FilePath -> SymbolicPath Pkg 'File)
-> (SymbolicPath Pkg 'File -> FilePath)
-> SymbolicPath Pkg 'File
-> SymbolicPath Pkg 'File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SymbolicPath Pkg ('Dir Build) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Build)
libTargetDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</>) (FilePath -> FilePath)
-> (SymbolicPath Pkg 'File -> FilePath)
-> SymbolicPath Pkg 'File
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath) [SymbolicPath Pkg 'File]
cObjs
[SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a. [a] -> [a] -> [a]
++ [SymbolicPath Pkg 'File]
forall a. [a]
stubObjs
dynamicObjectFiles =
[SymbolicPath Pkg 'File]
hSharedObjs
[SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a. [a] -> [a] -> [a]
++ (SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> SymbolicPath Pkg 'File
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath (FilePath -> SymbolicPath Pkg 'File)
-> (SymbolicPath Pkg 'File -> FilePath)
-> SymbolicPath Pkg 'File
-> SymbolicPath Pkg 'File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SymbolicPath Pkg ('Dir Build) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg ('Dir Build)
libTargetDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</>) (FilePath -> FilePath)
-> (SymbolicPath Pkg 'File -> FilePath)
-> SymbolicPath Pkg 'File
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath) [SymbolicPath Pkg 'File]
cSharedObjs
[SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a. [a] -> [a] -> [a]
++ [SymbolicPath Pkg 'File]
forall a. [a]
stubSharedObjs
ghcSharedLinkArgs =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptShared = toFlag True
, ghcOptDynLinkMode = toFlag GhcDynamicOnly
, ghcOptInputFiles = toNubListR dynamicObjectFiles
, ghcOptOutputFile = toFlag sharedLibFilePath
, ghcOptExtra = hcOptions GHC libBi ++ hcSharedOptions GHC libBi
,
ghcOptHideAllPackages = toFlag True
, ghcOptNoAutoLinkPackages = toFlag True
, ghcOptPackageDBs = withPackageDB lbi
, ghcOptThisUnitId = case clbi of
LibComponentLocalBuildInfo{componentCompatPackageKey :: ComponentLocalBuildInfo -> FilePath
componentCompatPackageKey = FilePath
pk} ->
FilePath -> Flag FilePath
forall a. a -> Flag a
toFlag FilePath
pk
ComponentLocalBuildInfo
_ -> Flag FilePath
forall a. Monoid a => a
mempty
, ghcOptThisComponentId = case clbi of
LibComponentLocalBuildInfo{componentInstantiatedWith :: ComponentLocalBuildInfo -> [(ModuleName, OpenModule)]
componentInstantiatedWith = [(ModuleName, OpenModule)]
insts} ->
if [(ModuleName, OpenModule)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, OpenModule)]
insts
then Flag ComponentId
forall a. Monoid a => a
mempty
else ComponentId -> Flag ComponentId
forall a. a -> Flag a
toFlag (ComponentLocalBuildInfo -> ComponentId
componentComponentId ComponentLocalBuildInfo
clbi)
ComponentLocalBuildInfo
_ -> Flag ComponentId
forall a. Monoid a => a
mempty
, ghcOptInstantiatedWith = case clbi of
LibComponentLocalBuildInfo{componentInstantiatedWith :: ComponentLocalBuildInfo -> [(ModuleName, OpenModule)]
componentInstantiatedWith = [(ModuleName, OpenModule)]
insts} ->
[(ModuleName, OpenModule)]
insts
ComponentLocalBuildInfo
_ -> []
, ghcOptPackages =
toNubListR $
Internal.mkGhcOptPackages mempty clbi
, ghcOptLinkLibs = extraLibs libBi
, ghcOptLinkLibPath = toNubListR $ extraLibDirs libBi
, ghcOptLinkFrameworks = toNubListR $ map getSymbolicPath $ PD.frameworks libBi
, ghcOptLinkFrameworkDirs =
toNubListR $ PD.extraFrameworkDirs libBi
, ghcOptRPaths = rpaths
}
ghcStaticLinkArgs =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptStaticLib = toFlag True
, ghcOptInputFiles = toNubListR staticObjectFiles
, ghcOptOutputFile = toFlag staticLibFilePath
, ghcOptExtra = hcStaticOptions GHC libBi
, ghcOptHideAllPackages = toFlag True
, ghcOptNoAutoLinkPackages = toFlag True
, ghcOptPackageDBs = withPackageDB lbi
, ghcOptThisUnitId = case clbi of
LibComponentLocalBuildInfo{componentCompatPackageKey :: ComponentLocalBuildInfo -> FilePath
componentCompatPackageKey = FilePath
pk} ->
FilePath -> Flag FilePath
forall a. a -> Flag a
toFlag FilePath
pk
ComponentLocalBuildInfo
_ -> Flag FilePath
forall a. Monoid a => a
mempty
, ghcOptThisComponentId = case clbi of
LibComponentLocalBuildInfo{componentInstantiatedWith :: ComponentLocalBuildInfo -> [(ModuleName, OpenModule)]
componentInstantiatedWith = [(ModuleName, OpenModule)]
insts} ->
if [(ModuleName, OpenModule)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, OpenModule)]
insts
then Flag ComponentId
forall a. Monoid a => a
mempty
else ComponentId -> Flag ComponentId
forall a. a -> Flag a
toFlag (ComponentLocalBuildInfo -> ComponentId
componentComponentId ComponentLocalBuildInfo
clbi)
ComponentLocalBuildInfo
_ -> Flag ComponentId
forall a. Monoid a => a
mempty
, ghcOptInstantiatedWith = case clbi of
LibComponentLocalBuildInfo{componentInstantiatedWith :: ComponentLocalBuildInfo -> [(ModuleName, OpenModule)]
componentInstantiatedWith = [(ModuleName, OpenModule)]
insts} ->
[(ModuleName, OpenModule)]
insts
ComponentLocalBuildInfo
_ -> []
, ghcOptPackages =
toNubListR $
Internal.mkGhcOptPackages mempty clbi
, ghcOptLinkLibs = extraLibs libBi
, ghcOptLinkLibPath = toNubListR $ extraLibDirs libBi
}
info verbosity (show (ghcOptPackages ghcSharedLinkArgs))
whenSharedLib False $
runGhcjsProg ghcSharedLinkArgs
whenStaticLib False $
runGhcjsProg ghcStaticLinkArgs
startInterpreter
:: Verbosity
-> ProgramDb
-> Compiler
-> Platform
-> PackageDBStack
-> IO ()
startInterpreter :: Verbosity
-> ProgramDb -> Compiler -> Platform -> [PackageDB] -> IO ()
startInterpreter Verbosity
verbosity ProgramDb
progdb Compiler
comp Platform
platform [PackageDB]
packageDBs = do
let replOpts :: GhcOptions
replOpts =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptMode = toFlag GhcModeInteractive
, ghcOptPackageDBs = packageDBs
}
Verbosity -> [PackageDB] -> IO ()
forall fp. Eq fp => Verbosity -> PackageDBStackX fp -> IO ()
checkPackageDbStack Verbosity
verbosity [PackageDB]
packageDBs
(ghcjsProg, _) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
ghcjsProgram ProgramDb
progdb
runGHC verbosity ghcjsProg comp platform Nothing replOpts
buildFLib
:: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
buildFLib :: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
buildFLib Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi = Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi (GBuildMode -> ComponentLocalBuildInfo -> IO ())
-> (ForeignLib -> GBuildMode)
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> GBuildMode
GBuildFLib
replFLib
:: [String]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
replFLib :: [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
replFLib [FilePath]
replFlags Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi =
Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi (GBuildMode -> ComponentLocalBuildInfo -> IO ())
-> (ForeignLib -> GBuildMode)
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> ForeignLib -> GBuildMode
GReplFLib [FilePath]
replFlags
buildExe
:: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
buildExe :: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
buildExe Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi = Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi (GBuildMode -> ComponentLocalBuildInfo -> IO ())
-> (Executable -> GBuildMode)
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> GBuildMode
GBuildExe
replExe
:: [String]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
replExe :: [FilePath]
-> Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
replExe [FilePath]
replFlags Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi =
Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild Verbosity
v Flag ParStrat
njobs PackageDescription
pkg LocalBuildInfo
lbi (GBuildMode -> ComponentLocalBuildInfo -> IO ())
-> (Executable -> GBuildMode)
-> Executable
-> ComponentLocalBuildInfo
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> Executable -> GBuildMode
GReplExe [FilePath]
replFlags
data GBuildMode
= GBuildExe Executable
| GReplExe [String] Executable
| GBuildFLib ForeignLib
| GReplFLib [String] ForeignLib
gbuildInfo :: GBuildMode -> BuildInfo
gbuildInfo :: GBuildMode -> BuildInfo
gbuildInfo (GBuildExe Executable
exe) = Executable -> BuildInfo
buildInfo Executable
exe
gbuildInfo (GReplExe [FilePath]
_ Executable
exe) = Executable -> BuildInfo
buildInfo Executable
exe
gbuildInfo (GBuildFLib ForeignLib
flib) = ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib
gbuildInfo (GReplFLib [FilePath]
_ ForeignLib
flib) = ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib
gbuildName :: GBuildMode -> String
gbuildName :: GBuildMode -> FilePath
gbuildName (GBuildExe Executable
exe) = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ Executable -> UnqualComponentName
exeName Executable
exe
gbuildName (GReplExe [FilePath]
_ Executable
exe) = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ Executable -> UnqualComponentName
exeName Executable
exe
gbuildName (GBuildFLib ForeignLib
flib) = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
gbuildName (GReplFLib [FilePath]
_ ForeignLib
flib) = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
gbuildTargetName :: LocalBuildInfo -> GBuildMode -> String
gbuildTargetName :: LocalBuildInfo -> GBuildMode -> FilePath
gbuildTargetName LocalBuildInfo
lbi (GBuildExe Executable
exe) = Platform -> Executable -> FilePath
exeTargetName (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi) Executable
exe
gbuildTargetName LocalBuildInfo
lbi (GReplExe [FilePath]
_ Executable
exe) = Platform -> Executable -> FilePath
exeTargetName (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi) Executable
exe
gbuildTargetName LocalBuildInfo
lbi (GBuildFLib ForeignLib
flib) = LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib
gbuildTargetName LocalBuildInfo
lbi (GReplFLib [FilePath]
_ ForeignLib
flib) = LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib
exeTargetName :: Platform -> Executable -> String
exeTargetName :: Platform -> Executable -> FilePath
exeTargetName Platform
platform Executable
exe = UnqualComponentName -> FilePath
unUnqualComponentName (Executable -> UnqualComponentName
exeName Executable
exe) FilePath -> FilePath -> FilePath
`withExt` Platform -> FilePath
exeExtension Platform
platform
flibTargetName :: LocalBuildInfo -> ForeignLib -> String
flibTargetName :: LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib =
case (OS
os, ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib) of
(OS
Windows, ForeignLibType
ForeignLibNativeShared) -> FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"dll"
(OS
Windows, ForeignLibType
ForeignLibNativeStatic) -> FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"lib"
(OS
Linux, ForeignLibType
ForeignLibNativeShared) -> FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
versionedExt
(OS
_other, ForeignLibType
ForeignLibNativeShared) -> FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
dllExtension (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi)
(OS
_other, ForeignLibType
ForeignLibNativeStatic) -> FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
staticLibExtension (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi)
(OS
_any, ForeignLibType
ForeignLibTypeUnknown) -> FilePath -> FilePath
forall a. FilePath -> a
cabalBug FilePath
"unknown foreign lib type"
where
nm :: String
nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
os :: OS
os :: OS
os =
let (Platform Arch
_ OS
os') = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
in OS
os'
versionedExt :: String
versionedExt :: FilePath
versionedExt =
let nums :: [Int]
nums = ForeignLib -> OS -> [Int]
foreignLibVersion ForeignLib
flib OS
os
in (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
(<.>) FilePath
"so" ((Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Int -> FilePath
forall a. Show a => a -> FilePath
show [Int]
nums)
flibBuildName :: LocalBuildInfo -> ForeignLib -> String
flibBuildName :: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildName LocalBuildInfo
lbi ForeignLib
flib
| (OS
os, ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib)
(OS, ForeignLibType) -> (OS, ForeignLibType) -> Bool
forall a. Eq a => a -> a -> Bool
== (OS
Linux, ForeignLibType
ForeignLibNativeShared) =
let nums :: [Int]
nums = ForeignLib -> OS -> [Int]
foreignLibVersion ForeignLib
flib OS
os
in FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
(<.>) FilePath
"so" ((Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 [Int]
nums))
| Bool
otherwise = LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib
where
os :: OS
os :: OS
os =
let (Platform Arch
_ OS
os') = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
in OS
os'
nm :: String
nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
gbuildIsRepl :: GBuildMode -> Bool
gbuildIsRepl :: GBuildMode -> Bool
gbuildIsRepl (GBuildExe Executable
_) = Bool
False
gbuildIsRepl (GReplExe [FilePath]
_ Executable
_) = Bool
True
gbuildIsRepl (GBuildFLib ForeignLib
_) = Bool
False
gbuildIsRepl (GReplFLib [FilePath]
_ ForeignLib
_) = Bool
True
gbuildNeedDynamic :: LocalBuildInfo -> GBuildMode -> Bool
gbuildNeedDynamic :: LocalBuildInfo -> GBuildMode -> Bool
gbuildNeedDynamic LocalBuildInfo
lbi GBuildMode
bm =
case GBuildMode
bm of
GBuildExe Executable
_ -> LocalBuildInfo -> Bool
withDynExe LocalBuildInfo
lbi
GReplExe [FilePath]
_ Executable
_ -> LocalBuildInfo -> Bool
withDynExe LocalBuildInfo
lbi
GBuildFLib ForeignLib
flib -> ForeignLib -> Bool
withDynFLib ForeignLib
flib
GReplFLib [FilePath]
_ ForeignLib
flib -> ForeignLib -> Bool
withDynFLib ForeignLib
flib
where
withDynFLib :: ForeignLib -> Bool
withDynFLib ForeignLib
flib =
case ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib of
ForeignLibType
ForeignLibNativeShared ->
ForeignLibOption
ForeignLibStandalone ForeignLibOption -> [ForeignLibOption] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ForeignLib -> [ForeignLibOption]
foreignLibOptions ForeignLib
flib
ForeignLibType
ForeignLibNativeStatic ->
Bool
False
ForeignLibType
ForeignLibTypeUnknown ->
FilePath -> Bool
forall a. FilePath -> a
cabalBug FilePath
"unknown foreign lib type"
gbuildModDefFiles :: GBuildMode -> [RelativePath Source File]
gbuildModDefFiles :: GBuildMode -> [RelativePath Source 'File]
gbuildModDefFiles (GBuildExe Executable
_) = []
gbuildModDefFiles (GReplExe [FilePath]
_ Executable
_) = []
gbuildModDefFiles (GBuildFLib ForeignLib
flib) = ForeignLib -> [RelativePath Source 'File]
foreignLibModDefFile ForeignLib
flib
gbuildModDefFiles (GReplFLib [FilePath]
_ ForeignLib
flib) = ForeignLib -> [RelativePath Source 'File]
foreignLibModDefFile ForeignLib
flib
exeMainModuleName :: Executable -> Maybe ModuleName
exeMainModuleName :: Executable -> Maybe ModuleName
exeMainModuleName Executable{buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bnfo} =
[Maybe ModuleName] -> Maybe ModuleName
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum ([Maybe ModuleName] -> Maybe ModuleName)
-> [Maybe ModuleName] -> Maybe ModuleName
forall a b. (a -> b) -> a -> b
$ [Maybe ModuleName] -> [Maybe ModuleName]
forall a. [a] -> [a]
reverse ([Maybe ModuleName] -> [Maybe ModuleName])
-> [Maybe ModuleName] -> [Maybe ModuleName]
forall a b. (a -> b) -> a -> b
$ (FilePath -> Maybe ModuleName) -> [FilePath] -> [Maybe ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Maybe ModuleName
decodeMainIsArg ([FilePath] -> [Maybe ModuleName])
-> [FilePath] -> [Maybe ModuleName]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
ghcopts
where
ghcopts :: [FilePath]
ghcopts = CompilerFlavor -> BuildInfo -> [FilePath]
hcOptions CompilerFlavor
GHC BuildInfo
bnfo
findIsMainArgs :: [FilePath] -> [FilePath]
findIsMainArgs [] = []
findIsMainArgs (FilePath
"-main-is" : FilePath
arg : [FilePath]
rest) = FilePath
arg FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
rest
findIsMainArgs (FilePath
_ : [FilePath]
rest) = [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
rest
decodeMainIsArg :: String -> Maybe ModuleName
decodeMainIsArg :: FilePath -> Maybe ModuleName
decodeMainIsArg FilePath
arg
| FilePath -> (Char -> Bool) -> Bool
headOf FilePath
main_fn Char -> Bool
isLower =
ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (FilePath -> ModuleName
forall a. IsString a => FilePath -> a
ModuleName.fromString FilePath
main_mod)
| FilePath -> (Char -> Bool) -> Bool
headOf FilePath
arg Char -> Bool
isUpper
=
ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (FilePath -> ModuleName
forall a. IsString a => FilePath -> a
ModuleName.fromString FilePath
arg)
| Bool
otherwise
=
Maybe ModuleName
forall a. Maybe a
Nothing
where
headOf :: String -> (Char -> Bool) -> Bool
headOf :: FilePath -> (Char -> Bool) -> Bool
headOf FilePath
str Char -> Bool
pred' = (Char -> Bool) -> Maybe Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
pred' (FilePath -> Maybe Char
forall a. [a] -> Maybe a
safeHead FilePath
str)
(FilePath
main_mod, FilePath
main_fn) = FilePath -> (Char -> Bool) -> (FilePath, FilePath)
splitLongestPrefix FilePath
arg (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')
splitLongestPrefix :: String -> (Char -> Bool) -> (String, String)
splitLongestPrefix :: FilePath -> (Char -> Bool) -> (FilePath, FilePath)
splitLongestPrefix FilePath
str Char -> Bool
pred'
| FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
r_pre = (FilePath
str, [])
| Bool
otherwise = (FilePath -> FilePath
forall a. [a] -> [a]
reverse (FilePath -> FilePath
forall a. [a] -> [a]
safeTail FilePath
r_pre), FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
r_suf)
where
(FilePath
r_suf, FilePath
r_pre) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
pred' (FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
str)
data BuildSources = BuildSources
{ BuildSources -> [SymbolicPath Pkg 'File]
cSourcesFiles :: [SymbolicPath Pkg File]
, BuildSources -> [SymbolicPath Pkg 'File]
cxxSourceFiles :: [SymbolicPath Pkg File]
, BuildSources -> [SymbolicPath Pkg 'File]
inputSourceFiles :: [SymbolicPath Pkg File]
, BuildSources -> [ModuleName]
inputSourceModules :: [ModuleName]
}
gbuildSources
:: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageId
-> CabalSpecVersion
-> SymbolicPath Pkg (Dir Source)
-> GBuildMode
-> IO BuildSources
gbuildSources :: Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> PackageId
-> CabalSpecVersion
-> SymbolicPath Pkg ('Dir Source)
-> GBuildMode
-> IO BuildSources
gbuildSources Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir PackageId
pkgId CabalSpecVersion
specVer SymbolicPath Pkg ('Dir Source)
tmpDir GBuildMode
bm =
case GBuildMode
bm of
GBuildExe Executable
exe -> Executable -> IO BuildSources
exeSources Executable
exe
GReplExe [FilePath]
_ Executable
exe -> Executable -> IO BuildSources
exeSources Executable
exe
GBuildFLib ForeignLib
flib -> BuildSources -> IO BuildSources
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BuildSources -> IO BuildSources)
-> BuildSources -> IO BuildSources
forall a b. (a -> b) -> a -> b
$ ForeignLib -> BuildSources
flibSources ForeignLib
flib
GReplFLib [FilePath]
_ ForeignLib
flib -> BuildSources -> IO BuildSources
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BuildSources -> IO BuildSources)
-> BuildSources -> IO BuildSources
forall a b. (a -> b) -> a -> b
$ ForeignLib -> BuildSources
flibSources ForeignLib
flib
where
exeSources :: Executable -> IO BuildSources
exeSources :: Executable -> IO BuildSources
exeSources exe :: Executable
exe@Executable{buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bnfo, modulePath :: Executable -> RelativePath Source 'File
modulePath = RelativePath Source 'File
modPath} = do
main <- Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Source)]
-> RelativePath Source 'File
-> IO (SymbolicPath Pkg 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
findFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir (SymbolicPath Pkg ('Dir Source)
tmpDir SymbolicPath Pkg ('Dir Source)
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. a -> [a] -> [a]
: BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bnfo) RelativePath Source 'File
modPath
let mainModName = ModuleName -> Maybe ModuleName -> ModuleName
forall a. a -> Maybe a -> a
fromMaybe ModuleName
ModuleName.main (Maybe ModuleName -> ModuleName) -> Maybe ModuleName -> ModuleName
forall a b. (a -> b) -> a -> b
$ Executable -> Maybe ModuleName
exeMainModuleName Executable
exe
otherModNames = Executable -> [ModuleName]
exeModules Executable
exe
haskellMain = FilePath -> Bool
isHaskell (SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg 'File
main)
if haskellMain || pkgId == fakePackageId
then
if specVer < CabalSpecV2_0 && (mainModName `elem` otherModNames)
then do
warn verbosity $
"Enabling workaround for Main module '"
++ prettyShow mainModName
++ "' listed in 'other-modules' illegally!"
return
BuildSources
{ cSourcesFiles = cSources bnfo
, cxxSourceFiles = cxxSources bnfo
, inputSourceFiles = [main]
, inputSourceModules = filter (/= mainModName) $ exeModules exe
}
else
return
BuildSources
{ cSourcesFiles = cSources bnfo
, cxxSourceFiles = cxxSources bnfo
, inputSourceFiles = [main]
, inputSourceModules = exeModules exe
}
else
let (csf, cxxsf)
| isCxx (getSymbolicPath main) = (cSources bnfo, main : cxxSources bnfo)
| otherwise = (main : cSources bnfo, cxxSources bnfo)
in return
BuildSources
{ cSourcesFiles = csf
, cxxSourceFiles = cxxsf
, inputSourceFiles = []
, inputSourceModules = exeModules exe
}
flibSources :: ForeignLib -> BuildSources
flibSources :: ForeignLib -> BuildSources
flibSources flib :: ForeignLib
flib@ForeignLib{foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
bnfo} =
BuildSources
{ cSourcesFiles :: [SymbolicPath Pkg 'File]
cSourcesFiles = BuildInfo -> [SymbolicPath Pkg 'File]
cSources BuildInfo
bnfo
, cxxSourceFiles :: [SymbolicPath Pkg 'File]
cxxSourceFiles = BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources BuildInfo
bnfo
, inputSourceFiles :: [SymbolicPath Pkg 'File]
inputSourceFiles = []
, inputSourceModules :: [ModuleName]
inputSourceModules = ForeignLib -> [ModuleName]
foreignLibModules ForeignLib
flib
}
isCxx :: FilePath -> Bool
isCxx :: FilePath -> Bool
isCxx FilePath
fp = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (FilePath -> FilePath
takeExtension FilePath
fp) [FilePath
".cpp", FilePath
".cxx", FilePath
".c++"]
isHaskell :: FilePath -> Bool
isHaskell :: FilePath -> Bool
isHaskell FilePath
fp = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (FilePath -> FilePath
takeExtension FilePath
fp) [FilePath
".hs", FilePath
".lhs"]
gbuild
:: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild :: Verbosity
-> Flag ParStrat
-> PackageDescription
-> LocalBuildInfo
-> GBuildMode
-> ComponentLocalBuildInfo
-> IO ()
gbuild Verbosity
verbosity Flag ParStrat
numJobs PackageDescription
pkg_descr LocalBuildInfo
lbi GBuildMode
bm ComponentLocalBuildInfo
clbi = do
(ghcjsProg, _) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
ghcjsProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
let replFlags = case GBuildMode
bm of
GReplExe [FilePath]
flags Executable
_ -> [FilePath]
flags
GReplFLib [FilePath]
flags ForeignLib
_ -> [FilePath]
flags
GBuildExe{} -> [FilePath]
forall a. Monoid a => a
mempty
GBuildFLib{} -> [FilePath]
forall a. Monoid a => a
mempty
comp = LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi
platform = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
runGhcProg = Verbosity
-> ConfiguredProgram
-> Compiler
-> Platform
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> GhcOptions
-> IO ()
runGHC Verbosity
verbosity ConfiguredProgram
ghcjsProg Compiler
comp Platform
platform Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
let (bnfo, threaded) = case bm of
GBuildFLib ForeignLib
_ -> BuildInfo -> (BuildInfo, Bool)
popThreadedFlag (GBuildMode -> BuildInfo
gbuildInfo GBuildMode
bm)
GBuildMode
_ -> (GBuildMode -> BuildInfo
gbuildInfo GBuildMode
bm, Bool
False)
let targetName = LocalBuildInfo -> GBuildMode -> FilePath
gbuildTargetName LocalBuildInfo
lbi GBuildMode
bm
targetDir = LocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
buildDir LocalBuildInfo
lbi SymbolicPath Pkg ('Dir Build)
-> RelativePath Build c3 -> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath Build c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx (GBuildMode -> FilePath
gbuildName GBuildMode
bm)
tmpDir = SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 0))
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
targetDir SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 0))
-> RelativePath (ZonkAny 0) c3
-> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath (ZonkAny 0) c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx (GBuildMode -> FilePath
gbuildName GBuildMode
bm FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp")
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
createDirectoryIfMissingVerbose verbosity True $ i targetDir
createDirectoryIfMissingVerbose verbosity True $ i tmpDir
let isCoverageEnabled = LocalBuildInfo -> Bool
exeCoverage LocalBuildInfo
lbi
hpcdir Way
way
| GBuildMode -> Bool
gbuildIsRepl GBuildMode
bm = Flag (SymbolicPath Pkg ('Dir Mix))
forall a. Monoid a => a
mempty
| Bool
isCoverageEnabled = SymbolicPath Pkg ('Dir Mix) -> Flag (SymbolicPath Pkg ('Dir Mix))
forall a. a -> Flag a
toFlag (SymbolicPath Pkg ('Dir Mix) -> Flag (SymbolicPath Pkg ('Dir Mix)))
-> SymbolicPath Pkg ('Dir Mix)
-> Flag (SymbolicPath Pkg ('Dir Mix))
forall a b. (a -> b) -> a -> b
$ SymbolicPath Pkg ('Dir Dist) -> Way -> SymbolicPath Pkg ('Dir Mix)
Hpc.mixDir (SymbolicPath Pkg ('Dir Build)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
tmpDir SymbolicPath Pkg ('Dir Build)
-> SymbolicPathX 'OnlyRelative Build ('Dir Dist)
-> SymbolicPath Pkg ('Dir Dist)
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative Build ('Dir Artifacts)
-> SymbolicPathX 'OnlyRelative Build ('Dir Dist)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPathX 'OnlyRelative Build ('Dir Artifacts)
extraCompilationArtifacts) Way
way
| Bool
otherwise = Flag (SymbolicPath Pkg ('Dir Mix))
forall a. Monoid a => a
mempty
rpaths <- getRPaths lbi clbi
buildSources <- gbuildSources verbosity mbWorkDir (package pkg_descr) (specVersion pkg_descr) tmpDir bm
let cSrcs = BuildSources -> [SymbolicPath Pkg 'File]
cSourcesFiles BuildSources
buildSources
cxxSrcs = BuildSources -> [SymbolicPath Pkg 'File]
cxxSourceFiles BuildSources
buildSources
inputFiles = BuildSources -> [SymbolicPath Pkg 'File]
inputSourceFiles BuildSources
buildSources
inputModules = BuildSources -> [ModuleName]
inputSourceModules BuildSources
buildSources
isGhcDynamic = Compiler -> Bool
isDynamic Compiler
comp
dynamicTooSupported = Compiler -> Bool
supportsDynamicToo Compiler
comp
cObjs = (SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map ((SymbolicPath Pkg 'File -> FilePath -> SymbolicPath Pkg 'File
forall (allowAbsolute :: AllowAbsolute) from.
SymbolicPathX allowAbsolute from 'File
-> FilePath -> SymbolicPathX allowAbsolute from 'File
`replaceExtensionSymbolicPath` FilePath
objExtension)) [SymbolicPath Pkg 'File]
cSrcs
cxxObjs = (SymbolicPath Pkg 'File -> SymbolicPath Pkg 'File)
-> [SymbolicPath Pkg 'File] -> [SymbolicPath Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map ((SymbolicPath Pkg 'File -> FilePath -> SymbolicPath Pkg 'File
forall (allowAbsolute :: AllowAbsolute) from.
SymbolicPathX allowAbsolute from 'File
-> FilePath -> SymbolicPathX allowAbsolute from 'File
`replaceExtensionSymbolicPath` FilePath
objExtension)) [SymbolicPath Pkg 'File]
cxxSrcs
needDynamic = LocalBuildInfo -> GBuildMode -> Bool
gbuildNeedDynamic LocalBuildInfo
lbi GBuildMode
bm
needProfiling = LocalBuildInfo -> Bool
withProfExe LocalBuildInfo
lbi
buildRunner = case ComponentLocalBuildInfo
clbi of
LibComponentLocalBuildInfo{} -> Bool
False
FLibComponentLocalBuildInfo{} -> Bool
False
ExeComponentLocalBuildInfo{} -> Bool
True
TestComponentLocalBuildInfo{} -> Bool
True
BenchComponentLocalBuildInfo{} -> Bool
True
baseOpts =
(Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir (ZonkAny 3))
-> GhcOptions
forall build.
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
componentGhcOptions Verbosity
verbosity LocalBuildInfo
lbi BuildInfo
bnfo ComponentLocalBuildInfo
clbi SymbolicPath Pkg ('Dir (ZonkAny 3))
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
tmpDir)
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptMode = toFlag GhcModeMake
, ghcOptInputFiles =
toNubListR $
if package pkg_descr == fakePackageId
then filter (isHaskell . getSymbolicPath) inputFiles
else inputFiles
, ghcOptInputScripts =
toNubListR $
if package pkg_descr == fakePackageId
then filter (not . isHaskell . getSymbolicPath) inputFiles
else []
, ghcOptInputModules = toNubListR inputModules
,
ghcOptExtra =
if buildRunner
then ["-build-runner"]
else mempty
}
staticOpts =
GhcOptions
baseOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcStaticOnly
, ghcOptHPCDir = hpcdir Hpc.Vanilla
}
profOpts =
GhcOptions
baseOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptProfilingMode = toFlag True
, ghcOptProfilingAuto =
Internal.profDetailLevelFlag
False
(withProfExeDetail lbi)
, ghcOptHiSuffix = toFlag "p_hi"
, ghcOptObjSuffix = toFlag "p_o"
, ghcOptExtra = hcProfOptions GHC bnfo
, ghcOptHPCDir = hpcdir Hpc.Prof
}
dynOpts =
GhcOptions
baseOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcDynamicOnly
,
ghcOptFPic = toFlag True
, ghcOptHiSuffix = toFlag "dyn_hi"
, ghcOptObjSuffix = toFlag "dyn_o"
, ghcOptExtra = hcOptions GHC bnfo ++ hcSharedOptions GHC bnfo
, ghcOptHPCDir = hpcdir Hpc.Dyn
}
dynTooOpts =
GhcOptions
staticOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcStaticAndDynamic
, ghcOptDynHiSuffix = toFlag "dyn_hi"
, ghcOptDynObjSuffix = toFlag "dyn_o"
, ghcOptHPCDir = hpcdir Hpc.Dyn
}
linkerOpts =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptLinkOptions = PD.ldOptions bnfo
, ghcOptLinkLibs = extraLibs bnfo
, ghcOptLinkLibPath = toNubListR $ extraLibDirs bnfo
, ghcOptLinkFrameworks =
toNubListR $
map getSymbolicPath $
PD.frameworks bnfo
, ghcOptLinkFrameworkDirs =
toNubListR $
PD.extraFrameworkDirs bnfo
, ghcOptInputFiles =
toNubListR
[makeSymbolicPath $ getSymbolicPath tmpDir </> getSymbolicPath x | x <- cObjs ++ cxxObjs]
}
dynLinkerOpts =
GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptRPaths = rpaths
}
replOpts =
GhcOptions
baseOpts
{ ghcOptExtra =
Internal.filterGhciFlags
(ghcOptExtra baseOpts)
<> replFlags
}
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
linkerOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptMode = toFlag GhcModeInteractive
, ghcOptOptimisation = toFlag GhcNoOptimisation
}
commonOpts
| Bool
needProfiling = GhcOptions
profOpts
| Bool
needDynamic = GhcOptions
dynOpts
| Bool
otherwise = GhcOptions
staticOpts
compileOpts
| Bool
useDynToo = GhcOptions
dynTooOpts
| Bool
otherwise = GhcOptions
commonOpts
withStaticExe = Bool -> Bool
not Bool
needProfiling Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
needDynamic
doingTH = BuildInfo -> Bool
usesTemplateHaskellOrQQ BuildInfo
bnfo
useDynToo =
Bool
dynamicTooSupported
Bool -> Bool -> Bool
&& Bool
isGhcDynamic
Bool -> Bool -> Bool
&& Bool
doingTH
Bool -> Bool -> Bool
&& Bool
withStaticExe
Bool -> Bool -> Bool
&& [FilePath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (CompilerFlavor -> BuildInfo -> [FilePath]
hcSharedOptions CompilerFlavor
GHC BuildInfo
bnfo)
compileTHOpts
| Bool
isGhcDynamic = GhcOptions
dynOpts
| Bool
otherwise = GhcOptions
staticOpts
compileForTH
| GBuildMode -> Bool
gbuildIsRepl GBuildMode
bm = Bool
False
| Bool
useDynToo = Bool
False
| Bool
isGhcDynamic = Bool
doingTH Bool -> Bool -> Bool
&& (Bool
needProfiling Bool -> Bool -> Bool
|| Bool
withStaticExe)
| Bool
otherwise = Bool
doingTH Bool -> Bool -> Bool
&& (Bool
needProfiling Bool -> Bool -> Bool
|| Bool
needDynamic)
when compileForTH $
runGhcProg
compileTHOpts
{ ghcOptNoLink = toFlag True
, ghcOptNumJobs = numJobs
}
unless
( (null inputFiles && null inputModules)
|| gbuildIsRepl bm
)
$ runGhcProg
compileOpts
{ ghcOptNoLink = toFlag True
, ghcOptNumJobs = numJobs
}
unless (null cxxSrcs) $ do
info verbosity "Building C++ Sources..."
sequence_
[ do
let baseCxxOpts =
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir Artifacts)
-> SymbolicPath Pkg 'File
-> GhcOptions
Internal.componentCxxGhcOptions
Verbosity
verbosity
LocalBuildInfo
lbi
BuildInfo
bnfo
ComponentLocalBuildInfo
clbi
SymbolicPath Pkg ('Dir Artifacts)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
tmpDir
SymbolicPath Pkg 'File
filename
vanillaCxxOpts =
if Bool
isGhcDynamic
then
GhcOptions
baseCxxOpts{ghcOptFPic = toFlag True}
else GhcOptions
baseCxxOpts
profCxxOpts =
GhcOptions
vanillaCxxOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptProfilingMode = toFlag True
}
sharedCxxOpts =
GhcOptions
vanillaCxxOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptFPic = toFlag True
, ghcOptDynLinkMode = toFlag GhcDynamicOnly
}
opts
| Bool
needProfiling = GhcOptions
profCxxOpts
| Bool
needDynamic = GhcOptions
sharedCxxOpts
| Bool
otherwise = GhcOptions
vanillaCxxOpts
odir = Flag (SymbolicPath Pkg ('Dir Artifacts))
-> SymbolicPath Pkg ('Dir Artifacts)
forall a. WithCallStack (Flag a -> a)
fromFlag (GhcOptions -> Flag (SymbolicPath Pkg ('Dir Artifacts))
ghcOptObjDir GhcOptions
opts)
createDirectoryIfMissingVerbose verbosity True (i odir)
needsRecomp <- checkNeedsRecompilation mbWorkDir filename opts
when needsRecomp $
runGhcProg opts
| filename <- cxxSrcs
]
unless (null cSrcs) $ do
info verbosity "Building C Sources..."
sequence_
[ do
let baseCcOpts =
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir Artifacts)
-> SymbolicPath Pkg 'File
-> GhcOptions
Internal.componentCcGhcOptions
Verbosity
verbosity
LocalBuildInfo
lbi
BuildInfo
bnfo
ComponentLocalBuildInfo
clbi
SymbolicPath Pkg ('Dir Artifacts)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
tmpDir
SymbolicPath Pkg 'File
filename
vanillaCcOpts =
if Bool
isGhcDynamic
then
GhcOptions
baseCcOpts{ghcOptFPic = toFlag True}
else GhcOptions
baseCcOpts
profCcOpts =
GhcOptions
vanillaCcOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptProfilingMode = toFlag True
}
sharedCcOpts =
GhcOptions
vanillaCcOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptFPic = toFlag True
, ghcOptDynLinkMode = toFlag GhcDynamicOnly
}
opts
| Bool
needProfiling = GhcOptions
profCcOpts
| Bool
needDynamic = GhcOptions
sharedCcOpts
| Bool
otherwise = GhcOptions
vanillaCcOpts
odir = Flag (SymbolicPath Pkg ('Dir Artifacts))
-> SymbolicPath Pkg ('Dir Artifacts)
forall a. WithCallStack (Flag a -> a)
fromFlag (GhcOptions -> Flag (SymbolicPath Pkg ('Dir Artifacts))
ghcOptObjDir GhcOptions
opts)
createDirectoryIfMissingVerbose verbosity True (i odir)
needsRecomp <- checkNeedsRecompilation mbWorkDir filename opts
when needsRecomp $
runGhcProg opts
| filename <- cSrcs
]
case bm of
GReplExe [FilePath]
_ Executable
_ -> GhcOptions -> IO ()
runGhcProg GhcOptions
replOpts
GReplFLib [FilePath]
_ ForeignLib
_ -> GhcOptions -> IO ()
runGhcProg GhcOptions
replOpts
GBuildExe Executable
_ -> do
let linkOpts :: GhcOptions
linkOpts =
GhcOptions
commonOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
linkerOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptLinkNoHsMain = toFlag (null inputFiles)
}
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` (if LocalBuildInfo -> Bool
withDynExe LocalBuildInfo
lbi then GhcOptions
dynLinkerOpts else GhcOptions
forall a. Monoid a => a
mempty)
Verbosity -> FilePath -> IO ()
info Verbosity
verbosity FilePath
"Linking..."
let target :: SymbolicPathX 'AllowAbsolute Pkg c3
target = SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 5))
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
targetDir SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 5))
-> RelativePath (ZonkAny 5) c3
-> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath (ZonkAny 5) c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx FilePath
targetName
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Compiler -> Version
compilerVersion Compiler
comp Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< [Int] -> Version
mkVersion [Int
7, Int
7]) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let targetPath :: FilePath
targetPath = SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 6) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 6)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
target
e <- FilePath -> IO Bool
doesFileExist FilePath
targetPath
when e (removeFile targetPath)
GhcOptions -> IO ()
runGhcProg GhcOptions
linkOpts{ghcOptOutputFile = toFlag target}
GBuildFLib ForeignLib
flib -> do
let rtsInfo :: RtsInfo
rtsInfo = LocalBuildInfo -> RtsInfo
extractRtsInfo LocalBuildInfo
lbi
rtsOptLinkLibs :: [FilePath]
rtsOptLinkLibs =
[ if Bool
needDynamic
then
if Bool
threaded
then DynamicRtsInfo -> FilePath
dynRtsThreadedLib (RtsInfo -> DynamicRtsInfo
rtsDynamicInfo RtsInfo
rtsInfo)
else DynamicRtsInfo -> FilePath
dynRtsVanillaLib (RtsInfo -> DynamicRtsInfo
rtsDynamicInfo RtsInfo
rtsInfo)
else
if Bool
threaded
then StaticRtsInfo -> FilePath
statRtsThreadedLib (RtsInfo -> StaticRtsInfo
rtsStaticInfo RtsInfo
rtsInfo)
else StaticRtsInfo -> FilePath
statRtsVanillaLib (RtsInfo -> StaticRtsInfo
rtsStaticInfo RtsInfo
rtsInfo)
]
linkOpts :: GhcOptions
linkOpts = case ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib of
ForeignLibType
ForeignLibNativeShared ->
GhcOptions
commonOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
linkerOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
dynLinkerOpts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptLinkNoHsMain = toFlag True
, ghcOptShared = toFlag True
, ghcOptLinkLibs = rtsOptLinkLibs
, ghcOptLinkLibPath = toNubListR $ map makeSymbolicPath $ rtsLibPaths rtsInfo
, ghcOptFPic = toFlag True
, ghcOptLinkModDefFiles = toNubListR $ fmap getSymbolicPath $ gbuildModDefFiles bm
}
ForeignLibType
ForeignLibNativeStatic ->
FilePath -> GhcOptions
forall a. FilePath -> a
cabalBug FilePath
"static libraries not yet implemented"
ForeignLibType
ForeignLibTypeUnknown ->
FilePath -> GhcOptions
forall a. FilePath -> a
cabalBug FilePath
"unknown foreign lib type"
Verbosity -> FilePath -> IO ()
info Verbosity
verbosity FilePath
"Linking..."
let buildName :: FilePath
buildName = LocalBuildInfo -> ForeignLib -> FilePath
flibBuildName LocalBuildInfo
lbi ForeignLib
flib
buildFile :: SymbolicPathX 'AllowAbsolute Pkg c3
buildFile = SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 7))
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
targetDir SymbolicPathX 'AllowAbsolute Pkg ('Dir (ZonkAny 7))
-> RelativePath (ZonkAny 7) c3
-> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath (ZonkAny 7) c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx FilePath
buildName
GhcOptions -> IO ()
runGhcProg GhcOptions
linkOpts{ghcOptOutputFile = toFlag buildFile}
FilePath -> FilePath -> IO ()
renameFile (SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 8) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 8)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
buildFile) (SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 9) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 9)
forall {c3 :: FileOrDir}. SymbolicPathX 'AllowAbsolute Pkg c3
targetDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
targetName)
data DynamicRtsInfo = DynamicRtsInfo
{ DynamicRtsInfo -> FilePath
dynRtsVanillaLib :: FilePath
, DynamicRtsInfo -> FilePath
dynRtsThreadedLib :: FilePath
, DynamicRtsInfo -> FilePath
dynRtsDebugLib :: FilePath
, DynamicRtsInfo -> FilePath
dynRtsEventlogLib :: FilePath
, DynamicRtsInfo -> FilePath
dynRtsThreadedDebugLib :: FilePath
, DynamicRtsInfo -> FilePath
dynRtsThreadedEventlogLib :: FilePath
}
data StaticRtsInfo = StaticRtsInfo
{ StaticRtsInfo -> FilePath
statRtsVanillaLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsThreadedLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsDebugLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsEventlogLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsThreadedDebugLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsThreadedEventlogLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsProfilingLib :: FilePath
, StaticRtsInfo -> FilePath
statRtsThreadedProfilingLib :: FilePath
}
data RtsInfo = RtsInfo
{ RtsInfo -> DynamicRtsInfo
rtsDynamicInfo :: DynamicRtsInfo
, RtsInfo -> StaticRtsInfo
rtsStaticInfo :: StaticRtsInfo
, RtsInfo -> [FilePath]
rtsLibPaths :: [FilePath]
}
extractRtsInfo :: LocalBuildInfo -> RtsInfo
LocalBuildInfo
lbi =
case InstalledPackageIndex
-> PackageName -> [(Version, [InstalledPackageInfo])]
forall a. PackageIndex a -> PackageName -> [(Version, [a])]
PackageIndex.lookupPackageName (LocalBuildInfo -> InstalledPackageIndex
installedPkgs LocalBuildInfo
lbi) (FilePath -> PackageName
mkPackageName FilePath
"rts") of
[(Version
_, [InstalledPackageInfo
rts])] -> InstalledPackageInfo -> RtsInfo
aux InstalledPackageInfo
rts
[(Version, [InstalledPackageInfo])]
_otherwise -> FilePath -> RtsInfo
forall a. HasCallStack => FilePath -> a
error FilePath
"No (or multiple) ghc rts package is registered"
where
aux :: InstalledPackageInfo -> RtsInfo
aux :: InstalledPackageInfo -> RtsInfo
aux InstalledPackageInfo
rts =
RtsInfo
{ rtsDynamicInfo :: DynamicRtsInfo
rtsDynamicInfo =
DynamicRtsInfo
{ dynRtsVanillaLib :: FilePath
dynRtsVanillaLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts"
, dynRtsThreadedLib :: FilePath
dynRtsThreadedLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts_thr"
, dynRtsDebugLib :: FilePath
dynRtsDebugLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts_debug"
, dynRtsEventlogLib :: FilePath
dynRtsEventlogLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts_l"
, dynRtsThreadedDebugLib :: FilePath
dynRtsThreadedDebugLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts_thr_debug"
, dynRtsThreadedEventlogLib :: FilePath
dynRtsThreadedEventlogLib = FilePath -> FilePath
withGhcVersion FilePath
"HSrts_thr_l"
}
, rtsStaticInfo :: StaticRtsInfo
rtsStaticInfo =
StaticRtsInfo
{ statRtsVanillaLib :: FilePath
statRtsVanillaLib = FilePath
"HSrts"
, statRtsThreadedLib :: FilePath
statRtsThreadedLib = FilePath
"HSrts_thr"
, statRtsDebugLib :: FilePath
statRtsDebugLib = FilePath
"HSrts_debug"
, statRtsEventlogLib :: FilePath
statRtsEventlogLib = FilePath
"HSrts_l"
, statRtsThreadedDebugLib :: FilePath
statRtsThreadedDebugLib = FilePath
"HSrts_thr_debug"
, statRtsThreadedEventlogLib :: FilePath
statRtsThreadedEventlogLib = FilePath
"HSrts_thr_l"
, statRtsProfilingLib :: FilePath
statRtsProfilingLib = FilePath
"HSrts_p"
, statRtsThreadedProfilingLib :: FilePath
statRtsThreadedProfilingLib = FilePath
"HSrts_thr_p"
}
, rtsLibPaths :: [FilePath]
rtsLibPaths = InstalledPackageInfo -> [FilePath]
InstalledPackageInfo.libraryDirs InstalledPackageInfo
rts
}
withGhcVersion :: FilePath -> FilePath
withGhcVersion = (FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (FilePath
"-ghc" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (Compiler -> Version
compilerVersion (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))))
checkNeedsRecompilation
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg File
-> GhcOptions
-> IO Bool
checkNeedsRecompilation :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> IO Bool
checkNeedsRecompilation Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts =
SymbolicPath Pkg 'File -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i SymbolicPath Pkg 'File
filename FilePath -> FilePath -> IO Bool
`moreRecentFile` FilePath
oname
where
oname :: FilePath
oname = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> FilePath
getObjectFileName Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
getObjectFileName
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg File
-> GhcOptions
-> FilePath
getObjectFileName :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> FilePath
getObjectFileName Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts = FilePath
oname
where
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
odir :: FilePath
odir = SymbolicPath Pkg ('Dir Artifacts) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i (SymbolicPath Pkg ('Dir Artifacts) -> FilePath)
-> SymbolicPath Pkg ('Dir Artifacts) -> FilePath
forall a b. (a -> b) -> a -> b
$ Flag (SymbolicPath Pkg ('Dir Artifacts))
-> SymbolicPath Pkg ('Dir Artifacts)
forall a. WithCallStack (Flag a -> a)
fromFlag (GhcOptions -> Flag (SymbolicPath Pkg ('Dir Artifacts))
ghcOptObjDir GhcOptions
opts)
oext :: FilePath
oext = FilePath -> Flag FilePath -> FilePath
forall a. a -> Flag a -> a
fromFlagOrDefault FilePath
"o" (GhcOptions -> Flag FilePath
ghcOptObjSuffix GhcOptions
opts)
oname :: FilePath
oname = FilePath
odir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> FilePath -> FilePath
replaceExtension (SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg 'File
filename) FilePath
oext
getRPaths
:: LocalBuildInfo
-> ComponentLocalBuildInfo
-> IO (NubListR FilePath)
getRPaths :: LocalBuildInfo -> ComponentLocalBuildInfo -> IO (NubListR FilePath)
getRPaths LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi | OS -> Bool
supportRPaths OS
hostOS = do
libraryPaths <- Bool
-> Bool
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> IO [FilePath]
depLibraryPaths Bool
False (LocalBuildInfo -> Bool
relocatable LocalBuildInfo
lbi) LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
let hostPref = case OS
hostOS of
OS
OSX -> FilePath
"@loader_path"
OS
_ -> FilePath
"$ORIGIN"
relPath FilePath
p = if FilePath -> Bool
isRelative FilePath
p then FilePath
hostPref FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
p else FilePath
p
rpaths = [FilePath] -> NubListR FilePath
forall a. Ord a => [a] -> NubListR a
toNubListR ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
relPath [FilePath]
libraryPaths)
return rpaths
where
(Platform Arch
_ OS
hostOS) = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
compid :: CompilerId
compid = Compiler -> CompilerId
compilerId (Compiler -> CompilerId)
-> (LocalBuildInfo -> Compiler) -> LocalBuildInfo -> CompilerId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LocalBuildInfo -> Compiler
compiler (LocalBuildInfo -> CompilerId) -> LocalBuildInfo -> CompilerId
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo
lbi
supportRPaths :: OS -> Bool
supportRPaths OS
Linux = Bool
True
supportRPaths OS
Windows = Bool
False
supportRPaths OS
OSX = Bool
True
supportRPaths OS
FreeBSD =
case CompilerId
compid of
CompilerId CompilerFlavor
GHC Version
ver | Version
ver Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
7, Int
10, Int
2] -> Bool
True
CompilerId
_ -> Bool
False
supportRPaths OS
OpenBSD = Bool
False
supportRPaths OS
NetBSD = Bool
False
supportRPaths OS
DragonFly = Bool
False
supportRPaths OS
Solaris = Bool
False
supportRPaths OS
AIX = Bool
False
supportRPaths OS
HPUX = Bool
False
supportRPaths OS
IRIX = Bool
False
supportRPaths OS
HaLVM = Bool
False
supportRPaths OS
IOS = Bool
False
supportRPaths OS
Android = Bool
False
supportRPaths OS
Ghcjs = Bool
False
supportRPaths OS
Wasi = Bool
False
supportRPaths OS
Hurd = Bool
True
supportRPaths OS
Haiku = Bool
False
supportRPaths (OtherOS FilePath
_) = Bool
False
getRPaths LocalBuildInfo
_ ComponentLocalBuildInfo
_ = NubListR FilePath -> IO (NubListR FilePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return NubListR FilePath
forall a. Monoid a => a
mempty
popThreadedFlag :: BuildInfo -> (BuildInfo, Bool)
popThreadedFlag :: BuildInfo -> (BuildInfo, Bool)
popThreadedFlag BuildInfo
bi =
( BuildInfo
bi{options = filterHcOptions (/= "-threaded") (options bi)}
, PerCompilerFlavor [FilePath] -> Bool
hasThreaded (BuildInfo -> PerCompilerFlavor [FilePath]
options BuildInfo
bi)
)
where
filterHcOptions
:: (String -> Bool)
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
filterHcOptions :: (FilePath -> Bool)
-> PerCompilerFlavor [FilePath] -> PerCompilerFlavor [FilePath]
filterHcOptions FilePath -> Bool
p (PerCompilerFlavor [FilePath]
ghc [FilePath]
ghcjs) =
[FilePath] -> [FilePath] -> PerCompilerFlavor [FilePath]
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor ((FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
p [FilePath]
ghc) [FilePath]
ghcjs
hasThreaded :: PerCompilerFlavor [String] -> Bool
hasThreaded :: PerCompilerFlavor [FilePath] -> Bool
hasThreaded (PerCompilerFlavor [FilePath]
ghc [FilePath]
_) = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem FilePath
"-threaded" [FilePath]
ghc
libAbiHash
:: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO String
libAbiHash :: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO FilePath
libAbiHash Verbosity
verbosity PackageDescription
_pkg_descr LocalBuildInfo
lbi Library
lib ComponentLocalBuildInfo
clbi = do
let
libBi :: BuildInfo
libBi = Library -> BuildInfo
libBuildInfo Library
lib
comp :: Compiler
comp = LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi
platform :: Platform
platform = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
vanillaArgs :: GhcOptions
vanillaArgs =
(Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir Build)
-> GhcOptions
forall build.
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
componentGhcOptions Verbosity
verbosity LocalBuildInfo
lbi BuildInfo
libBi ComponentLocalBuildInfo
clbi (LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi))
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptMode = toFlag GhcModeAbiHash
, ghcOptInputModules = toNubListR $ exposedModules lib
}
sharedArgs :: GhcOptions
sharedArgs =
GhcOptions
vanillaArgs
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptDynLinkMode = toFlag GhcDynamicOnly
, ghcOptFPic = toFlag True
, ghcOptHiSuffix = toFlag "js_dyn_hi"
, ghcOptObjSuffix = toFlag "js_dyn_o"
, ghcOptExtra = hcOptions GHC libBi ++ hcSharedOptions GHC libBi
}
profArgs :: GhcOptions
profArgs =
GhcOptions
vanillaArgs
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptProfilingMode = toFlag True
, ghcOptProfilingAuto =
Internal.profDetailLevelFlag
True
(withProfLibDetail lbi)
, ghcOptHiSuffix = toFlag "js_p_hi"
, ghcOptObjSuffix = toFlag "js_p_o"
, ghcOptExtra = hcProfOptions GHC libBi
}
ghcArgs :: GhcOptions
ghcArgs
| LocalBuildInfo -> Bool
withVanillaLib LocalBuildInfo
lbi = GhcOptions
vanillaArgs
| LocalBuildInfo -> Bool
withSharedLib LocalBuildInfo
lbi = GhcOptions
sharedArgs
| LocalBuildInfo -> Bool
withProfLib LocalBuildInfo
lbi = GhcOptions
profArgs
| Bool
otherwise = FilePath -> GhcOptions
forall a. HasCallStack => FilePath -> a
error FilePath
"libAbiHash: Can't find an enabled library way"
(ghcjsProg, _) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
ghcjsProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
hash <-
getProgramInvocationOutput
verbosity
=<< ghcInvocation verbosity ghcjsProg comp platform mbWorkDir ghcArgs
return (takeWhile (not . isSpace) hash)
componentGhcOptions
:: Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg (Dir build)
-> GhcOptions
componentGhcOptions :: forall build.
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
componentGhcOptions Verbosity
verbosity LocalBuildInfo
lbi BuildInfo
bi ComponentLocalBuildInfo
clbi SymbolicPath Pkg ('Dir build)
odir =
let opts :: GhcOptions
opts = Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
forall build.
Verbosity
-> LocalBuildInfo
-> BuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPath Pkg ('Dir build)
-> GhcOptions
Internal.componentGhcOptions Verbosity
verbosity LocalBuildInfo
lbi BuildInfo
bi ComponentLocalBuildInfo
clbi SymbolicPath Pkg ('Dir build)
odir
in GhcOptions
opts
{ ghcOptExtra = ghcOptExtra opts `mappend` hcOptions GHCJS bi
}
installExe
:: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> (FilePath, FilePath)
-> PackageDescription
-> Executable
-> IO ()
installExe :: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> (FilePath, FilePath)
-> PackageDescription
-> Executable
-> IO ()
installExe
Verbosity
verbosity
LocalBuildInfo
lbi
FilePath
binDir
FilePath
buildPref
(FilePath
progprefix, FilePath
progsuffix)
PackageDescription
_pkg
Executable
exe = do
Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
binDir
let exeName' :: FilePath
exeName' = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ Executable -> UnqualComponentName
exeName Executable
exe
exeFileName :: FilePath
exeFileName = FilePath
exeName'
fixedExeBaseName :: FilePath
fixedExeBaseName = FilePath
progprefix FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
exeName' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
progsuffix
installBinary :: FilePath -> IO ()
installBinary FilePath
dest = do
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> Program
-> ProgramDb
-> [FilePath]
-> IO ()
forall to.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir to))
-> Program
-> ProgramDb
-> [FilePath]
-> IO ()
runDbProgramCwd Verbosity
verbosity (LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi) Program
ghcjsProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi) ([FilePath] -> IO ()) -> [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$
[ FilePath
"--install-executable"
, FilePath
buildPref FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
exeName' FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
exeFileName
, FilePath
"-o"
, FilePath
dest
]
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ case (LocalBuildInfo -> Bool
stripExes LocalBuildInfo
lbi, Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
stripProgram (ProgramDb -> Maybe ConfiguredProgram)
-> ProgramDb -> Maybe ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi) of
(Bool
True, Just ConfiguredProgram
strip) -> [FilePath
"-strip-program", ConfiguredProgram -> FilePath
programPath ConfiguredProgram
strip]
(Bool, Maybe ConfiguredProgram)
_ -> []
FilePath -> IO ()
installBinary (FilePath
binDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
fixedExeBaseName)
installFLib
:: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> PackageDescription
-> ForeignLib
-> IO ()
installFLib :: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> PackageDescription
-> ForeignLib
-> IO ()
installFLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
targetDir FilePath
builtDir PackageDescription
_pkg ForeignLib
flib =
Bool -> FilePath -> FilePath -> FilePath -> IO ()
forall {p} {p} {p}.
PathLike p p FilePath =>
p -> p -> p -> p -> IO ()
install
(ForeignLib -> Bool
foreignLibIsShared ForeignLib
flib)
FilePath
builtDir
FilePath
targetDir
(LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib)
where
install :: p -> p -> p -> p -> IO ()
install p
_isShared p
srcDir p
dstDir p
name = do
let src :: FilePath
src = p
srcDir p -> p -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> p
name
dst :: FilePath
dst = p
dstDir p -> p -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> p
name
Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
targetDir
Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile Verbosity
verbosity FilePath
src FilePath
dst
installLib
:: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
installLib :: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
installLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
targetDir FilePath
dynlibTargetDir FilePath
_builtDir PackageDescription
_pkg Library
lib ComponentLocalBuildInfo
clbi = do
IO () -> IO ()
whenVanilla (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Suffix -> IO ()
copyModuleFiles (Suffix -> IO ()) -> Suffix -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Suffix
Suffix FilePath
"js_hi"
IO () -> IO ()
whenProf (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Suffix -> IO ()
copyModuleFiles (Suffix -> IO ()) -> Suffix -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Suffix
Suffix FilePath
"js_p_hi"
IO () -> IO ()
whenShared (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Suffix -> IO ()
copyModuleFiles (Suffix -> IO ()) -> Suffix -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Suffix
Suffix FilePath
"js_dyn_hi"
IO () -> IO ()
whenHasCode (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IO () -> IO ()
whenVanilla (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ SymbolicPath Pkg ('Dir Build) -> FilePath -> FilePath -> IO ()
forall {allowAbsolute :: AllowAbsolute} {from}.
SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath -> FilePath -> IO ()
installOrdinary SymbolicPath Pkg ('Dir Build)
builtDir' FilePath
targetDir (FilePath -> FilePath
toJSLibName (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
mkGenericStaticLibName (FilePath
l FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
f))
| FilePath
l <- UnitId -> FilePath
getHSLibraryName (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (BuildInfo -> [FilePath]
extraBundledLibs (Library -> BuildInfo
libBuildInfo Library
lib))
, FilePath
f <- FilePath
"" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
extraLibFlavours (Library -> BuildInfo
libBuildInfo Library
lib)
]
IO () -> IO ()
whenProf (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
SymbolicPath Pkg ('Dir Build) -> FilePath -> FilePath -> IO ()
forall {allowAbsolute :: AllowAbsolute} {from}.
SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath -> FilePath -> IO ()
installOrdinary SymbolicPath Pkg ('Dir Build)
builtDir' FilePath
targetDir (FilePath -> FilePath
toJSLibName FilePath
profileLibName)
IO () -> IO ()
whenShared (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ SymbolicPath Pkg ('Dir Build) -> FilePath -> FilePath -> IO ()
forall {allowAbsolute :: AllowAbsolute} {from}.
SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath -> FilePath -> IO ()
installShared
SymbolicPath Pkg ('Dir Build)
builtDir'
FilePath
dynlibTargetDir
(FilePath -> FilePath
toJSLibName (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Platform -> CompilerId -> FilePath -> FilePath
mkGenericSharedLibName Platform
platform CompilerId
compiler_id (FilePath
l FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
f))
| FilePath
l <- UnitId -> FilePath
getHSLibraryName UnitId
uid FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
extraBundledLibs (Library -> BuildInfo
libBuildInfo Library
lib)
, FilePath
f <- FilePath
"" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
extraDynLibFlavours (Library -> BuildInfo
libBuildInfo Library
lib)
]
where
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi
builtDir' :: SymbolicPath Pkg ('Dir Build)
builtDir' = LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
install :: Bool
-> Bool
-> SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath
-> FilePath
-> IO ()
install Bool
isShared Bool
isJS SymbolicPathX allowAbsolute Pkg ('Dir from)
srcDir FilePath
dstDir FilePath
name = do
let src :: FilePath
src = SymbolicPathX allowAbsolute Pkg (ZonkAny 11) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i (SymbolicPathX allowAbsolute Pkg (ZonkAny 11) -> FilePath)
-> SymbolicPathX allowAbsolute Pkg (ZonkAny 11) -> FilePath
forall a b. (a -> b) -> a -> b
$ SymbolicPathX allowAbsolute Pkg ('Dir from)
srcDir SymbolicPathX allowAbsolute Pkg ('Dir from)
-> RelativePath from (ZonkAny 11)
-> SymbolicPathX allowAbsolute Pkg (ZonkAny 11)
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath from (ZonkAny 11)
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx FilePath
name
dst :: FilePath
dst = FilePath
dstDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
name
Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
dstDir
if Bool
isShared
then Verbosity -> FilePath -> FilePath -> IO ()
installExecutableFile Verbosity
verbosity FilePath
src FilePath
dst
else Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile Verbosity
verbosity FilePath
src FilePath
dst
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (LocalBuildInfo -> Bool
stripLibs LocalBuildInfo
lbi Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
isJS) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Verbosity -> Platform -> ProgramDb -> FilePath -> IO ()
Strip.stripLib
Verbosity
verbosity
(LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi)
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
FilePath
dst
installOrdinary :: SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath -> FilePath -> IO ()
installOrdinary = Bool
-> Bool
-> SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath
-> FilePath
-> IO ()
forall {allowAbsolute :: AllowAbsolute} {from}.
Bool
-> Bool
-> SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath
-> FilePath
-> IO ()
install Bool
False Bool
True
installShared :: SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath -> FilePath -> IO ()
installShared = Bool
-> Bool
-> SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath
-> FilePath
-> IO ()
forall {allowAbsolute :: AllowAbsolute} {from}.
Bool
-> Bool
-> SymbolicPathX allowAbsolute Pkg ('Dir from)
-> FilePath
-> FilePath
-> IO ()
install Bool
True Bool
True
copyModuleFiles :: Suffix -> IO ()
copyModuleFiles Suffix
ext = do
files <- Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Build)]
-> [Suffix]
-> [ModuleName]
-> IO [(SymbolicPath Pkg ('Dir Build), RelativePath Build 'File)]
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> [Suffix]
-> [ModuleName]
-> IO
[(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File)]
findModuleFilesCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [SymbolicPath Pkg ('Dir Build)
builtDir'] [Suffix
ext] (Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi)
let files' = ((SymbolicPath Pkg ('Dir Build), RelativePath Build 'File)
-> (FilePath, FilePath))
-> [(SymbolicPath Pkg ('Dir Build), RelativePath Build 'File)]
-> [(FilePath, FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (SymbolicPath Pkg ('Dir Build) -> FilePath
forall (allowAbs :: AllowAbsolute) (to :: FileOrDir).
SymbolicPathX allowAbs Pkg to -> FilePath
i (SymbolicPath Pkg ('Dir Build) -> FilePath)
-> (RelativePath Build 'File -> FilePath)
-> (SymbolicPath Pkg ('Dir Build), RelativePath Build 'File)
-> (FilePath, FilePath)
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** RelativePath Build 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath) [(SymbolicPath Pkg ('Dir Build), RelativePath Build 'File)]
files
installOrdinaryFiles verbosity targetDir files'
compiler_id :: CompilerId
compiler_id = Compiler -> CompilerId
compilerId (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
platform :: Platform
platform = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
uid :: UnitId
uid = ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi
profileLibName :: FilePath
profileLibName = UnitId -> FilePath
mkProfLibName UnitId
uid
hasLib :: Bool
hasLib =
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
[ModuleName] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi)
Bool -> Bool -> Bool
&& [SymbolicPath Pkg 'File] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [SymbolicPath Pkg 'File]
cSources (Library -> BuildInfo
libBuildInfo Library
lib))
Bool -> Bool -> Bool
&& [SymbolicPath Pkg 'File] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [SymbolicPath Pkg 'File]
cxxSources (Library -> BuildInfo
libBuildInfo Library
lib))
Bool -> Bool -> Bool
&& [SymbolicPath Pkg 'File] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (BuildInfo -> [SymbolicPath Pkg 'File]
jsSources (Library -> BuildInfo
libBuildInfo Library
lib))
has_code :: Bool
has_code = Bool -> Bool
not (ComponentLocalBuildInfo -> Bool
componentIsIndefinite ComponentLocalBuildInfo
clbi)
whenHasCode :: IO () -> IO ()
whenHasCode = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
has_code
whenVanilla :: IO () -> IO ()
whenVanilla = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
hasLib Bool -> Bool -> Bool
&& LocalBuildInfo -> Bool
withVanillaLib LocalBuildInfo
lbi)
whenProf :: IO () -> IO ()
whenProf = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
hasLib Bool -> Bool -> Bool
&& LocalBuildInfo -> Bool
withProfLib LocalBuildInfo
lbi Bool -> Bool -> Bool
&& Bool
has_code)
whenShared :: IO () -> IO ()
whenShared = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
hasLib Bool -> Bool -> Bool
&& LocalBuildInfo -> Bool
withSharedLib LocalBuildInfo
lbi Bool -> Bool -> Bool
&& Bool
has_code)
adjustExts :: String -> String -> GhcOptions -> GhcOptions
adjustExts :: FilePath -> FilePath -> GhcOptions -> GhcOptions
adjustExts FilePath
hiSuf FilePath
objSuf GhcOptions
opts =
GhcOptions
opts
GhcOptions -> GhcOptions -> GhcOptions
forall a. Monoid a => a -> a -> a
`mappend` GhcOptions
forall a. Monoid a => a
mempty
{ ghcOptHiSuffix = toFlag hiSuf
, ghcOptObjSuffix = toFlag objSuf
}
isDynamic :: Compiler -> Bool
isDynamic :: Compiler -> Bool
isDynamic = FilePath -> Compiler -> Bool
Internal.ghcLookupProperty FilePath
"GHC Dynamic"
supportsDynamicToo :: Compiler -> Bool
supportsDynamicToo :: Compiler -> Bool
supportsDynamicToo = FilePath -> Compiler -> Bool
Internal.ghcLookupProperty FilePath
"Support dynamic-too"
withExt :: FilePath -> String -> FilePath
withExt :: FilePath -> FilePath -> FilePath
withExt FilePath
fp FilePath
ext = FilePath
fp FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> if FilePath -> FilePath
takeExtension FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= (Char
'.' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
ext) then FilePath
ext else FilePath
""
findGhcjsGhcVersion :: Verbosity -> FilePath -> IO (Maybe Version)
findGhcjsGhcVersion :: Verbosity -> FilePath -> IO (Maybe Version)
findGhcjsGhcVersion Verbosity
verbosity FilePath
pgm =
FilePath
-> (FilePath -> FilePath)
-> Verbosity
-> FilePath
-> IO (Maybe Version)
findProgramVersion FilePath
"--numeric-ghc-version" FilePath -> FilePath
forall a. a -> a
id Verbosity
verbosity FilePath
pgm
findGhcjsPkgGhcjsVersion :: Verbosity -> FilePath -> IO (Maybe Version)
findGhcjsPkgGhcjsVersion :: Verbosity -> FilePath -> IO (Maybe Version)
findGhcjsPkgGhcjsVersion Verbosity
verbosity FilePath
pgm =
FilePath
-> (FilePath -> FilePath)
-> Verbosity
-> FilePath
-> IO (Maybe Version)
findProgramVersion FilePath
"--numeric-ghcjs-version" FilePath -> FilePath
forall a. a -> a
id Verbosity
verbosity FilePath
pgm
hcPkgInfo :: ProgramDb -> HcPkg.HcPkgInfo
hcPkgInfo :: ProgramDb -> HcPkgInfo
hcPkgInfo ProgramDb
progdb =
HcPkg.HcPkgInfo
{ hcPkgProgram :: ConfiguredProgram
HcPkg.hcPkgProgram = ConfiguredProgram
ghcjsPkgProg
, noPkgDbStack :: Bool
HcPkg.noPkgDbStack = Bool
False
, noVerboseFlag :: Bool
HcPkg.noVerboseFlag = Bool
False
, flagPackageConf :: Bool
HcPkg.flagPackageConf = Bool
False
, supportsDirDbs :: Bool
HcPkg.supportsDirDbs = Bool
True
, requiresDirDbs :: Bool
HcPkg.requiresDirDbs = Version
ver Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= Version
v7_10
, nativeMultiInstance :: Bool
HcPkg.nativeMultiInstance = Version
ver Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= Version
v7_10
, recacheMultiInstance :: Bool
HcPkg.recacheMultiInstance = Bool
True
, suppressFilesCheck :: Bool
HcPkg.suppressFilesCheck = Bool
True
}
where
v7_10 :: Version
v7_10 = [Int] -> Version
mkVersion [Int
7, Int
10]
ghcjsPkgProg :: ConfiguredProgram
ghcjsPkgProg = ConfiguredProgram -> Maybe ConfiguredProgram -> ConfiguredProgram
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ConfiguredProgram
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.hcPkgInfo no ghcjs program") (Maybe ConfiguredProgram -> ConfiguredProgram)
-> Maybe ConfiguredProgram -> ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
ghcjsPkgProgram ProgramDb
progdb
ver :: Version
ver = Version -> Maybe Version -> Version
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> Version
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.hcPkgInfo no ghcjs version") (Maybe Version -> Version) -> Maybe Version -> Version
forall a b. (a -> b) -> a -> b
$ ConfiguredProgram -> Maybe Version
programVersion ConfiguredProgram
ghcjsPkgProg
registerPackage
:: Verbosity
-> ProgramDb
-> Maybe (SymbolicPath CWD (Dir from))
-> PackageDBStackS from
-> InstalledPackageInfo
-> HcPkg.RegisterOptions
-> IO ()
registerPackage :: forall from.
Verbosity
-> ProgramDb
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBStackS from
-> InstalledPackageInfo
-> RegisterOptions
-> IO ()
registerPackage Verbosity
verbosity ProgramDb
progdb Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir PackageDBStackS from
packageDbs InstalledPackageInfo
installedPkgInfo RegisterOptions
registerOptions =
HcPkgInfo
-> Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBStackS from
-> InstalledPackageInfo
-> RegisterOptions
-> IO ()
forall from.
HcPkgInfo
-> Verbosity
-> Maybe (SymbolicPath CWD ('Dir from))
-> PackageDBStackS from
-> InstalledPackageInfo
-> RegisterOptions
-> IO ()
HcPkg.register
(ProgramDb -> HcPkgInfo
hcPkgInfo ProgramDb
progdb)
Verbosity
verbosity
Maybe (SymbolicPath CWD ('Dir from))
mbWorkDir
PackageDBStackS from
packageDbs
InstalledPackageInfo
installedPkgInfo
RegisterOptions
registerOptions
pkgRoot :: Verbosity -> LocalBuildInfo -> PackageDB -> IO FilePath
pkgRoot :: Verbosity -> LocalBuildInfo -> PackageDB -> IO FilePath
pkgRoot Verbosity
verbosity LocalBuildInfo
lbi = PackageDB -> IO FilePath
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
PackageDBX (SymbolicPathX allowAbsolute Pkg to) -> IO FilePath
pkgRoot'
where
pkgRoot' :: PackageDBX (SymbolicPathX allowAbsolute Pkg to) -> IO FilePath
pkgRoot' PackageDBX (SymbolicPathX allowAbsolute Pkg to)
GlobalPackageDB =
let ghcjsProg :: ConfiguredProgram
ghcjsProg = ConfiguredProgram -> Maybe ConfiguredProgram -> ConfiguredProgram
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ConfiguredProgram
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.pkgRoot: no ghcjs program") (Maybe ConfiguredProgram -> ConfiguredProgram)
-> Maybe ConfiguredProgram -> ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
ghcjsProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
in (FilePath -> FilePath) -> IO FilePath -> IO FilePath
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> FilePath
takeDirectory (Verbosity -> ConfiguredProgram -> IO FilePath
getGlobalPackageDB Verbosity
verbosity ConfiguredProgram
ghcjsProg)
pkgRoot' PackageDBX (SymbolicPathX allowAbsolute Pkg to)
UserPackageDB = do
appDir <- FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"ghcjs"
let ver = Compiler -> Version
compilerVersion (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
subdir =
FilePath
System.Info.arch
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Char
'-'
Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
System.Info.os
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Char
'-'
Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow Version
ver
rootDir = FilePath
appDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
subdir
createDirectoryIfMissing True rootDir
return rootDir
pkgRoot' (SpecificPackageDB SymbolicPathX allowAbsolute Pkg to
fp) =
FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> FilePath
takeDirectory (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi SymbolicPathX allowAbsolute Pkg to
fp
runCmd
:: ProgramDb
-> FilePath
-> (FilePath, FilePath, [String])
runCmd :: ProgramDb -> FilePath -> (FilePath, FilePath, [FilePath])
runCmd ProgramDb
progdb FilePath
exe =
( FilePath
script
, ConfiguredProgram -> FilePath
programPath ConfiguredProgram
ghcjsProg
, ConfiguredProgram -> [FilePath]
programDefaultArgs ConfiguredProgram
ghcjsProg [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> [FilePath]
programOverrideArgs ConfiguredProgram
ghcjsProg [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"--run"]
)
where
script :: FilePath
script = FilePath
exe FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"jsexe" FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
"all" FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"js"
ghcjsProg :: ConfiguredProgram
ghcjsProg = ConfiguredProgram -> Maybe ConfiguredProgram -> ConfiguredProgram
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ConfiguredProgram
forall a. HasCallStack => FilePath -> a
error FilePath
"GHCJS.runCmd: no ghcjs program") (Maybe ConfiguredProgram -> ConfiguredProgram)
-> Maybe ConfiguredProgram -> ConfiguredProgram
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
ghcjsProgram ProgramDb
progdb