{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.GHC.Build.Utils where
import Distribution.Compat.Prelude
import Prelude ()
import Control.Monad (msum)
import Data.Char (isLower)
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.PackageDescription as PD
import Distribution.PackageDescription.Utils (cabalBug)
import Distribution.Simple.BuildPaths
import Distribution.Simple.BuildWay
import Distribution.Simple.Compiler
import qualified Distribution.Simple.GHC.Internal as Internal
import Distribution.Simple.Program.GHC
import Distribution.Simple.Setup.Common
import Distribution.Simple.Utils
import Distribution.System
import Distribution.Types.LocalBuildInfo
( LocalBuildInfo (hostPlatform)
)
import Distribution.Utils.Path
import Distribution.Verbosity
import System.FilePath
( replaceExtension
, takeExtension
)
findExecutableMain
:: Verbosity
-> Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir build)
-> (BuildInfo, RelativePath Source File)
-> IO (SymbolicPath Pkg File)
findExecutableMain :: forall build.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir build)
-> (BuildInfo, RelativePath Source 'File)
-> IO (SymbolicPath Pkg 'File)
findExecutableMain Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir build)
buildDir (BuildInfo
bnfo, RelativePath Source 'File
modPath) =
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
-> RelativePath Source 'File
-> IO (SymbolicPath Pkg 'File)
forall searchDir (allowAbsolute :: AllowAbsolute).
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (SymbolicPathX allowAbsolute Pkg 'File)
findFileCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir (SymbolicPath Pkg ('Dir build)
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPath Pkg ('Dir build)
buildDir SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
forall a. a -> [a] -> [a]
: BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bnfo) RelativePath Source 'File
modPath
supportsDynamicToo :: Compiler -> Bool
supportsDynamicToo :: Compiler -> Bool
supportsDynamicToo = FilePath -> Compiler -> Bool
Internal.ghcLookupProperty FilePath
"Support dynamic-too"
compilerBuildWay :: Compiler -> BuildWay
compilerBuildWay :: Compiler -> BuildWay
compilerBuildWay Compiler
c =
case (Compiler -> Bool
isDynamic Compiler
c, Compiler -> Bool
isProfiled Compiler
c) of
(Bool
True, Bool
True) -> BuildWay
ProfDynWay
(Bool
True, Bool
False) -> BuildWay
DynWay
(Bool
False, Bool
True) -> BuildWay
ProfWay
(Bool
False, Bool
False) -> BuildWay
StaticWay
isDynamic :: Compiler -> Bool
isDynamic :: Compiler -> Bool
isDynamic = FilePath -> Compiler -> Bool
Internal.ghcLookupProperty FilePath
"GHC Dynamic"
isProfiled :: Compiler -> Bool
isProfiled :: Compiler -> Bool
isProfiled = FilePath -> Compiler -> Bool
Internal.ghcLookupProperty FilePath
"GHC Profiled"
withDynFLib :: ForeignLib -> Bool
withDynFLib :: ForeignLib -> Bool
withDynFLib ForeignLib
flib =
case ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib of
ForeignLibType
ForeignLibNativeShared ->
ForeignLibOption
ForeignLibStandalone ForeignLibOption -> [ForeignLibOption] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ForeignLib -> [ForeignLibOption]
foreignLibOptions ForeignLib
flib
ForeignLibType
ForeignLibNativeStatic ->
Bool
False
ForeignLibType
ForeignLibTypeUnknown ->
FilePath -> Bool
forall a. FilePath -> a
cabalBug FilePath
"unknown foreign lib type"
isCxx :: FilePath -> Bool
isCxx :: FilePath -> Bool
isCxx FilePath
fp = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (FilePath -> FilePath
takeExtension FilePath
fp) [FilePath
".cpp", FilePath
".cxx", FilePath
".c++"]
isC :: FilePath -> Bool
isC :: FilePath -> Bool
isC FilePath
fp = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (FilePath -> FilePath
takeExtension FilePath
fp) [FilePath
".c"]
isHaskell :: FilePath -> Bool
isHaskell :: FilePath -> Bool
isHaskell FilePath
fp = FilePath -> [FilePath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem (FilePath -> FilePath
takeExtension FilePath
fp) [FilePath
".hs", FilePath
".lhs"]
checkNeedsRecompilation
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg File
-> GhcOptions
-> IO Bool
checkNeedsRecompilation :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> IO Bool
checkNeedsRecompilation Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts =
SymbolicPath Pkg 'File -> FilePath
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> FilePath
i SymbolicPath Pkg 'File
filename FilePath -> FilePath -> IO Bool
`moreRecentFile` FilePath
oname
where
oname :: FilePath
oname = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> FilePath
getObjectFileName Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = Maybe (SymbolicPath 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 (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
getObjectFileName
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg File
-> GhcOptions
-> FilePath
getObjectFileName :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg 'File -> GhcOptions -> FilePath
getObjectFileName Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg 'File
filename GhcOptions
opts = FilePath
oname
where
i :: SymbolicPathX allowAbsolute Pkg to -> FilePath
i = Maybe (SymbolicPath 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 (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
odir :: FilePath
odir = 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
$ Flag (SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts))
-> SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts)
forall a. WithCallStack (Flag a -> a)
fromFlag (GhcOptions
-> Flag (SymbolicPathX 'AllowAbsolute Pkg ('Dir Artifacts))
ghcOptObjDir GhcOptions
opts)
oext :: FilePath
oext = FilePath -> Flag FilePath -> FilePath
forall a. a -> Flag a -> a
fromFlagOrDefault FilePath
"o" (GhcOptions -> Flag FilePath
ghcOptObjSuffix GhcOptions
opts)
oname :: FilePath
oname = FilePath
odir FilePath -> FilePath -> FilePath
forall p q r. PathLike p q r => p -> q -> r
</> FilePath -> FilePath -> FilePath
replaceExtension (SymbolicPath Pkg 'File -> FilePath
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> FilePath
getSymbolicPath SymbolicPath Pkg 'File
filename) FilePath
oext
flibTargetName :: LocalBuildInfo -> ForeignLib -> String
flibTargetName :: LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib =
case (OS
os, ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib) of
(OS
Windows, ForeignLibType
ForeignLibNativeShared) -> FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"dll"
(OS
Windows, ForeignLibType
ForeignLibNativeStatic) -> FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
"lib"
(OS
Linux, ForeignLibType
ForeignLibNativeShared) -> FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> FilePath
versionedExt
(OS
_other, ForeignLibType
ForeignLibNativeShared) ->
FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
dllExtension (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi)
(OS
_other, ForeignLibType
ForeignLibNativeStatic) ->
FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> Platform -> FilePath
staticLibExtension (LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi)
(OS
_any, ForeignLibType
ForeignLibTypeUnknown) -> FilePath -> FilePath
forall a. FilePath -> a
cabalBug FilePath
"unknown foreign lib type"
where
nm :: String
nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
os :: OS
Platform Arch
_ OS
os = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
versionedExt :: String
versionedExt :: FilePath
versionedExt =
let nums :: [Int]
nums = ForeignLib -> OS -> [Int]
foreignLibVersion ForeignLib
flib OS
os
in (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
(<.>) FilePath
"so" ((Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Int -> FilePath
forall a. Show a => a -> FilePath
show [Int]
nums)
flibBuildName :: LocalBuildInfo -> ForeignLib -> String
flibBuildName :: LocalBuildInfo -> ForeignLib -> FilePath
flibBuildName LocalBuildInfo
lbi ForeignLib
flib
| (OS
os, ForeignLib -> ForeignLibType
foreignLibType ForeignLib
flib)
(OS, ForeignLibType) -> (OS, ForeignLibType) -> Bool
forall a. Eq a => a -> a -> Bool
== (OS
Linux, ForeignLibType
ForeignLibNativeShared) =
let nums :: [Int]
nums = ForeignLib -> OS -> [Int]
foreignLibVersion ForeignLib
flib OS
os
in FilePath
"lib" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
nm FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> (FilePath -> FilePath -> FilePath)
-> FilePath -> [FilePath] -> FilePath
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
(<.>) FilePath
"so" ((Int -> FilePath) -> [Int] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Int -> FilePath
forall a. Show a => a -> FilePath
show (Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
1 [Int]
nums))
| Bool
otherwise = LocalBuildInfo -> ForeignLib -> FilePath
flibTargetName LocalBuildInfo
lbi ForeignLib
flib
where
os :: OS
Platform Arch
_ OS
os = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
nm :: String
nm :: FilePath
nm = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ ForeignLib -> UnqualComponentName
foreignLibName ForeignLib
flib
exeTargetName :: Platform -> UnqualComponentName -> String
exeTargetName :: Platform -> UnqualComponentName -> FilePath
exeTargetName Platform
platform UnqualComponentName
name = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
name FilePath -> FilePath -> FilePath
`withExt` Platform -> FilePath
exeExtension Platform
platform
where
withExt :: FilePath -> String -> FilePath
withExt :: FilePath -> FilePath -> FilePath
withExt FilePath
fp FilePath
ext = FilePath
fp FilePath -> FilePath -> FilePath
forall p. FileLike p => p -> FilePath -> p
<.> if FilePath -> FilePath
takeExtension FilePath
fp FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= (Char
'.' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
ext) then FilePath
ext else FilePath
""
exeMainModuleName
:: BuildInfo
-> ModuleName
exeMainModuleName :: BuildInfo -> ModuleName
exeMainModuleName BuildInfo
bnfo =
ModuleName -> Maybe ModuleName -> ModuleName
forall a. a -> Maybe a -> a
fromMaybe ModuleName
ModuleName.main (Maybe ModuleName -> ModuleName) -> Maybe ModuleName -> ModuleName
forall a b. (a -> b) -> a -> b
$ [Maybe ModuleName] -> Maybe ModuleName
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum ([Maybe ModuleName] -> Maybe ModuleName)
-> [Maybe ModuleName] -> Maybe ModuleName
forall a b. (a -> b) -> a -> b
$ [Maybe ModuleName] -> [Maybe ModuleName]
forall a. [a] -> [a]
reverse ([Maybe ModuleName] -> [Maybe ModuleName])
-> [Maybe ModuleName] -> [Maybe ModuleName]
forall a b. (a -> b) -> a -> b
$ (FilePath -> Maybe ModuleName) -> [FilePath] -> [Maybe ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Maybe ModuleName
decodeMainIsArg ([FilePath] -> [Maybe ModuleName])
-> [FilePath] -> [Maybe ModuleName]
forall a b. (a -> b) -> a -> b
$ [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
ghcopts
where
ghcopts :: [FilePath]
ghcopts = CompilerFlavor -> BuildInfo -> [FilePath]
hcOptions CompilerFlavor
GHC BuildInfo
bnfo
findIsMainArgs :: [FilePath] -> [FilePath]
findIsMainArgs [] = []
findIsMainArgs (FilePath
"-main-is" : FilePath
arg : [FilePath]
rest) = FilePath
arg FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
rest
findIsMainArgs (FilePath
_ : [FilePath]
rest) = [FilePath] -> [FilePath]
findIsMainArgs [FilePath]
rest
decodeMainIsArg :: String -> Maybe ModuleName
decodeMainIsArg :: FilePath -> Maybe ModuleName
decodeMainIsArg FilePath
arg
| FilePath -> (Char -> Bool) -> Bool
headOf FilePath
main_fn Char -> Bool
isLower =
ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (FilePath -> ModuleName
forall a. IsString a => FilePath -> a
ModuleName.fromString FilePath
main_mod)
| FilePath -> (Char -> Bool) -> Bool
headOf FilePath
arg Char -> Bool
isUpper
=
ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (FilePath -> ModuleName
forall a. IsString a => FilePath -> a
ModuleName.fromString FilePath
arg)
| Bool
otherwise
=
Maybe ModuleName
forall a. Maybe a
Nothing
where
headOf :: String -> (Char -> Bool) -> Bool
headOf :: FilePath -> (Char -> Bool) -> Bool
headOf FilePath
str Char -> Bool
pred' = (Char -> Bool) -> Maybe Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
pred' (FilePath -> Maybe Char
forall a. [a] -> Maybe a
safeHead FilePath
str)
(FilePath
main_mod, FilePath
main_fn) = FilePath -> (Char -> Bool) -> (FilePath, FilePath)
splitLongestPrefix FilePath
arg (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')
splitLongestPrefix :: String -> (Char -> Bool) -> (String, String)
splitLongestPrefix :: FilePath -> (Char -> Bool) -> (FilePath, FilePath)
splitLongestPrefix FilePath
str Char -> Bool
pred'
| FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
r_pre = (FilePath
str, [])
| Bool
otherwise = (FilePath -> FilePath
forall a. [a] -> [a]
reverse (FilePath -> FilePath
forall a. [a] -> [a]
safeTail FilePath
r_pre), FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
r_suf)
where
(FilePath
r_suf, FilePath
r_pre) = (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
pred' (FilePath -> FilePath
forall a. [a] -> [a]
reverse FilePath
str)