{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
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,
    
    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 Data.List (stripPrefix)
import System.FilePath ((</>), (<.>), normalise)
srcPref :: FilePath -> FilePath
srcPref :: FilePath -> FilePath
srcPref FilePath
distPref = FilePath
distPref FilePath -> FilePath -> FilePath
</> FilePath
"src"
hscolourPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
hscolourPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
hscolourPref = HaddockTarget -> FilePath -> PackageDescription -> FilePath
haddockPref
haddockDirName :: HaddockTarget -> PackageDescription -> FilePath
haddockDirName :: HaddockTarget -> PackageDescription -> FilePath
haddockDirName HaddockTarget
ForDevelopment = PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageName -> FilePath)
-> (PackageDescription -> PackageName)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName
haddockDirName HaddockTarget
ForHackage = (FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-docs") (FilePath -> FilePath)
-> (PackageDescription -> FilePath)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageIdentifier -> FilePath)
-> (PackageDescription -> PackageIdentifier)
-> PackageDescription
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId
haddockPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
haddockPref :: HaddockTarget -> FilePath -> PackageDescription -> FilePath
haddockPref HaddockTarget
haddockTarget FilePath
distPref PackageDescription
pkg_descr
    = FilePath
distPref FilePath -> FilePath -> FilePath
</> FilePath
"doc" FilePath -> FilePath -> FilePath
</> FilePath
"html" FilePath -> FilePath -> FilePath
</> HaddockTarget -> PackageDescription -> FilePath
haddockDirName HaddockTarget
haddockTarget PackageDescription
pkg_descr
autogenPackageModulesDir :: LocalBuildInfo -> String
autogenPackageModulesDir :: LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
"global-autogen"
autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> String
autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi = LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> FilePath -> FilePath
</> FilePath
"autogen"
cppHeaderName :: String
 = FilePath
"cabal_macros.h"
autogenPathsModuleName :: PackageDescription -> ModuleName
autogenPathsModuleName :: PackageDescription -> ModuleName
autogenPathsModuleName PackageDescription
pkg_descr =
  FilePath -> ModuleName
forall a. IsString a => FilePath -> a
ModuleName.fromString (FilePath -> ModuleName) -> FilePath -> ModuleName
forall a b. (a -> b) -> a -> b
$
    FilePath
"Paths_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar (PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageDescription -> PackageName
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 -> FilePath
haddockName PackageDescription
pkg_descr = PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (PackageDescription -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName PackageDescription
pkg_descr) FilePath -> FilePath -> FilePath
<.> FilePath
"haddock"
getLibSourceFiles :: Verbosity
                     -> LocalBuildInfo
                     -> Library
                     -> ComponentLocalBuildInfo
                     -> IO [(ModuleName.ModuleName, FilePath)]
getLibSourceFiles :: Verbosity
-> LocalBuildInfo
-> Library
-> ComponentLocalBuildInfo
-> IO [(ModuleName, FilePath)]
getLibSourceFiles Verbosity
verbosity LocalBuildInfo
lbi Library
lib ComponentLocalBuildInfo
clbi = Verbosity
-> [FilePath] -> [ModuleName] -> IO [(ModuleName, FilePath)]
getSourceFiles Verbosity
verbosity [FilePath]
searchpaths [ModuleName]
modules
  where
    bi :: BuildInfo
bi               = Library -> BuildInfo
libBuildInfo Library
lib
    modules :: [ModuleName]
modules          = Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi
    searchpaths :: [FilePath]
searchpaths      = LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
                     [ LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                     , LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi ]
getExeSourceFiles :: Verbosity
                     -> LocalBuildInfo
                     -> Executable
                     -> ComponentLocalBuildInfo
                     -> IO [(ModuleName.ModuleName, FilePath)]
getExeSourceFiles :: Verbosity
-> LocalBuildInfo
-> Executable
-> ComponentLocalBuildInfo
-> IO [(ModuleName, FilePath)]
getExeSourceFiles Verbosity
verbosity LocalBuildInfo
lbi Executable
exe ComponentLocalBuildInfo
clbi = do
    [(ModuleName, FilePath)]
moduleFiles <- Verbosity
-> [FilePath] -> [ModuleName] -> IO [(ModuleName, FilePath)]
getSourceFiles Verbosity
verbosity [FilePath]
searchpaths [ModuleName]
modules
    FilePath
srcMainPath <- Verbosity -> [FilePath] -> FilePath -> IO FilePath
findFileEx Verbosity
verbosity (BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi) (Executable -> FilePath
modulePath Executable
exe)
    [(ModuleName, FilePath)] -> IO [(ModuleName, FilePath)]
forall (m :: * -> *) a. Monad m => a -> m a
return ((ModuleName
ModuleName.main, FilePath
srcMainPath) (ModuleName, FilePath)
-> [(ModuleName, FilePath)] -> [(ModuleName, FilePath)]
forall a. a -> [a] -> [a]
: [(ModuleName, FilePath)]
moduleFiles)
  where
    bi :: BuildInfo
bi          = Executable -> BuildInfo
buildInfo Executable
exe
    modules :: [ModuleName]
modules     = BuildInfo -> [ModuleName]
otherModules BuildInfo
bi
    searchpaths :: [FilePath]
searchpaths = LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi
                FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: LocalBuildInfo -> Executable -> FilePath
exeBuildDir LocalBuildInfo
lbi Executable
exe FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi
getFLibSourceFiles :: Verbosity
                   -> LocalBuildInfo
                   -> ForeignLib
                   -> ComponentLocalBuildInfo
                   -> IO [(ModuleName.ModuleName, FilePath)]
getFLibSourceFiles :: Verbosity
-> LocalBuildInfo
-> ForeignLib
-> ComponentLocalBuildInfo
-> IO [(ModuleName, FilePath)]
getFLibSourceFiles Verbosity
verbosity LocalBuildInfo
lbi ForeignLib
flib ComponentLocalBuildInfo
clbi = Verbosity
-> [FilePath] -> [ModuleName] -> IO [(ModuleName, FilePath)]
getSourceFiles Verbosity
verbosity [FilePath]
searchpaths [ModuleName]
modules
  where
    bi :: BuildInfo
bi          = ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib
    modules :: [ModuleName]
modules     = BuildInfo -> [ModuleName]
otherModules BuildInfo
bi
    searchpaths :: [FilePath]
searchpaths = LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi
                FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: BuildInfo -> [FilePath]
hsSourceDirs BuildInfo
bi
getSourceFiles :: Verbosity -> [FilePath]
                  -> [ModuleName.ModuleName]
                  -> IO [(ModuleName.ModuleName, FilePath)]
getSourceFiles :: Verbosity
-> [FilePath] -> [ModuleName] -> IO [(ModuleName, FilePath)]
getSourceFiles Verbosity
verbosity [FilePath]
dirs [ModuleName]
modules = ((ModuleName -> IO (ModuleName, FilePath))
 -> [ModuleName] -> IO [(ModuleName, FilePath)])
-> [ModuleName]
-> (ModuleName -> IO (ModuleName, FilePath))
-> IO [(ModuleName, FilePath)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ModuleName -> IO (ModuleName, FilePath))
-> [ModuleName] -> IO [(ModuleName, FilePath)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse [ModuleName]
modules ((ModuleName -> IO (ModuleName, FilePath))
 -> IO [(ModuleName, FilePath)])
-> (ModuleName -> IO (ModuleName, FilePath))
-> IO [(ModuleName, FilePath)]
forall a b. (a -> b) -> a -> b
$ \ModuleName
m -> (FilePath -> (ModuleName, FilePath))
-> IO FilePath -> IO (ModuleName, FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) ModuleName
m) (IO FilePath -> IO (ModuleName, FilePath))
-> IO FilePath -> IO (ModuleName, FilePath)
forall a b. (a -> b) -> a -> b
$
    [FilePath] -> [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileWithExtension [FilePath
"hs", FilePath
"lhs", FilePath
"hsig", FilePath
"lhsig"] [FilePath]
dirs (ModuleName -> FilePath
ModuleName.toFilePath ModuleName
m)
      IO (Maybe FilePath)
-> (Maybe FilePath -> IO FilePath) -> IO FilePath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO FilePath
-> (FilePath -> IO FilePath) -> Maybe FilePath -> IO FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (ModuleName -> IO FilePath
forall a a. Pretty a => a -> IO a
notFound ModuleName
m) (FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> IO FilePath)
-> (FilePath -> FilePath) -> FilePath -> IO FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
normalise)
  where
    notFound :: a -> IO a
notFound a
module_ = Verbosity -> FilePath -> IO a
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO a) -> FilePath -> IO a
forall a b. (a -> b) -> a -> b
$ FilePath
"can't find source for module " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ a -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow a
module_
exeBuildDir :: LocalBuildInfo -> Executable -> FilePath
exeBuildDir :: LocalBuildInfo -> Executable -> FilePath
exeBuildDir LocalBuildInfo
lbi Executable
exe = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm FilePath -> FilePath -> FilePath
</> FilePath
nm FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
  where
    nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ Executable -> UnqualComponentName
exeName Executable
exe
flibBuildDir :: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildDir :: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm FilePath -> FilePath -> FilePath
</> FilePath
nm FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
  where
    nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
mkGenericStaticLibName :: String -> String
mkGenericStaticLibName :: FilePath -> FilePath
mkGenericStaticLibName FilePath
lib = FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
lib FilePath -> FilePath -> FilePath
<.> FilePath
"a"
mkLibName :: UnitId -> String
mkLibName :: UnitId -> FilePath
mkLibName UnitId
lib = FilePath -> FilePath
mkGenericStaticLibName (UnitId -> FilePath
getHSLibraryName UnitId
lib)
mkProfLibName :: UnitId -> String
mkProfLibName :: UnitId -> FilePath
mkProfLibName UnitId
lib =  FilePath -> FilePath
mkGenericStaticLibName (UnitId -> FilePath
getHSLibraryName UnitId
lib FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_p")
mkGenericSharedLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedLibName :: Platform -> CompilerId -> FilePath -> FilePath
mkGenericSharedLibName Platform
platform (CompilerId CompilerFlavor
compilerFlavor Version
compilerVersion) FilePath
lib
  = [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [ FilePath
"lib", FilePath
lib, FilePath
"-", FilePath
comp FilePath -> FilePath -> FilePath
<.> Platform -> FilePath
dllExtension Platform
platform ]
  where comp :: FilePath
comp = CompilerFlavor -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow CompilerFlavor
compilerFlavor FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow Version
compilerVersion
mkSharedLibName :: Platform -> CompilerId -> UnitId -> String
mkSharedLibName :: Platform -> CompilerId -> UnitId -> FilePath
mkSharedLibName Platform
platform CompilerId
comp UnitId
lib
  = Platform -> CompilerId -> FilePath -> FilePath
mkGenericSharedLibName Platform
platform CompilerId
comp (UnitId -> FilePath
getHSLibraryName UnitId
lib)
mkStaticLibName :: Platform -> CompilerId -> UnitId -> String
mkStaticLibName :: Platform -> CompilerId -> UnitId -> FilePath
mkStaticLibName Platform
platform (CompilerId CompilerFlavor
compilerFlavor Version
compilerVersion) UnitId
lib
  = FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnitId -> FilePath
getHSLibraryName UnitId
lib FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
comp FilePath -> FilePath -> FilePath
<.> Platform -> FilePath
staticLibExtension Platform
platform
  where comp :: FilePath
comp = CompilerFlavor -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow CompilerFlavor
compilerFlavor FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow Version
compilerVersion
mkGenericSharedBundledLibName :: Platform -> CompilerId -> String -> String
mkGenericSharedBundledLibName :: Platform -> CompilerId -> FilePath -> FilePath
mkGenericSharedBundledLibName Platform
platform CompilerId
comp FilePath
lib
  | FilePath
"HS" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
lib
    = Platform -> CompilerId -> FilePath -> FilePath
mkGenericSharedLibName Platform
platform CompilerId
comp FilePath
lib
  | Just FilePath
lib' <- FilePath -> FilePath -> Maybe FilePath
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix FilePath
"C" FilePath
lib
    = FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
lib' FilePath -> FilePath -> FilePath
<.> Platform -> FilePath
dllExtension Platform
platform
  | Bool
otherwise
    = FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error (FilePath
"Don't understand library name " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
lib)
exeExtension :: Platform -> String
exeExtension :: Platform -> FilePath
exeExtension (Platform Arch
_arch OS
os) = case OS
os of
                   OS
Windows -> FilePath
"exe"
                   OS
_       -> FilePath
""
objExtension :: String
objExtension :: FilePath
objExtension = FilePath
"o"
dllExtension :: Platform -> String
dllExtension :: Platform -> FilePath
dllExtension (Platform Arch
_arch OS
os)= case OS
os of
                   OS
Windows -> FilePath
"dll"
                   OS
OSX     -> FilePath
"dylib"
                   OS
_       -> FilePath
"so"
staticLibExtension :: Platform -> String
staticLibExtension :: Platform -> FilePath
staticLibExtension (Platform Arch
_arch OS
os) = case OS
os of
                       OS
Windows -> FilePath
"lib"
                       OS
_       -> FilePath
"a"