module Distribution.Simple.Build.PathsModule (
generatePathsModule, pkgPathEnvVar
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Simple.Compiler
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.Utils (shortRelativePath)
import Distribution.System
import Distribution.Version
import qualified Distribution.Simple.Build.PathsModule.Z as Z
generatePathsModule :: PackageDescription -> LocalBuildInfo -> ComponentLocalBuildInfo -> String
generatePathsModule :: PackageDescription
-> LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
generatePathsModule PackageDescription
pkg_descr LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi = Z -> FilePath
Z.render Z.Z
{ zPackageName :: PackageName
Z.zPackageName = forall pkg. Package pkg => pkg -> PackageName
packageName PackageDescription
pkg_descr
, zVersionDigits :: FilePath
Z.zVersionDigits = forall a. Show a => a -> FilePath
show forall a b. (a -> b) -> a -> b
$ Version -> [Int]
versionNumbers forall a b. (a -> b) -> a -> b
$ forall pkg. Package pkg => pkg -> Version
packageVersion PackageDescription
pkg_descr
, zSupportsCpp :: Bool
Z.zSupportsCpp = Bool
supports_cpp
, zSupportsNoRebindableSyntax :: Bool
Z.zSupportsNoRebindableSyntax = Bool
supports_rebindable_syntax
, zAbsolute :: Bool
Z.zAbsolute = Bool
absolute
, zRelocatable :: Bool
Z.zRelocatable = LocalBuildInfo -> Bool
relocatable LocalBuildInfo
lbi
, zIsWindows :: Bool
Z.zIsWindows = Bool
isWindows
, zIsI386 :: Bool
Z.zIsI386 = Arch
buildArch forall a. Eq a => a -> a -> Bool
== Arch
I386
, zIsX8664 :: Bool
Z.zIsX8664 = Arch
buildArch forall a. Eq a => a -> a -> Bool
== Arch
X86_64
, zNot :: Bool -> Bool
Z.zNot = Bool -> Bool
not
, zManglePkgName :: PackageName -> FilePath
Z.zManglePkgName = PackageName -> FilePath
showPkgName
, zPrefix :: FilePath
Z.zPrefix = forall a. Show a => a -> FilePath
show FilePath
flat_prefix
, zBindir :: FilePath
Z.zBindir = FilePath
zBindir
, zLibdir :: FilePath
Z.zLibdir = FilePath
zLibdir
, zDynlibdir :: FilePath
Z.zDynlibdir = FilePath
zDynlibdir
, zDatadir :: FilePath
Z.zDatadir = FilePath
zDatadir
, zLibexecdir :: FilePath
Z.zLibexecdir = FilePath
zLibexecdir
, zSysconfdir :: FilePath
Z.zSysconfdir = FilePath
zSysconfdir
}
where
supports_cpp :: Bool
supports_cpp = Bool
supports_language_pragma
supports_rebindable_syntax :: Bool
supports_rebindable_syntax = Version -> Bool
ghc_newer_than ([Int] -> Version
mkVersion [Int
7,Int
0,Int
1])
supports_language_pragma :: Bool
supports_language_pragma = Version -> Bool
ghc_newer_than ([Int] -> Version
mkVersion [Int
6,Int
6,Int
1])
ghc_newer_than :: Version -> Bool
ghc_newer_than Version
minVersion =
case CompilerFlavor -> Compiler -> Maybe Version
compilerCompatVersion CompilerFlavor
GHC (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
Maybe Version
Nothing -> Bool
False
Just Version
version -> Version
version Version -> VersionRange -> Bool
`withinRange` Version -> VersionRange
orLaterVersion Version
minVersion
absolute :: Bool
absolute =
PackageDescription -> Bool
hasLibs PackageDescription
pkg_descr
Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isNothing Maybe FilePath
flat_bindirrel
Bool -> Bool -> Bool
|| Bool -> Bool
not (CompilerFlavor -> Bool
supportsRelocatableProgs (Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)))
isWindows :: Bool
isWindows = case OS
buildOS of
OS
Windows -> Bool
True
OS
_ -> Bool
False
supportsRelocatableProgs :: CompilerFlavor -> Bool
supportsRelocatableProgs CompilerFlavor
GHC = Bool
isWindows
supportsRelocatableProgs CompilerFlavor
GHCJS = Bool
isWindows
supportsRelocatableProgs CompilerFlavor
_ = Bool
False
cid :: UnitId
cid = ComponentLocalBuildInfo -> UnitId
componentUnitId ComponentLocalBuildInfo
clbi
InstallDirs
{ bindir :: forall dir. InstallDirs dir -> dir
bindir = FilePath
flat_bindir
, libdir :: forall dir. InstallDirs dir -> dir
libdir = FilePath
flat_libdir
, dynlibdir :: forall dir. InstallDirs dir -> dir
dynlibdir = FilePath
flat_dynlibdir
, datadir :: forall dir. InstallDirs dir -> dir
datadir = FilePath
flat_datadir
, libexecdir :: forall dir. InstallDirs dir -> dir
libexecdir = FilePath
flat_libexecdir
, sysconfdir :: forall dir. InstallDirs dir -> dir
sysconfdir = FilePath
flat_sysconfdir
, prefix :: forall dir. InstallDirs dir -> dir
prefix = FilePath
flat_prefix
} = PackageDescription
-> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
absoluteInstallCommandDirs PackageDescription
pkg_descr LocalBuildInfo
lbi UnitId
cid CopyDest
NoCopyDest
InstallDirs
{ bindir :: forall dir. InstallDirs dir -> dir
bindir = Maybe FilePath
flat_bindirrel
, libdir :: forall dir. InstallDirs dir -> dir
libdir = Maybe FilePath
flat_libdirrel
, dynlibdir :: forall dir. InstallDirs dir -> dir
dynlibdir = Maybe FilePath
flat_dynlibdirrel
, datadir :: forall dir. InstallDirs dir -> dir
datadir = Maybe FilePath
flat_datadirrel
, libexecdir :: forall dir. InstallDirs dir -> dir
libexecdir = Maybe FilePath
flat_libexecdirrel
, sysconfdir :: forall dir. InstallDirs dir -> dir
sysconfdir = Maybe FilePath
flat_sysconfdirrel
} = PackageId
-> LocalBuildInfo -> UnitId -> InstallDirs (Maybe FilePath)
prefixRelativeComponentInstallDirs (forall pkg. Package pkg => pkg -> PackageId
packageId PackageDescription
pkg_descr) LocalBuildInfo
lbi UnitId
cid
zBindir, zLibdir, zDynlibdir, zDatadir, zLibexecdir, zSysconfdir :: String
(FilePath
zBindir, FilePath
zLibdir, FilePath
zDynlibdir, FilePath
zDatadir, FilePath
zLibexecdir, FilePath
zSysconfdir)
| LocalBuildInfo -> Bool
relocatable LocalBuildInfo
lbi =
( forall a. Show a => a -> FilePath
show FilePath
flat_bindir_reloc
, forall a. Show a => a -> FilePath
show FilePath
flat_libdir_reloc
, forall a. Show a => a -> FilePath
show FilePath
flat_dynlibdir_reloc
, forall a. Show a => a -> FilePath
show FilePath
flat_datadir_reloc
, forall a. Show a => a -> FilePath
show FilePath
flat_libexecdir_reloc
, forall a. Show a => a -> FilePath
show FilePath
flat_sysconfdir_reloc
)
| Bool
absolute =
( forall a. Show a => a -> FilePath
show FilePath
flat_bindir
, forall a. Show a => a -> FilePath
show FilePath
flat_libdir
, forall a. Show a => a -> FilePath
show FilePath
flat_dynlibdir
, forall a. Show a => a -> FilePath
show FilePath
flat_datadir
, forall a. Show a => a -> FilePath
show FilePath
flat_libexecdir
, forall a. Show a => a -> FilePath
show FilePath
flat_sysconfdir
)
| Bool
isWindows =
( FilePath
"maybe (error \"PathsModule.generate\") id (" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Maybe FilePath
flat_bindirrel forall a. [a] -> [a] -> [a]
++ FilePath
")"
, FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
flat_libdir Maybe FilePath
flat_libdirrel
, FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
flat_dynlibdir Maybe FilePath
flat_dynlibdirrel
, FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
flat_datadir Maybe FilePath
flat_datadirrel
, FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
flat_libexecdir Maybe FilePath
flat_libexecdirrel
, FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
flat_sysconfdir Maybe FilePath
flat_sysconfdirrel
)
| Bool
otherwise =
forall a. HasCallStack => FilePath -> a
error FilePath
"panic! generatePathsModule: should never happen"
mkGetDir :: FilePath -> Maybe FilePath -> String
mkGetDir :: FilePath -> Maybe FilePath -> FilePath
mkGetDir FilePath
_ (Just FilePath
dirrel) = FilePath
"getPrefixDirRel " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
dirrel
mkGetDir FilePath
dir Maybe FilePath
Nothing = FilePath
"return " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show FilePath
dir
flat_bindir_reloc :: FilePath
flat_bindir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_bindir
flat_libdir_reloc :: FilePath
flat_libdir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_libdir
flat_dynlibdir_reloc :: FilePath
flat_dynlibdir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_dynlibdir
flat_datadir_reloc :: FilePath
flat_datadir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_datadir
flat_libexecdir_reloc :: FilePath
flat_libexecdir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_libexecdir
flat_sysconfdir_reloc :: FilePath
flat_sysconfdir_reloc = FilePath -> FilePath -> FilePath
shortRelativePath FilePath
flat_prefix FilePath
flat_sysconfdir
pkgPathEnvVar
:: PackageDescription
-> String
-> String
pkgPathEnvVar :: PackageDescription -> FilePath -> FilePath
pkgPathEnvVar PackageDescription
pkg_descr FilePath
var =
PackageName -> FilePath
showPkgName (forall pkg. Package pkg => pkg -> PackageName
packageName PackageDescription
pkg_descr) forall a. [a] -> [a] -> [a]
++ FilePath
"_" forall a. [a] -> [a] -> [a]
++ FilePath
var
showPkgName :: PackageName -> String
showPkgName :: PackageName -> FilePath
showPkgName = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
fixchar forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageName -> FilePath
unPackageName
fixchar :: Char -> Char
fixchar :: Char -> Char
fixchar Char
'-' = Char
'_'
fixchar Char
c = Char
c