{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Install
( install
, install_setupHooks
, installFileGlob
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion (CabalSpecVersion)
import Distribution.Types.ExecutableScope
import Distribution.Types.ForeignLib
import Distribution.Types.LocalBuildInfo
import Distribution.Types.PackageDescription
import Distribution.Types.TargetInfo
import Distribution.Types.UnqualComponentName
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Simple.BuildPaths (haddockPath, haddockPref)
import Distribution.Simple.BuildTarget
import Distribution.Simple.Compiler
( CompilerFlavor (..)
, compilerFlavor
)
import Distribution.Simple.Glob (matchDirFileGlob)
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.Setup.Config
import Distribution.Simple.Setup.Copy
( CopyFlags (..)
)
import Distribution.Simple.Setup.Haddock
( HaddockTarget (ForDevelopment)
)
import Distribution.Simple.SetupHooks.Internal
( InstallHooks (..)
)
import qualified Distribution.Simple.SetupHooks.Internal as SetupHooks
import Distribution.Simple.Utils
( createDirectoryIfMissingVerbose
, dieWithException
, info
, installDirectoryContents
, installOrdinaryFile
, isAbsoluteOnAnyPlatform
, isInSearchPath
, noticeNoWrap
, warn
)
import Distribution.Utils.Path
import Distribution.Compat.Graph (IsNode (..))
import Distribution.Simple.Errors
import qualified Distribution.Simple.GHC as GHC
import qualified Distribution.Simple.GHCJS as GHCJS
import qualified Distribution.Simple.HaskellSuite as HaskellSuite
import Distribution.Simple.Setup.Common
import qualified Distribution.Simple.UHC as UHC
import System.Directory
( doesDirectoryExist
, doesFileExist
)
import System.FilePath
( takeDirectory
, takeFileName
)
import Distribution.Pretty
( prettyShow
)
import Distribution.Verbosity
install
:: PackageDescription
-> LocalBuildInfo
-> CopyFlags
-> IO ()
install :: PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install = InstallHooks
-> PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install_setupHooks InstallHooks
SetupHooks.noInstallHooks
install_setupHooks
:: InstallHooks
-> PackageDescription
-> LocalBuildInfo
-> CopyFlags
-> IO ()
install_setupHooks :: InstallHooks
-> PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install_setupHooks
(InstallHooks{Maybe InstallComponentHook
installComponentHook :: Maybe InstallComponentHook
installComponentHook :: InstallHooks -> Maybe InstallComponentHook
installComponentHook})
PackageDescription
pkg_descr
LocalBuildInfo
lbi
CopyFlags
flags = do
IO ()
checkHasLibsOrExes
targets <- Verbosity
-> PackageDescription
-> LocalBuildInfo
-> [FilePath]
-> IO [TargetInfo]
readTargetInfos Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CopyFlags -> [FilePath]
copyTargets CopyFlags
flags)
copyPackage verbosity pkg_descr lbi distPref copydest
withNeededTargetsInBuildOrder' pkg_descr lbi (map nodeKey targets) $ \TargetInfo
target -> do
let comp :: Component
comp = TargetInfo -> Component
targetComponent TargetInfo
target
clbi :: ComponentLocalBuildInfo
clbi = TargetInfo -> ComponentLocalBuildInfo
targetCLBI TargetInfo
target
Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Component
-> ComponentLocalBuildInfo
-> CopyDest
-> IO ()
copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi Component
comp ComponentLocalBuildInfo
clbi CopyDest
copydest
Maybe InstallComponentHook
-> (InstallComponentHook -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe InstallComponentHook
installComponentHook ((InstallComponentHook -> IO ()) -> IO ())
-> (InstallComponentHook -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \InstallComponentHook
instAction ->
let inputs :: InstallComponentInputs
inputs =
SetupHooks.InstallComponentInputs
{ copyFlags :: CopyFlags
copyFlags = CopyFlags
flags
, localBuildInfo :: LocalBuildInfo
localBuildInfo = LocalBuildInfo
lbi
, targetInfo :: TargetInfo
targetInfo = TargetInfo
target
}
in InstallComponentHook
instAction InstallComponentInputs
inputs
where
common :: CommonSetupFlags
common = CopyFlags -> CommonSetupFlags
copyCommonFlags CopyFlags
flags
distPref :: SymbolicPath Pkg ('Dir Dist)
distPref = Flag (SymbolicPath Pkg ('Dir Dist)) -> SymbolicPath Pkg ('Dir Dist)
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag (SymbolicPath Pkg ('Dir Dist))
-> SymbolicPath Pkg ('Dir Dist))
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> SymbolicPath Pkg ('Dir Dist)
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
setupDistPref CommonSetupFlags
common
verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (Flag Verbosity -> Verbosity) -> Flag Verbosity -> Verbosity
forall a b. (a -> b) -> a -> b
$ CommonSetupFlags -> Flag Verbosity
setupVerbosity CommonSetupFlags
common
copydest :: CopyDest
copydest = Flag CopyDest -> CopyDest
forall a. WithCallStack (Flag a -> a)
fromFlag (CopyFlags -> Flag CopyDest
copyDest CopyFlags
flags)
checkHasLibsOrExes :: IO ()
checkHasLibsOrExes =
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (PackageDescription -> Bool
hasLibs PackageDescription
pkg_descr Bool -> Bool -> Bool
|| PackageDescription -> Bool
hasForeignLibs PackageDescription
pkg_descr Bool -> Bool -> Bool
|| PackageDescription -> Bool
hasExes PackageDescription
pkg_descr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Verbosity -> FilePath -> IO ()
warn Verbosity
verbosity FilePath
"No executables and no library found. Nothing to do."
copyPackage
:: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> SymbolicPath Pkg (Dir Dist)
-> CopyDest
-> IO ()
copyPackage :: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> SymbolicPath Pkg ('Dir Dist)
-> CopyDest
-> IO ()
copyPackage Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi SymbolicPath Pkg ('Dir Dist)
distPref CopyDest
copydest = do
let
InstallDirs
{ datadir :: forall dir. InstallDirs dir -> dir
datadir = FilePath
dataPref
, docdir :: forall dir. InstallDirs dir -> dir
docdir = FilePath
docPref
, htmldir :: forall dir. InstallDirs dir -> dir
htmldir = FilePath
htmlPref
, haddockdir :: forall dir. InstallDirs dir -> dir
haddockdir = FilePath
interfacePref
} = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
absoluteInstallCommandDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (LocalBuildInfo -> UnitId
localUnitId LocalBuildInfo
lbi) CopyDest
copydest
mbWorkDir :: Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = Maybe (SymbolicPathX 'AllowAbsolute 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 (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir
Verbosity
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> PackageDescription
-> SymbolicPath Pkg ('Dir DataDir)
-> IO ()
installDataFiles Verbosity
verbosity Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir PackageDescription
pkg_descr (SymbolicPath Pkg ('Dir DataDir) -> IO ())
-> SymbolicPath Pkg ('Dir DataDir) -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> SymbolicPath Pkg ('Dir DataDir)
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath FilePath
dataPref
docExists <- FilePath -> IO Bool
doesDirectoryExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts) -> FilePath
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> FilePath
i (SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts) -> FilePath)
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts) -> FilePath
forall a b. (a -> b) -> a -> b
$ HaddockTarget
-> SymbolicPath Pkg ('Dir Dist)
-> PackageDescription
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts)
forall root.
HaddockTarget
-> SymbolicPath root ('Dir Dist)
-> PackageDescription
-> SymbolicPath root ('Dir Artifacts)
haddockPref HaddockTarget
ForDevelopment SymbolicPath Pkg ('Dir Dist)
distPref PackageDescription
pkg_descr
info
verbosity
( "directory "
++ getSymbolicPath (haddockPref ForDevelopment distPref pkg_descr)
++ " does exist: "
++ show docExists
)
when docExists $ do
createDirectoryIfMissingVerbose verbosity True htmlPref
installDirectoryContents
verbosity
(i $ haddockPref ForDevelopment distPref pkg_descr)
htmlPref
let haddockInterfaceFileSrc =
HaddockTarget
-> SymbolicPath Pkg ('Dir Dist)
-> PackageDescription
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts)
forall root.
HaddockTarget
-> SymbolicPath root ('Dir Dist)
-> PackageDescription
-> SymbolicPath root ('Dir Artifacts)
haddockPref HaddockTarget
ForDevelopment SymbolicPath Pkg ('Dir Dist)
distPref PackageDescription
pkg_descr
SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts)
-> RelativePath Artifacts c3 -> SymbolicPathX 'AllowAbsolute Pkg c3
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath Artifacts c3
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx (PackageDescription -> FilePath
haddockPath PackageDescription
pkg_descr)
haddockInterfaceFileDest = FilePath
interfacePref FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> PackageDescription -> FilePath
haddockPath PackageDescription
pkg_descr
exists <- doesFileExist $ i haddockInterfaceFileSrc
when exists $ do
createDirectoryIfMissingVerbose verbosity True interfacePref
installOrdinaryFile
verbosity
(i haddockInterfaceFileSrc)
haddockInterfaceFileDest
let lfiles = PackageDescription -> [RelativePath Pkg 'File]
licenseFiles PackageDescription
pkg_descr
unless (null lfiles) $ do
createDirectoryIfMissingVerbose verbosity True docPref
for_ lfiles $ \RelativePath Pkg 'File
lfile -> do
Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile
Verbosity
verbosity
(RelativePath Pkg 'File -> FilePath
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> FilePath
i RelativePath Pkg 'File
lfile)
(FilePath
docPref FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> FilePath
takeFileName (RelativePath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath RelativePath Pkg 'File
lfile))
copyComponent
:: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Component
-> ComponentLocalBuildInfo
-> CopyDest
-> IO ()
copyComponent :: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Component
-> ComponentLocalBuildInfo
-> CopyDest
-> IO ()
copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CLib Library
lib) ComponentLocalBuildInfo
clbi CopyDest
copydest = do
let InstallDirs
{ libdir :: forall dir. InstallDirs dir -> dir
libdir = FilePath
libPref
, dynlibdir :: forall dir. InstallDirs dir -> dir
dynlibdir = FilePath
dynlibPref
, includedir :: forall dir. InstallDirs dir -> dir
includedir = FilePath
incPref
} = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
absoluteInstallCommandDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
buildPref :: FilePath
buildPref = LocalBuildInfo
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi (SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath)
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
case Library -> LibraryName
libName Library
lib of
LibraryName
LMainLibName -> Verbosity -> FilePath -> IO ()
noticeNoWrap Verbosity
verbosity (FilePath
"Installing library in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
libPref)
LSubLibName UnqualComponentName
n -> Verbosity -> FilePath -> IO ()
noticeNoWrap Verbosity
verbosity (FilePath
"Installing internal library " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
libPref)
Verbosity
-> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
installIncludeFiles Verbosity
verbosity (Library -> BuildInfo
libBuildInfo Library
lib) LocalBuildInfo
lbi FilePath
buildPref FilePath
incPref
case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
CompilerFlavor
GHC -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
GHC.installLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
libPref FilePath
dynlibPref FilePath
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
GHCJS.installLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
libPref FilePath
dynlibPref FilePath
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
CompilerFlavor
UHC -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
UHC.installLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
libPref FilePath
dynlibPref FilePath
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
HaskellSuite FilePath
_ ->
Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
HaskellSuite.installLib
Verbosity
verbosity
LocalBuildInfo
lbi
FilePath
libPref
FilePath
dynlibPref
FilePath
buildPref
PackageDescription
pkg_descr
Library
lib
ComponentLocalBuildInfo
clbi
CompilerFlavor
_ ->
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ CompilerFlavor -> CabalException
CompilerNotInstalled (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CFLib ForeignLib
flib) ComponentLocalBuildInfo
clbi CopyDest
copydest = do
let InstallDirs
{ flibdir :: forall dir. InstallDirs dir -> dir
flibdir = FilePath
flibPref
, includedir :: forall dir. InstallDirs dir -> dir
includedir = FilePath
incPref
} = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
absoluteComponentInstallDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
buildPref :: FilePath
buildPref = LocalBuildInfo
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi (SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath)
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo
-> ComponentLocalBuildInfo
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
Verbosity -> FilePath -> IO ()
noticeNoWrap Verbosity
verbosity (FilePath
"Installing foreign library " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> FilePath
unUnqualComponentName (ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
flibPref)
Verbosity
-> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
installIncludeFiles Verbosity
verbosity (ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib) LocalBuildInfo
lbi FilePath
buildPref FilePath
incPref
case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
CompilerFlavor
GHC -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> PackageDescription
-> ForeignLib
-> IO ()
GHC.installFLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
flibPref FilePath
buildPref PackageDescription
pkg_descr ForeignLib
flib
CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> PackageDescription
-> ForeignLib
-> IO ()
GHCJS.installFLib Verbosity
verbosity LocalBuildInfo
lbi FilePath
flibPref FilePath
buildPref PackageDescription
pkg_descr ForeignLib
flib
CompilerFlavor
_ -> Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ CompilerFlavor -> CabalException
CompilerNotInstalled (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CExe Executable
exe) ComponentLocalBuildInfo
clbi CopyDest
copydest = do
let installDirs :: InstallDirs FilePath
installDirs = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
absoluteComponentInstallDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
buildPref :: FilePath
buildPref = LocalBuildInfo
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
interpretSymbolicPathLBI LocalBuildInfo
lbi (SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath)
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build) -> FilePath
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> SymbolicPathX 'AllowAbsolute Pkg ('Dir Build)
buildDir LocalBuildInfo
lbi
uid :: UnitId
uid = ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi
pkgid :: PackageIdentifier
pkgid = PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pkg_descr
binPref :: FilePath
binPref
| ExecutableScope
ExecutablePrivate <- Executable -> ExecutableScope
exeScope Executable
exe = InstallDirs FilePath -> FilePath
forall dir. InstallDirs dir -> dir
libexecdir InstallDirs FilePath
installDirs
| Bool
otherwise = InstallDirs FilePath -> FilePath
forall dir. InstallDirs dir -> dir
bindir InstallDirs FilePath
installDirs
progPrefixPref :: FilePath
progPrefixPref = PackageIdentifier
-> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath
substPathTemplate PackageIdentifier
pkgid LocalBuildInfo
lbi UnitId
uid (LocalBuildInfo -> PathTemplate
progPrefix LocalBuildInfo
lbi)
progSuffixPref :: FilePath
progSuffixPref = PackageIdentifier
-> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath
substPathTemplate PackageIdentifier
pkgid LocalBuildInfo
lbi UnitId
uid (LocalBuildInfo -> PathTemplate
progSuffix LocalBuildInfo
lbi)
progFix :: (FilePath, FilePath)
progFix = (FilePath
progPrefixPref, FilePath
progSuffixPref)
Verbosity -> FilePath -> IO ()
noticeNoWrap
Verbosity
verbosity
( FilePath
"Installing executable "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (Executable -> UnqualComponentName
exeName Executable
exe)
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" in "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
binPref
)
inPath <- FilePath -> IO Bool
isInSearchPath FilePath
binPref
when (not inPath) $
warn
verbosity
( "The directory "
++ binPref
++ " is not in the system search path."
)
case compilerFlavor (compiler lbi) of
CompilerFlavor
GHC -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> (FilePath, FilePath)
-> PackageDescription
-> Executable
-> IO ()
GHC.installExe Verbosity
verbosity LocalBuildInfo
lbi FilePath
binPref FilePath
buildPref (FilePath, FilePath)
progFix PackageDescription
pkg_descr Executable
exe
CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> (FilePath, FilePath)
-> PackageDescription
-> Executable
-> IO ()
GHCJS.installExe Verbosity
verbosity LocalBuildInfo
lbi FilePath
binPref FilePath
buildPref (FilePath, FilePath)
progFix PackageDescription
pkg_descr Executable
exe
CompilerFlavor
UHC -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
HaskellSuite{} -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
CompilerFlavor
_ ->
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ CompilerFlavor -> CabalException
CompilerNotInstalled (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
copyComponent Verbosity
_ PackageDescription
_ LocalBuildInfo
_ (CBench Benchmark
_) ComponentLocalBuildInfo
_ CopyDest
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
copyComponent Verbosity
_ PackageDescription
_ LocalBuildInfo
_ (CTest TestSuite
_) ComponentLocalBuildInfo
_ CopyDest
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
installDataFiles
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> PackageDescription
-> SymbolicPath Pkg (Dir DataDir)
-> IO ()
installDataFiles :: Verbosity
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> PackageDescription
-> SymbolicPath Pkg ('Dir DataDir)
-> IO ()
installDataFiles Verbosity
verbosity Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir PackageDescription
pkg_descr SymbolicPath Pkg ('Dir DataDir)
destDataDir =
(RelativePath DataDir 'File -> IO ())
-> [RelativePath DataDir 'File] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_
(Verbosity
-> CabalSpecVersion
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> (Maybe (SymbolicPath CWD ('Dir DataDir)),
SymbolicPath Pkg ('Dir DataDir))
-> RelativePath DataDir 'File
-> IO ()
installFileGlob Verbosity
verbosity (PackageDescription -> CabalSpecVersion
specVersion PackageDescription
pkg_descr) Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir (Maybe (SymbolicPath CWD ('Dir DataDir))
srcDataDir, SymbolicPath Pkg ('Dir DataDir)
destDataDir))
(PackageDescription -> [RelativePath DataDir 'File]
dataFiles PackageDescription
pkg_descr)
where
srcDataDirRaw :: FilePath
srcDataDirRaw = SymbolicPath Pkg ('Dir DataDir) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (SymbolicPath Pkg ('Dir DataDir) -> FilePath)
-> SymbolicPath Pkg ('Dir DataDir) -> FilePath
forall a b. (a -> b) -> a -> b
$ PackageDescription -> SymbolicPath Pkg ('Dir DataDir)
dataDir PackageDescription
pkg_descr
srcDataDir :: Maybe (SymbolicPath CWD (Dir DataDir))
srcDataDir :: Maybe (SymbolicPath CWD ('Dir DataDir))
srcDataDir
| FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
srcDataDirRaw =
Maybe (SymbolicPath CWD ('Dir DataDir))
forall a. Maybe a
Nothing
| FilePath -> Bool
isAbsoluteOnAnyPlatform FilePath
srcDataDirRaw =
SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir))
forall a. a -> Maybe a
Just (SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir)))
-> SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir))
forall a b. (a -> b) -> a -> b
$ FilePath -> SymbolicPath CWD ('Dir DataDir)
forall from (to :: FileOrDir). FilePath -> SymbolicPath from to
makeSymbolicPath FilePath
srcDataDirRaw
| Bool
otherwise =
SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir))
forall a. a -> Maybe a
Just (SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir)))
-> SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir))
forall a b. (a -> b) -> a -> b
$ SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg)
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg)
forall a. a -> Maybe a -> a
fromMaybe SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg)
forall (allowAbsolute :: AllowAbsolute) from to.
SymbolicPathX allowAbsolute from ('Dir to)
sameDirectory Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg)
-> RelativePath Pkg ('Dir DataDir)
-> SymbolicPath CWD ('Dir DataDir)
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> RelativePath Pkg ('Dir DataDir)
forall from (to :: FileOrDir).
HasCallStack =>
FilePath -> RelativePath from to
makeRelativePathEx FilePath
srcDataDirRaw
installFileGlob
:: Verbosity
-> CabalSpecVersion
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> (Maybe (SymbolicPath CWD (Dir DataDir)), SymbolicPath Pkg (Dir DataDir))
-> RelativePath DataDir File
-> IO ()
installFileGlob :: Verbosity
-> CabalSpecVersion
-> Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> (Maybe (SymbolicPath CWD ('Dir DataDir)),
SymbolicPath Pkg ('Dir DataDir))
-> RelativePath DataDir 'File
-> IO ()
installFileGlob Verbosity
verbosity CabalSpecVersion
spec_version Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir (Maybe (SymbolicPath CWD ('Dir DataDir))
srcDir, SymbolicPath Pkg ('Dir DataDir)
destDir) RelativePath DataDir 'File
glob = do
files <- Verbosity
-> CabalSpecVersion
-> Maybe (SymbolicPath CWD ('Dir DataDir))
-> RelativePath DataDir 'File
-> IO [RelativePath DataDir 'File]
forall dir (allowAbs :: AllowAbsolute) (file :: FileOrDir).
Verbosity
-> CabalSpecVersion
-> Maybe (SymbolicPath CWD ('Dir dir))
-> SymbolicPathX allowAbs dir file
-> IO [SymbolicPathX allowAbs dir file]
matchDirFileGlob Verbosity
verbosity CabalSpecVersion
spec_version Maybe (SymbolicPath CWD ('Dir DataDir))
srcDir RelativePath DataDir 'File
glob
for_ files $ \RelativePath DataDir 'File
file' -> do
let src :: FilePath
src = SymbolicPathX 'AllowAbsolute CWD 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath (SymbolicPath CWD ('Dir DataDir)
-> Maybe (SymbolicPath CWD ('Dir DataDir))
-> SymbolicPath CWD ('Dir DataDir)
forall a. a -> Maybe a -> a
fromMaybe SymbolicPath CWD ('Dir DataDir)
forall (allowAbsolute :: AllowAbsolute) from to.
SymbolicPathX allowAbsolute from ('Dir to)
sameDirectory Maybe (SymbolicPath CWD ('Dir DataDir))
srcDir SymbolicPath CWD ('Dir DataDir)
-> RelativePath DataDir 'File
-> SymbolicPathX 'AllowAbsolute CWD 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath DataDir 'File
file')
dst :: FilePath
dst = Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
-> SymbolicPathX 'AllowAbsolute Pkg 'File -> FilePath
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> FilePath
interpretSymbolicPath Maybe (SymbolicPathX 'AllowAbsolute CWD ('Dir Pkg))
mbWorkDir (SymbolicPath Pkg ('Dir DataDir)
destDir SymbolicPath Pkg ('Dir DataDir)
-> RelativePath DataDir 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath DataDir 'File
file')
Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True (FilePath -> FilePath
takeDirectory FilePath
dst)
Verbosity -> FilePath -> FilePath -> IO ()
installOrdinaryFile Verbosity
verbosity FilePath
src FilePath
dst
installIncludeFiles :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
installIncludeFiles :: Verbosity
-> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
installIncludeFiles Verbosity
verbosity BuildInfo
libBi LocalBuildInfo
lbi FilePath
buildPref FilePath
destIncludeDir = do
let relincdirs :: [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
relincdirs = SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
forall (allowAbsolute :: AllowAbsolute) from to.
SymbolicPathX allowAbsolute from ('Dir to)
sameDirectory SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
forall a. a -> [a] -> [a]
: (SymbolicPath Pkg ('Dir Include)
-> Maybe (SymbolicPathX 'OnlyRelative Pkg ('Dir Include)))
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe SymbolicPath Pkg ('Dir Include)
-> Maybe (SymbolicPathX 'OnlyRelative Pkg ('Dir Include))
forall from (to :: FileOrDir).
SymbolicPath from to -> Maybe (RelativePath from to)
symbolicPathRelative_maybe (BuildInfo -> [SymbolicPath Pkg ('Dir Include)]
includeDirs BuildInfo
libBi)
incdirs :: [FilePath]
incdirs =
[ FilePath
root FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative Pkg ('Dir Include) -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
dir
|
SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
dir <- [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
relincdirs
, FilePath
root <- [LocalBuildInfo -> FilePath
baseDir LocalBuildInfo
lbi, FilePath
buildPref]
]
incs <- (SymbolicPathX 'OnlyRelative Include 'File
-> IO (FilePath, FilePath))
-> [SymbolicPathX 'OnlyRelative Include 'File]
-> IO [(FilePath, 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 ([FilePath] -> FilePath -> IO (FilePath, FilePath)
findInc [FilePath]
incdirs (FilePath -> IO (FilePath, FilePath))
-> (SymbolicPathX 'OnlyRelative Include 'File -> FilePath)
-> SymbolicPathX 'OnlyRelative Include 'File
-> IO (FilePath, FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPathX 'OnlyRelative Include 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath) (BuildInfo -> [SymbolicPathX 'OnlyRelative Include 'File]
installIncludes BuildInfo
libBi)
sequence_
[ do
createDirectoryIfMissingVerbose verbosity True destDir
installOrdinaryFile verbosity srcFile destFile
| (relFile, srcFile) <- incs
, let destFile = FilePath
destIncludeDir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
relFile
destDir = FilePath -> FilePath
takeDirectory FilePath
destFile
]
where
baseDir :: LocalBuildInfo -> FilePath
baseDir LocalBuildInfo
lbi' = CommonSetupFlags -> FilePath
packageRoot (CommonSetupFlags -> FilePath) -> CommonSetupFlags -> FilePath
forall a b. (a -> b) -> a -> b
$ ConfigFlags -> CommonSetupFlags
configCommonFlags (ConfigFlags -> CommonSetupFlags)
-> ConfigFlags -> CommonSetupFlags
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> ConfigFlags
configFlags LocalBuildInfo
lbi'
findInc :: [FilePath] -> FilePath -> IO (FilePath, FilePath)
findInc [] FilePath
file = Verbosity -> CabalException -> IO (FilePath, FilePath)
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO (FilePath, FilePath))
-> CabalException -> IO (FilePath, FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath -> CabalException
CantFindIncludeFile FilePath
file
findInc (FilePath
dir : [FilePath]
dirs) FilePath
file = do
let path :: FilePath
path = FilePath
dir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath
file
exists <- FilePath -> IO Bool
doesFileExist FilePath
path
if exists then return (file, path) else findInc dirs file