{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.BuildPaths
-- Copyright   :  Isaac Jones 2003-2004,
--                Duncan Coutts 2008
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- A bunch of dirs, paths and file names used for intermediate build steps.
--

module Distribution.Simple.BuildPaths (
    defaultDistPref, srcPref,
    haddockDirName, hscolourPref, haddockPref,
    autogenPackageModulesDir,
    autogenComponentModulesDir,

    autogenPathsModuleName,
    cppHeaderName,
    haddockName,

    mkGenericStaticLibName,
    mkLibName,
    mkProfLibName,
    mkGenericSharedLibName,
    mkSharedLibName,
    mkStaticLibName,
    mkGenericSharedBundledLibName,

    exeExtension,
    objExtension,
    dllExtension,
    staticLibExtension,
    -- * Source files & build directories
    getSourceFiles, getLibSourceFiles, getExeSourceFiles,
    getFLibSourceFiles, exeBuildDir, flibBuildDir,
  ) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Package
import Distribution.ModuleName as ModuleName
import Distribution.Compiler
import Distribution.PackageDescription
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.Setup
import Distribution.Pretty
import Distribution.System
import Distribution.Verbosity
import Distribution.Simple.Utils
import Distribution.Utils.Path

import Data.List (stripPrefix)
import System.FilePath ((</>), (<.>), normalise)

-- ---------------------------------------------------------------------------
-- Build directories and files

srcPref :: FilePath -> FilePath
srcPref :: String -> String
srcPref String
distPref = String
distPref String -> String -> String
</> String
"src"

hscolourPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
hscolourPref :: HaddockTarget -> String -> PackageDescription -> String
hscolourPref = HaddockTarget -> String -> PackageDescription -> String
haddockPref

-- | This is the name of the directory in which the generated haddocks
-- should be stored. It does not include the @<dist>/doc/html@ prefix.
haddockDirName :: HaddockTarget -> PackageDescription -> FilePath
haddockDirName :: HaddockTarget -> PackageDescription -> String
haddockDirName HaddockTarget
ForDevelopment = forall a. Pretty a => a -> String
prettyShow forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall pkg. Package pkg => pkg -> PackageName
packageName
haddockDirName HaddockTarget
ForHackage = (forall a. [a] -> [a] -> [a]
++ String
"-docs") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Pretty a => a -> String
prettyShow forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall pkg. Package pkg => pkg -> PackageIdentifier
packageId

-- | The directory to which generated haddock documentation should be written.
haddockPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
haddockPref :: HaddockTarget -> String -> PackageDescription -> String
haddockPref HaddockTarget
haddockTarget String
distPref PackageDescription
pkg_descr
    = String
distPref String -> String -> String
</> String
"doc" String -> String -> String
</> String
"html" String -> String -> String
</> HaddockTarget -> PackageDescription -> String
haddockDirName HaddockTarget
haddockTarget PackageDescription
pkg_descr

-- | The directory in which we put auto-generated modules for EVERY
-- component in the package.
autogenPackageModulesDir :: LocalBuildInfo -> String
autogenPackageModulesDir :: LocalBuildInfo -> String
autogenPackageModulesDir LocalBuildInfo
lbi = LocalBuildInfo -> String
buildDir LocalBuildInfo
lbi String -> String -> String
</> String
"global-autogen"

-- | The directory in which we put auto-generated modules for a
-- particular component.
autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi = LocalBuildInfo -> ComponentLocalBuildInfo -> String
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi String -> String -> String
</> String
"autogen"
-- NB: Look at 'checkForeignDeps' for where a simplified version of this
-- has been copy-pasted.

cppHeaderName :: String
cppHeaderName :: String
cppHeaderName = String
"cabal_macros.h"

-- | The name of the auto-generated Paths_* module associated with a package
autogenPathsModuleName :: PackageDescription -> ModuleName
autogenPathsModuleName :: PackageDescription -> ModuleName
autogenPathsModuleName PackageDescription
pkg_descr =
  forall a. IsString a => String -> a
ModuleName.fromString forall a b. (a -> b) -> a -> b
$
    String
"Paths_" forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar (forall a. Pretty a => a -> String
prettyShow (forall pkg. Package pkg => pkg -> PackageName
packageName PackageDescription
pkg_descr))
  where fixchar :: Char -> Char
fixchar Char
'-' = Char
'_'
        fixchar Char
c   = Char
c

haddockName :: PackageDescription -> FilePath
haddockName :: PackageDescription -> String
haddockName PackageDescription
pkg_descr = forall a. Pretty a => a -> String
prettyShow (forall pkg. Package pkg => pkg -> PackageName
packageName PackageDescription
pkg_descr) String -> String -> String
<.> String
"haddock"

-- -----------------------------------------------------------------------------
-- Source File helper

getLibSourceFiles :: Verbosity
                     -> LocalBuildInfo
                     -> Library
                     -> ComponentLocalBuildInfo
                     -> IO [(ModuleName.ModuleName, FilePath)]
getLibSourceFiles :: Verbosity
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO [(ModuleName, String)]
getLibSourceFiles Verbosity
verbosity LocalBuildInfo
lbi Library
lib ComponentLocalBuildInfo
clbi = Verbosity -> [String] -> [ModuleName] -> IO [(ModuleName, String)]
getSourceFiles Verbosity
verbosity [String]
searchpaths [ModuleName]
modules
  where
    bi :: BuildInfo
bi               = Library -> BuildInfo
libBuildInfo Library
lib
    modules :: [ModuleName]
modules          = Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi
    searchpaths :: [String]
searchpaths      = LocalBuildInfo -> ComponentLocalBuildInfo -> String
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) forall a. [a] -> [a] -> [a]
++
                     [ LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                     , LocalBuildInfo -> String
autogenPackageModulesDir LocalBuildInfo
lbi ]

getExeSourceFiles :: Verbosity
                     -> LocalBuildInfo
                     -> Executable
                     -> ComponentLocalBuildInfo
                     -> IO [(ModuleName.ModuleName, FilePath)]
getExeSourceFiles :: Verbosity
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO [(ModuleName, String)]
getExeSourceFiles Verbosity
verbosity LocalBuildInfo
lbi Executable
exe ComponentLocalBuildInfo
clbi = do
    [(ModuleName, String)]
moduleFiles <- Verbosity -> [String] -> [ModuleName] -> IO [(ModuleName, String)]
getSourceFiles Verbosity
verbosity [String]
searchpaths [ModuleName]
modules
    String
srcMainPath <- Verbosity -> [String] -> String -> IO String
findFileEx Verbosity
verbosity (forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
getSymbolicPath forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) (Executable -> String
modulePath Executable
exe)
    forall (m :: * -> *) a. Monad m => a -> m a
return ((ModuleName
ModuleName.main, String
srcMainPath) forall a. a -> [a] -> [a]
: [(ModuleName, String)]
moduleFiles)
  where
    bi :: BuildInfo
bi          = Executable -> BuildInfo
buildInfo Executable
exe
    modules :: [ModuleName]
modules     = BuildInfo -> [ModuleName]
otherModules BuildInfo
bi
    searchpaths :: [String]
searchpaths = LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                forall a. a -> [a] -> [a]
: LocalBuildInfo -> String
autogenPackageModulesDir LocalBuildInfo
lbi
                forall a. a -> [a] -> [a]
: LocalBuildInfo -> Executable -> String
exeBuildDir LocalBuildInfo
lbi Executable
exe forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi)

getFLibSourceFiles :: Verbosity
                   -> LocalBuildInfo
                   -> ForeignLib
                   -> ComponentLocalBuildInfo
                   -> IO [(ModuleName.ModuleName, FilePath)]
getFLibSourceFiles :: Verbosity
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO [(ModuleName, String)]
getFLibSourceFiles Verbosity
verbosity LocalBuildInfo
lbi ForeignLib
flib ComponentLocalBuildInfo
clbi = Verbosity -> [String] -> [ModuleName] -> IO [(ModuleName, String)]
getSourceFiles Verbosity
verbosity [String]
searchpaths [ModuleName]
modules
  where
    bi :: BuildInfo
bi          = ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib
    modules :: [ModuleName]
modules     = BuildInfo -> [ModuleName]
otherModules BuildInfo
bi
    searchpaths :: [String]
searchpaths = LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                forall a. a -> [a] -> [a]
: LocalBuildInfo -> String
autogenPackageModulesDir LocalBuildInfo
lbi
                forall a. a -> [a] -> [a]
: LocalBuildInfo -> ForeignLib -> String
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall from to. SymbolicPath from to -> String
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi)

getSourceFiles :: Verbosity -> [FilePath]
                  -> [ModuleName.ModuleName]
                  -> IO [(ModuleName.ModuleName, FilePath)]
getSourceFiles :: Verbosity -> [String] -> [ModuleName] -> IO [(ModuleName, String)]
getSourceFiles Verbosity
verbosity [String]
dirs [ModuleName]
modules = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse [ModuleName]
modules forall a b. (a -> b) -> a -> b
$ \ModuleName
m -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) ModuleName
m) forall a b. (a -> b) -> a -> b
$
    [String] -> [String] -> String -> IO (Maybe String)
findFileWithExtension [String
"hs", String
"lhs", String
"hsig", String
"lhsig"] [String]
dirs (ModuleName -> String
ModuleName.toFilePath ModuleName
m)
      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall {a} {a}. Pretty a => a -> IO a
notFound ModuleName
m) (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
normalise)
  where
    notFound :: a -> IO a
notFound a
module_ = forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ String
"can't find source for module " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow a
module_

-- | The directory where we put build results for an executable
exeBuildDir :: LocalBuildInfo -> Executable -> FilePath
exeBuildDir :: LocalBuildInfo -> Executable -> String
exeBuildDir LocalBuildInfo
lbi Executable
exe = LocalBuildInfo -> String
buildDir LocalBuildInfo
lbi String -> String -> String
</> String
nm String -> String -> String
</> String
nm forall a. [a] -> [a] -> [a]
++ String
"-tmp"
  where
    nm :: String
nm = UnqualComponentName -> String
unUnqualComponentName forall a b. (a -> b) -> a -> b
$ Executable -> UnqualComponentName
exeName Executable
exe

-- | The directory where we put build results for a foreign library
flibBuildDir :: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildDir :: LocalBuildInfo -> ForeignLib -> String
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib = LocalBuildInfo -> String
buildDir LocalBuildInfo
lbi String -> String -> String
</> String
nm String -> String -> String
</> String
nm forall a. [a] -> [a] -> [a]
++ String
"-tmp"
  where
    nm :: String
nm = UnqualComponentName -> String
unUnqualComponentName forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib

-- ---------------------------------------------------------------------------
-- Library file names

-- | Create a library name for a static library from a given name.
-- Prepends @lib@ and appends the static library extension (@.a@).
mkGenericStaticLibName :: String -> String
mkGenericStaticLibName :: String -> String
mkGenericStaticLibName String
lib = String
"lib" forall a. [a] -> [a] -> [a]
++ String
lib String -> String -> String
<.> String
"a"

mkLibName :: UnitId -> String
mkLibName :: UnitId -> String
mkLibName UnitId
lib = String -> String
mkGenericStaticLibName (UnitId -> String
getHSLibraryName UnitId
lib)

mkProfLibName :: UnitId -> String
mkProfLibName :: UnitId -> String
mkProfLibName UnitId
lib =  String -> String
mkGenericStaticLibName (UnitId -> String
getHSLibraryName UnitId
lib forall a. [a] -> [a] -> [a]
++ String
"_p")

-- | Create a library name for a shared library from a given name.
-- Prepends @lib@ and appends the @-\<compilerFlavour\>\<compilerVersion\>@
-- as well as the shared library extension.
mkGenericSharedLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedLibName Platform
platform (CompilerId CompilerFlavor
compilerFlavor Version
compilerVersion) String
lib
  = forall a. Monoid a => [a] -> a
mconcat [ String
"lib", String
lib, String
"-", String
comp String -> String -> String
<.> Platform -> String
dllExtension Platform
platform ]
  where comp :: String
comp = forall a. Pretty a => a -> String
prettyShow CompilerFlavor
compilerFlavor forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow Version
compilerVersion

-- Implement proper name mangling for dynamical shared objects
-- @libHS\<packagename\>-\<compilerFlavour\>\<compilerVersion\>@
-- e.g. @libHSbase-2.1-ghc6.6.1.so@
mkSharedLibName :: Platform -> CompilerId -> UnitId -> String
mkSharedLibName :: Platform -> CompilerId -> UnitId -> String
mkSharedLibName Platform
platform CompilerId
comp UnitId
lib
  = Platform -> CompilerId -> String -> String
mkGenericSharedLibName Platform
platform CompilerId
comp (UnitId -> String
getHSLibraryName UnitId
lib)

-- Static libs are named the same as shared libraries, only with
-- a different extension.
mkStaticLibName :: Platform -> CompilerId -> UnitId -> String
mkStaticLibName :: Platform -> CompilerId -> UnitId -> String
mkStaticLibName Platform
platform (CompilerId CompilerFlavor
compilerFlavor Version
compilerVersion) UnitId
lib
  = String
"lib" forall a. [a] -> [a] -> [a]
++ UnitId -> String
getHSLibraryName UnitId
lib forall a. [a] -> [a] -> [a]
++ String
"-" forall a. [a] -> [a] -> [a]
++ String
comp String -> String -> String
<.> Platform -> String
staticLibExtension Platform
platform
  where comp :: String
comp = forall a. Pretty a => a -> String
prettyShow CompilerFlavor
compilerFlavor forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow Version
compilerVersion

-- | Create a library name for a bundled shared library from a given name.
-- This matches the naming convention for shared libraries as implemented in
-- GHC's packageHsLibs function in the Packages module.
-- If the given name is prefixed with HS, then this prepends 'lib' and appends
-- the compiler flavour/version and shared library extension e.g.:
--     "HSrts-1.0" -> "libHSrts-1.0-ghc8.7.20190109.so"
-- Otherwise the given name should be prefixed with 'C', then this strips the
-- 'C', prepends 'lib' and appends the shared library extension e.g.:
--     "Cffi" -> "libffi.so"
mkGenericSharedBundledLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedBundledLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedBundledLibName Platform
platform CompilerId
comp String
lib
  | String
"HS" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
lib
    = Platform -> CompilerId -> String -> String
mkGenericSharedLibName Platform
platform CompilerId
comp String
lib
  | Just String
lib' <- forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
"C" String
lib
    = String
"lib" forall a. [a] -> [a] -> [a]
++ String
lib' String -> String -> String
<.> Platform -> String
dllExtension Platform
platform
  | Bool
otherwise
    = forall a. HasCallStack => String -> a
error (String
"Don't understand library name " forall a. [a] -> [a] -> [a]
++ String
lib)

-- ------------------------------------------------------------
-- * Platform file extensions
-- ------------------------------------------------------------

-- | Default extension for executable files on the current platform.
-- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
exeExtension :: Platform -> String
exeExtension :: Platform -> String
exeExtension (Platform Arch
_arch OS
os) = case OS
os of
                   OS
Windows -> String
"exe"
                   OS
_       -> String
""

-- | Extension for object files. For GHC the extension is @\"o\"@.
objExtension :: String
objExtension :: String
objExtension = String
"o"

-- | Extension for dynamically linked (or shared) libraries
-- (typically @\"so\"@ on Unix and @\"dll\"@ on Windows)
dllExtension :: Platform -> String
dllExtension :: Platform -> String
dllExtension (Platform Arch
_arch OS
os)= case OS
os of
                   OS
Windows -> String
"dll"
                   OS
OSX     -> String
"dylib"
                   OS
_       -> String
"so"

-- | Extension for static libraries
--
-- TODO: Here, as well as in dllExtension, it's really the target OS that we're
-- interested in, not the build OS.
staticLibExtension :: Platform -> String
staticLibExtension :: Platform -> String
staticLibExtension (Platform Arch
_arch OS
os) = case OS
os of
                       OS
Windows -> String
"lib"
                       OS
_       -> String
"a"