{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.Install
-- Copyright   :  Isaac Jones 2003-2004
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is the entry point into installing a built package. Performs the
-- \"@.\/setup install@\" and \"@.\/setup copy@\" actions. It moves files into
-- place based on the prefix argument. It does the generic bits and then calls
-- compiler-specific functions to do the rest.

module Distribution.Simple.Install (
        install,
  ) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Types.TargetInfo
import Distribution.Types.LocalBuildInfo
import Distribution.Types.ForeignLib
import Distribution.Types.PackageDescription
import Distribution.Types.UnqualComponentName
import Distribution.Types.ExecutableScope

import Distribution.Package
import Distribution.PackageDescription
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.BuildPaths (haddockName, haddockPref)
import Distribution.Simple.Glob (matchDirFileGlob)
import Distribution.Simple.Utils
         ( createDirectoryIfMissingVerbose
         , installDirectoryContents, installOrdinaryFile, isInSearchPath
         , die', info, noticeNoWrap, warn )
import Distribution.Simple.Compiler
         ( CompilerFlavor(..), compilerFlavor )
import Distribution.Simple.Setup
         ( CopyFlags(..), fromFlag, HaddockTarget(ForDevelopment) )
import Distribution.Simple.BuildTarget

import qualified Distribution.Simple.GHC   as GHC
import qualified Distribution.Simple.GHCJS as GHCJS
import qualified Distribution.Simple.UHC   as UHC
import qualified Distribution.Simple.HaskellSuite as HaskellSuite
import Distribution.Compat.Graph (IsNode(..))

import System.Directory
         ( doesDirectoryExist, doesFileExist )
import System.FilePath
         ( takeFileName, takeDirectory, (</>), isRelative )

import Distribution.Verbosity
import Distribution.Pretty
         ( prettyShow )

-- |Perform the \"@.\/setup install@\" and \"@.\/setup copy@\"
-- actions.  Move files into place based on the prefix argument.
--
-- This does NOT register libraries, you should call 'register'
-- to do that.

install :: PackageDescription -- ^information from the .cabal file
        -> LocalBuildInfo -- ^information from the configure step
        -> CopyFlags -- ^flags sent to copy or install
        -> IO ()
install :: PackageDescription -> LocalBuildInfo -> CopyFlags -> IO ()
install PackageDescription
pkg_descr LocalBuildInfo
lbi CopyFlags
flags = do
  IO ()
checkHasLibsOrExes
  [TargetInfo]
targets <- Verbosity
-> PackageDescription
-> LocalBuildInfo
-> [String]
-> IO [TargetInfo]
readTargetInfos Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CopyFlags -> [String]
copyArgs CopyFlags
flags)

  Verbosity
-> PackageDescription
-> LocalBuildInfo
-> String
-> CopyDest
-> IO ()
copyPackage Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi String
distPref CopyDest
copydest

  -- It's not necessary to do these in build-order, but it's harmless
  PackageDescription
-> LocalBuildInfo -> [UnitId] -> (TargetInfo -> IO ()) -> IO ()
withNeededTargetsInBuildOrder' PackageDescription
pkg_descr LocalBuildInfo
lbi ((TargetInfo -> UnitId) -> [TargetInfo] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map TargetInfo -> UnitId
forall a. IsNode a => a -> Key a
nodeKey [TargetInfo]
targets) ((TargetInfo -> IO ()) -> IO ()) -> (TargetInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \TargetInfo
target ->
    let comp :: Component
comp = TargetInfo -> Component
targetComponent TargetInfo
target
        clbi :: ComponentLocalBuildInfo
clbi = TargetInfo -> ComponentLocalBuildInfo
targetCLBI TargetInfo
target
    in Verbosity
-> PackageDescription
-> LocalBuildInfo
-> Component
-> ComponentLocalBuildInfo
-> CopyDest
-> IO ()
copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi Component
comp ComponentLocalBuildInfo
clbi CopyDest
copydest
 where
  distPref :: String
distPref  = Flag String -> String
forall a. WithCallStack (Flag a -> a)
fromFlag (CopyFlags -> Flag String
copyDistPref CopyFlags
flags)
  verbosity :: Verbosity
verbosity = Flag Verbosity -> Verbosity
forall a. WithCallStack (Flag a -> a)
fromFlag (CopyFlags -> Flag Verbosity
copyVerbosity CopyFlags
flags)
  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 -> String -> IO ()
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity String
"No executables and no library found. Nothing to do."

-- | Copy package global files.
copyPackage :: Verbosity -> PackageDescription
            -> LocalBuildInfo -> FilePath -> CopyDest -> IO ()
copyPackage :: Verbosity
-> PackageDescription
-> LocalBuildInfo
-> String
-> CopyDest
-> IO ()
copyPackage Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi String
distPref CopyDest
copydest = do
  let -- This is a bit of a hack, to handle files which are not
      -- per-component (data files and Haddock files.)
      InstallDirs {
         datadir :: forall dir. InstallDirs dir -> dir
datadir    = String
dataPref,
         docdir :: forall dir. InstallDirs dir -> dir
docdir     = String
docPref,
         htmldir :: forall dir. InstallDirs dir -> dir
htmldir    = String
htmlPref,
         haddockdir :: forall dir. InstallDirs dir -> dir
haddockdir = String
interfacePref
      } = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs String
absoluteInstallCommandDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (LocalBuildInfo -> UnitId
localUnitId LocalBuildInfo
lbi) CopyDest
copydest

  -- Install (package-global) data files
  Verbosity -> PackageDescription -> String -> IO ()
installDataFiles Verbosity
verbosity PackageDescription
pkg_descr String
dataPref

  -- Install (package-global) Haddock files
  -- TODO: these should be done per-library
  Bool
docExists <- String -> IO Bool
doesDirectoryExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ HaddockTarget -> String -> PackageDescription -> String
haddockPref HaddockTarget
ForDevelopment String
distPref PackageDescription
pkg_descr
  Verbosity -> String -> IO ()
info Verbosity
verbosity (String
"directory " String -> String -> String
forall a. [a] -> [a] -> [a]
++ HaddockTarget -> String -> PackageDescription -> String
haddockPref HaddockTarget
ForDevelopment String
distPref PackageDescription
pkg_descr String -> String -> String
forall a. [a] -> [a] -> [a]
++
                  String
" does exist: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Bool -> String
forall a. Show a => a -> String
show Bool
docExists)

  -- TODO: this is a bit questionable, Haddock files really should
  -- be per library (when there are convenience libraries.)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
docExists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True String
htmlPref
      Verbosity -> String -> String -> IO ()
installDirectoryContents Verbosity
verbosity
          (HaddockTarget -> String -> PackageDescription -> String
haddockPref HaddockTarget
ForDevelopment String
distPref PackageDescription
pkg_descr) String
htmlPref
      -- setPermissionsRecursive [Read] htmlPref
      -- The haddock interface file actually already got installed
      -- in the recursive copy, but now we install it where we actually
      -- want it to be (normally the same place). We could remove the
      -- copy in htmlPref first.
      let haddockInterfaceFileSrc :: String
haddockInterfaceFileSrc  = HaddockTarget -> String -> PackageDescription -> String
haddockPref HaddockTarget
ForDevelopment String
distPref PackageDescription
pkg_descr
                                                   String -> String -> String
</> PackageDescription -> String
haddockName PackageDescription
pkg_descr
          haddockInterfaceFileDest :: String
haddockInterfaceFileDest = String
interfacePref String -> String -> String
</> PackageDescription -> String
haddockName PackageDescription
pkg_descr
      -- We only generate the haddock interface file for libs, So if the
      -- package consists only of executables there will not be one:
      Bool
exists <- String -> IO Bool
doesFileExist String
haddockInterfaceFileSrc
      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True String
interfacePref
        Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity String
haddockInterfaceFileSrc
                                      String
haddockInterfaceFileDest

  let lfiles :: [String]
lfiles = PackageDescription -> [String]
licenseFiles PackageDescription
pkg_descr
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
lfiles) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True String
docPref
    [IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
      [ Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity String
lfile (String
docPref String -> String -> String
</> String -> String
takeFileName String
lfile)
      | String
lfile <- [String]
lfiles ]

-- | Copy files associated with a component.
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 = String
libPref,
            dynlibdir :: forall dir. InstallDirs dir -> dir
dynlibdir = String
dynlibPref,
            includedir :: forall dir. InstallDirs dir -> dir
includedir = String
incPref
            } = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs String
absoluteInstallCommandDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
        buildPref :: String
buildPref = LocalBuildInfo -> ComponentLocalBuildInfo -> String
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi

    case Library -> LibraryName
libName Library
lib of
        LibraryName
LMainLibName  -> Verbosity -> String -> IO ()
noticeNoWrap Verbosity
verbosity (String
"Installing library in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
libPref)
        LSubLibName UnqualComponentName
n -> Verbosity -> String -> IO ()
noticeNoWrap Verbosity
verbosity (String
"Installing internal library " String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
libPref)

    -- install include files for all compilers - they may be needed to compile
    -- haskell files (using the CPP extension)
    Verbosity
-> BuildInfo -> LocalBuildInfo -> String -> String -> IO ()
installIncludeFiles Verbosity
verbosity (Library -> BuildInfo
libBuildInfo Library
lib) LocalBuildInfo
lbi String
buildPref String
incPref

    case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
      CompilerFlavor
GHC   -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> String
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
GHC.installLib   Verbosity
verbosity LocalBuildInfo
lbi String
libPref String
dynlibPref String
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
      CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> String
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
GHCJS.installLib Verbosity
verbosity LocalBuildInfo
lbi String
libPref String
dynlibPref String
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
      CompilerFlavor
UHC   -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> String
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
UHC.installLib   Verbosity
verbosity LocalBuildInfo
lbi String
libPref String
dynlibPref String
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
      HaskellSuite String
_ -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> String
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
HaskellSuite.installLib
                                Verbosity
verbosity LocalBuildInfo
lbi String
libPref String
dynlibPref String
buildPref PackageDescription
pkg_descr Library
lib ComponentLocalBuildInfo
clbi
      CompilerFlavor
_ -> Verbosity -> String -> IO ()
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"installing with "
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not implemented"

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 = String
flibPref,
            includedir :: forall dir. InstallDirs dir -> dir
includedir = String
incPref
            } = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs String
absoluteComponentInstallDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
        buildPref :: String
buildPref = LocalBuildInfo -> ComponentLocalBuildInfo -> String
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi

    Verbosity -> String -> IO ()
noticeNoWrap Verbosity
verbosity (String
"Installing foreign library " String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
unUnqualComponentName (ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flibPref)
    Verbosity
-> BuildInfo -> LocalBuildInfo -> String -> String -> IO ()
installIncludeFiles Verbosity
verbosity (ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib) LocalBuildInfo
lbi String
buildPref String
incPref

    case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
      CompilerFlavor
GHC   -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> PackageDescription
-> ForeignLib
-> IO ()
GHC.installFLib   Verbosity
verbosity LocalBuildInfo
lbi String
flibPref String
buildPref PackageDescription
pkg_descr ForeignLib
flib
      CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> PackageDescription
-> ForeignLib
-> IO ()
GHCJS.installFLib Verbosity
verbosity LocalBuildInfo
lbi String
flibPref String
buildPref PackageDescription
pkg_descr ForeignLib
flib
      CompilerFlavor
_ -> Verbosity -> String -> IO ()
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"installing foreign lib with "
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not implemented"

copyComponent Verbosity
verbosity PackageDescription
pkg_descr LocalBuildInfo
lbi (CExe Executable
exe) ComponentLocalBuildInfo
clbi CopyDest
copydest = do
    let installDirs :: InstallDirs String
installDirs = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs String
absoluteComponentInstallDirs PackageDescription
pkg_descr LocalBuildInfo
lbi (ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi) CopyDest
copydest
        -- the installers know how to find the actual location of the
        -- binaries
        buildPref :: String
buildPref = LocalBuildInfo -> String
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 :: String
binPref | ExecutableScope
ExecutablePrivate <- Executable -> ExecutableScope
exeScope Executable
exe = InstallDirs String -> String
forall dir. InstallDirs dir -> dir
libexecdir InstallDirs String
installDirs
                | Bool
otherwise = InstallDirs String -> String
forall dir. InstallDirs dir -> dir
bindir InstallDirs String
installDirs
        progPrefixPref :: String
progPrefixPref = PackageIdentifier
-> LocalBuildInfo -> UnitId -> PathTemplate -> String
substPathTemplate PackageIdentifier
pkgid LocalBuildInfo
lbi UnitId
uid (LocalBuildInfo -> PathTemplate
progPrefix LocalBuildInfo
lbi)
        progSuffixPref :: String
progSuffixPref = PackageIdentifier
-> LocalBuildInfo -> UnitId -> PathTemplate -> String
substPathTemplate PackageIdentifier
pkgid LocalBuildInfo
lbi UnitId
uid (LocalBuildInfo -> PathTemplate
progSuffix LocalBuildInfo
lbi)
        progFix :: (String, String)
progFix = (String
progPrefixPref, String
progSuffixPref)
    Verbosity -> String -> IO ()
noticeNoWrap Verbosity
verbosity (String
"Installing executable " String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow (Executable -> UnqualComponentName
exeName Executable
exe)
                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
binPref)
    Bool
inPath <- String -> IO Bool
isInSearchPath String
binPref
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
inPath) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      Verbosity -> String -> IO ()
warn Verbosity
verbosity (String
"The directory " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
binPref
                      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not in the system search path.")
    case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
      CompilerFlavor
GHC   -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> (String, String)
-> PackageDescription
-> Executable
-> IO ()
GHC.installExe   Verbosity
verbosity LocalBuildInfo
lbi String
binPref String
buildPref (String, String)
progFix PackageDescription
pkg_descr Executable
exe
      CompilerFlavor
GHCJS -> Verbosity
-> LocalBuildInfo
-> String
-> String
-> (String, String)
-> PackageDescription
-> Executable
-> IO ()
GHCJS.installExe Verbosity
verbosity LocalBuildInfo
lbi String
binPref String
buildPref (String, String)
progFix PackageDescription
pkg_descr Executable
exe
      CompilerFlavor
UHC   -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      HaskellSuite {} -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      CompilerFlavor
_ -> Verbosity -> String -> IO ()
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"installing with "
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi))
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not implemented"

-- Nothing to do for benchmark/testsuite
copyComponent Verbosity
_ PackageDescription
_ LocalBuildInfo
_ (CBench Benchmark
_) ComponentLocalBuildInfo
_ CopyDest
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
copyComponent Verbosity
_ PackageDescription
_ LocalBuildInfo
_ (CTest TestSuite
_) ComponentLocalBuildInfo
_ CopyDest
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Install the files listed in data-files
--
installDataFiles :: Verbosity -> PackageDescription -> FilePath -> IO ()
installDataFiles :: Verbosity -> PackageDescription -> String -> IO ()
installDataFiles Verbosity
verbosity PackageDescription
pkg_descr String
destDataDir =
  ((String -> IO ()) -> [String] -> IO ())
-> [String] -> (String -> IO ()) -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (PackageDescription -> [String]
dataFiles PackageDescription
pkg_descr) ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ String
glob -> do
    let srcDataDirRaw :: String
srcDataDirRaw = PackageDescription -> String
dataDir PackageDescription
pkg_descr
        srcDataDir :: String
srcDataDir = if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
srcDataDirRaw
          then String
"."
          else String
srcDataDirRaw
    [String]
files <- Verbosity -> Version -> String -> String -> IO [String]
matchDirFileGlob Verbosity
verbosity (PackageDescription -> Version
specVersion PackageDescription
pkg_descr) String
srcDataDir String
glob
    [String] -> (String -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [String]
files ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ String
file' -> do
      let src :: String
src = String
srcDataDir String -> String -> String
</> String
file'
          dst :: String
dst = String
destDataDir String -> String -> String
</> String
file'
      Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True (String -> String
takeDirectory String
dst)
      Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity String
src String
dst

-- | Install the files listed in install-includes for a library
--
installIncludeFiles :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
installIncludeFiles :: Verbosity
-> BuildInfo -> LocalBuildInfo -> String -> String -> IO ()
installIncludeFiles Verbosity
verbosity BuildInfo
libBi LocalBuildInfo
lbi String
buildPref String
destIncludeDir = do
    let relincdirs :: [String]
relincdirs = String
"." String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
isRelative (BuildInfo -> [String]
includeDirs BuildInfo
libBi)
        incdirs :: [String]
incdirs = [ LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi String -> String -> String
</> String
dir | String
dir <- [String]
relincdirs ]
                  [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
buildPref String -> String -> String
</> String
dir | String
dir <- [String]
relincdirs ]
    [(String, String)]
incs <- (String -> IO (String, String))
-> [String] -> IO [(String, String)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ([String] -> String -> IO (String, String)
findInc [String]
incdirs) (BuildInfo -> [String]
installIncludes BuildInfo
libBi)
    [IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
      [ do Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True String
destDir
           Verbosity -> String -> String -> IO ()
installOrdinaryFile Verbosity
verbosity String
srcFile String
destFile
      | (String
relFile, String
srcFile) <- [(String, String)]
incs
      , let destFile :: String
destFile = String
destIncludeDir String -> String -> String
</> String
relFile
            destDir :: String
destDir  = String -> String
takeDirectory String
destFile ]
  where
   baseDir :: LocalBuildInfo -> String
baseDir LocalBuildInfo
lbi' = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" (String -> String
takeDirectory (String -> String) -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LocalBuildInfo -> Maybe String
cabalFilePath LocalBuildInfo
lbi')
   findInc :: [String] -> String -> IO (String, String)
findInc []         String
file = Verbosity -> String -> IO (String, String)
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity (String
"can't find include file " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file)
   findInc (String
dir:[String]
dirs) String
file = do
     let path :: String
path = String
dir String -> String -> String
</> String
file
     Bool
exists <- String -> IO Bool
doesFileExist String
path
     if Bool
exists then (String, String) -> IO (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (String
file, String
path) else [String] -> String -> IO (String, String)
findInc [String]
dirs String
file