{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
module Distribution.Simple.PreProcess
( preprocessComponent
, preprocessExtras
, preprocessFile
, knownSuffixHandlers
, ppSuffixes
, PPSuffixHandler
, Suffix (..)
, builtinHaskellSuffixes
, builtinHaskellBootSuffixes
, PreProcessor (..)
, mkSimplePreProcessor
, runSimplePreProcessor
, ppCpp
, ppCpp'
, ppGreenCard
, ppC2hs
, ppHsc2hs
, ppHappy
, ppAlex
, ppUnlit
, platformDefines
, unsorted
)
where
import Distribution.Compat.Prelude
import Distribution.Compat.Stack
import Prelude ()
import Distribution.Backpack.DescribeUnitId
import qualified Distribution.InstalledPackageInfo as Installed
import Distribution.ModuleName (ModuleName)
import Distribution.Package
import Distribution.PackageDescription as PD
import Distribution.Simple.BuildPaths
import Distribution.Simple.CCompiler
import Distribution.Simple.Compiler
import Distribution.Simple.Errors
import Distribution.Simple.LocalBuildInfo
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PreProcess.Types
import Distribution.Simple.PreProcess.Unlit
import Distribution.Simple.Program
import Distribution.Simple.Program.ResponseFile
import Distribution.Simple.Test.LibV09
import Distribution.Simple.Utils
import Distribution.System
import Distribution.Types.PackageName.Magic
import Distribution.Utils.Path
import Distribution.Verbosity
import Distribution.Version
import System.Directory (doesDirectoryExist, doesFileExist)
import System.FilePath
( normalise
, replaceExtension
, splitExtension
, takeDirectory
, takeExtensions
)
import System.Info (arch, os)
unsorted
:: Verbosity
-> [path]
-> [ModuleName]
-> IO [ModuleName]
unsorted :: forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted Verbosity
_ [path]
_ [ModuleName]
ms = [ModuleName] -> IO [ModuleName]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ModuleName]
ms
type =
Maybe (SymbolicPath CWD (Dir Pkg))
-> SymbolicPath Pkg (Dir Source)
-> IO [RelativePath Source File]
mkSimplePreProcessor
:: (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor :: (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor
String -> String -> Verbosity -> IO ()
simplePP
(String
inBaseDir, String
inRelativeFile)
(String
outBaseDir, String
outRelativeFile)
Verbosity
verbosity = String -> String -> Verbosity -> IO ()
simplePP String
inFile String
outFile Verbosity
verbosity
where
inFile :: String
inFile = String -> String
normalise (String
inBaseDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
inRelativeFile)
outFile :: String
outFile = String -> String
normalise (String
outBaseDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
outRelativeFile)
runSimplePreProcessor
:: PreProcessor
-> FilePath
-> FilePath
-> Verbosity
-> IO ()
runSimplePreProcessor :: PreProcessor -> String -> String -> Verbosity -> IO ()
runSimplePreProcessor PreProcessor
pp String
inFile String
outFile Verbosity
verbosity =
PreProcessor
-> (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor PreProcessor
pp (String
".", String
inFile) (String
".", String
outFile) Verbosity
verbosity
type PPSuffixHandler =
(Suffix, BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)
preprocessComponent
:: PackageDescription
-> Component
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> Bool
-> Verbosity
-> [PPSuffixHandler]
-> IO ()
preprocessComponent :: PackageDescription
-> Component
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> Bool
-> Verbosity
-> [PPSuffixHandler]
-> IO ()
preprocessComponent PackageDescription
pd Component
comp LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi Bool
isSrcDist Verbosity
verbosity [PPSuffixHandler]
handlers =
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PackageDescription -> PackageIdentifier
package PackageDescription
pd PackageIdentifier -> PackageIdentifier -> Bool
forall a. Eq a => a -> a -> Bool
/= PackageIdentifier
fakePackageId) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity
-> String
-> PackageIdentifier
-> ComponentName
-> Maybe [(ModuleName, Module)]
-> IO ()
forall a.
Pretty a =>
Verbosity
-> String
-> PackageIdentifier
-> ComponentName
-> Maybe [(ModuleName, a)]
-> IO ()
setupMessage'
Verbosity
verbosity
String
"Preprocessing"
(PackageDescription -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId PackageDescription
pd)
(ComponentLocalBuildInfo -> ComponentName
componentLocalName ComponentLocalBuildInfo
clbi)
(Maybe [(ModuleName, Module)]
forall a. Maybe a
Nothing :: Maybe [(ModuleName, Module)])
case Component
comp of
(CLib lib :: Library
lib@Library{libBuildInfo :: Library -> BuildInfo
libBuildInfo = BuildInfo
bi}) -> do
let dirs :: [SymbolicPath Pkg ('Dir Source)]
dirs =
BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. [a] -> [a] -> [a]
++ [LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi, LocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenPackageModulesDir LocalBuildInfo
lbi]
let hndlrs :: [(Suffix, PreProcessor)]
hndlrs = BuildInfo -> [(Suffix, PreProcessor)]
localHandlers BuildInfo
bi
mods <- Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [(Suffix, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall {t :: * -> *} {a}.
Foldable t =>
Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [SymbolicPath Pkg ('Dir Source)]
dirs [(Suffix, PreProcessor)]
hndlrs (Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi)
for_ (map moduleNameSymbolicPath mods) $
pre dirs (componentBuildDir lbi clbi) hndlrs
(CFLib flib :: ForeignLib
flib@ForeignLib{foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
bi}) -> do
let flibDir :: SymbolicPath Pkg ('Dir Build)
flibDir = LocalBuildInfo -> ForeignLib -> SymbolicPath Pkg ('Dir Build)
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib
dirs :: [SymbolicPath Pkg ('Dir Source)]
dirs =
BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. [a] -> [a] -> [a]
++ [ LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
, LocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenPackageModulesDir LocalBuildInfo
lbi
]
let hndlrs :: [(Suffix, PreProcessor)]
hndlrs = BuildInfo -> [(Suffix, PreProcessor)]
localHandlers BuildInfo
bi
mods <- Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [(Suffix, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall {t :: * -> *} {a}.
Foldable t =>
Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [SymbolicPath Pkg ('Dir Source)]
dirs [(Suffix, PreProcessor)]
hndlrs (ForeignLib -> [ModuleName]
foreignLibModules ForeignLib
flib)
for_ (map moduleNameSymbolicPath mods) $
pre dirs flibDir hndlrs
(CExe exe :: Executable
exe@Executable{buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bi}) -> do
let exeDir :: SymbolicPath Pkg ('Dir Build)
exeDir = LocalBuildInfo -> Executable -> SymbolicPath Pkg ('Dir Build)
exeBuildDir LocalBuildInfo
lbi Executable
exe
dirs :: [SymbolicPath Pkg ('Dir Source)]
dirs =
BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. [a] -> [a] -> [a]
++ [ LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
, LocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenPackageModulesDir LocalBuildInfo
lbi
]
let hndlrs :: [(Suffix, PreProcessor)]
hndlrs = BuildInfo -> [(Suffix, PreProcessor)]
localHandlers BuildInfo
bi
mods <- Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [(Suffix, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall {t :: * -> *} {a}.
Foldable t =>
Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [SymbolicPath Pkg ('Dir Source)]
dirs [(Suffix, PreProcessor)]
hndlrs (BuildInfo -> [ModuleName]
otherModules BuildInfo
bi)
for_ (map moduleNameSymbolicPath mods) $
pre dirs exeDir hndlrs
pre (hsSourceDirs bi) exeDir (localHandlers bi) $
dropExtensionsSymbolicPath (modulePath exe)
CTest test :: TestSuite
test@TestSuite{} -> do
let testDir :: SymbolicPath Pkg ('Dir Build)
testDir = LocalBuildInfo -> TestSuite -> SymbolicPath Pkg ('Dir Build)
testBuildDir LocalBuildInfo
lbi TestSuite
test
case TestSuite -> TestSuiteInterface
testInterface TestSuite
test of
TestSuiteExeV10 Version
_ RelativePath Source 'File
f ->
TestSuite
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessTest TestSuite
test RelativePath Source 'File
f SymbolicPath Pkg ('Dir Build)
testDir
TestSuiteLibV09 Version
_ ModuleName
_ -> do
TestSuite -> String -> IO ()
writeSimpleTestStub TestSuite
test (SymbolicPath Pkg ('Dir Build) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
i SymbolicPath Pkg ('Dir Build)
testDir)
TestSuite
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessTest TestSuite
test (String -> RelativePath Source 'File
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx (String -> RelativePath Source 'File)
-> String -> RelativePath Source 'File
forall a b. (a -> b) -> a -> b
$ TestSuite -> String
stubFilePath TestSuite
test) SymbolicPath Pkg ('Dir Build)
testDir
TestSuiteUnsupported TestType
tt ->
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ TestType -> CabalException
NoSupportForPreProcessingTest TestType
tt
CBench bm :: Benchmark
bm@Benchmark{} -> do
let benchDir :: SymbolicPath Pkg ('Dir Build)
benchDir = LocalBuildInfo -> Benchmark -> SymbolicPath Pkg ('Dir Build)
benchmarkBuildDir LocalBuildInfo
lbi Benchmark
bm
case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
BenchmarkExeV10 Version
_ RelativePath Source 'File
f ->
Benchmark
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessBench Benchmark
bm RelativePath Source 'File
f SymbolicPath Pkg ('Dir Build)
benchDir
BenchmarkUnsupported BenchmarkType
tt ->
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$ BenchmarkType -> CabalException
NoSupportForPreProcessingBenchmark BenchmarkType
tt
where
orderingFromHandlers :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
v [SymbolicPath Pkg ('Dir Source)]
d t (a, PreProcessor)
hndlrs [ModuleName]
mods =
([ModuleName] -> (a, PreProcessor) -> IO [ModuleName])
-> [ModuleName] -> t (a, PreProcessor) -> IO [ModuleName]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\[ModuleName]
acc (a
_, PreProcessor
pp) -> PreProcessor
-> Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering PreProcessor
pp Verbosity
v [SymbolicPath Pkg ('Dir Source)]
d [ModuleName]
acc) [ModuleName]
mods t (a, PreProcessor)
hndlrs
builtinCSuffixes :: [Suffix]
builtinCSuffixes = (String -> Suffix) -> [String] -> [Suffix]
forall a b. (a -> b) -> [a] -> [b]
map String -> Suffix
Suffix [String]
cSourceExtensions
builtinSuffixes :: [Suffix]
builtinSuffixes = [Suffix]
builtinHaskellSuffixes [Suffix] -> [Suffix] -> [Suffix]
forall a. [a] -> [a] -> [a]
++ [Suffix]
builtinCSuffixes
localHandlers :: BuildInfo -> [(Suffix, PreProcessor)]
localHandlers BuildInfo
bi = [(Suffix
ext, BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
h BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi) | (Suffix
ext, BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
h) <- [PPSuffixHandler]
handlers]
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
i :: SymbolicPathX allowAbsolute Pkg to -> String
i = LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> String
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> String
interpretSymbolicPathLBI LocalBuildInfo
lbi
pre :: [SymbolicPath Pkg ('Dir Source)]
-> SymbolicPath Pkg ('Dir Build)
-> [(Suffix, PreProcessor)]
-> RelativePath Source 'File
-> IO ()
pre [SymbolicPath Pkg ('Dir Source)]
dirs SymbolicPath Pkg ('Dir Build)
dir [(Suffix, PreProcessor)]
lhndlrs RelativePath Source 'File
fp =
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Source)]
-> SymbolicPath Pkg ('Dir Build)
-> Bool
-> RelativePath Source 'File
-> Verbosity
-> [Suffix]
-> [(Suffix, PreProcessor)]
-> Bool
-> IO ()
preprocessFile Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [SymbolicPath Pkg ('Dir Source)]
dirs SymbolicPath Pkg ('Dir Build)
dir Bool
isSrcDist RelativePath Source 'File
fp Verbosity
verbosity [Suffix]
builtinSuffixes [(Suffix, PreProcessor)]
lhndlrs Bool
True
preProcessTest :: TestSuite
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessTest TestSuite
test =
BuildInfo
-> [ModuleName]
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessComponent
(TestSuite -> BuildInfo
testBuildInfo TestSuite
test)
(TestSuite -> [ModuleName]
testModules TestSuite
test)
preProcessBench :: Benchmark
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessBench Benchmark
bm =
BuildInfo
-> [ModuleName]
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessComponent
(Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bm)
(Benchmark -> [ModuleName]
benchmarkModules Benchmark
bm)
preProcessComponent
:: BuildInfo
-> [ModuleName]
-> RelativePath Source File
-> SymbolicPath Pkg (Dir Build)
-> IO ()
preProcessComponent :: BuildInfo
-> [ModuleName]
-> RelativePath Source 'File
-> SymbolicPath Pkg ('Dir Build)
-> IO ()
preProcessComponent BuildInfo
bi [ModuleName]
modules RelativePath Source 'File
exePath SymbolicPath Pkg ('Dir Build)
outputDir = do
let biHandlers :: [(Suffix, PreProcessor)]
biHandlers = BuildInfo -> [(Suffix, PreProcessor)]
localHandlers BuildInfo
bi
sourceDirs :: [SymbolicPath Pkg ('Dir Source)]
sourceDirs =
BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. [a] -> [a] -> [a]
++ [ LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
, LocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenPackageModulesDir LocalBuildInfo
lbi
]
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Source)]
-> SymbolicPath Pkg ('Dir Build)
-> Bool
-> RelativePath Source 'File
-> Verbosity
-> [Suffix]
-> [(Suffix, PreProcessor)]
-> Bool
-> IO ()
preprocessFile
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
[SymbolicPath Pkg ('Dir Source)]
sourceDirs
SymbolicPath Pkg ('Dir Build)
outputDir
Bool
isSrcDist
(ModuleName -> RelativePath Source 'File
forall (allowAbsolute :: AllowAbsolute).
ModuleName -> SymbolicPathX allowAbsolute Source 'File
moduleNameSymbolicPath ModuleName
modu)
Verbosity
verbosity
[Suffix]
builtinSuffixes
[(Suffix, PreProcessor)]
biHandlers
Bool
False
| ModuleName
modu <- [ModuleName]
modules
]
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Source)]
-> SymbolicPath Pkg ('Dir Build)
-> Bool
-> RelativePath Source 'File
-> Verbosity
-> [Suffix]
-> [(Suffix, PreProcessor)]
-> Bool
-> IO ()
preprocessFile
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
(SymbolicPath Pkg ('Dir Build) -> SymbolicPath Pkg ('Dir Source)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPath Pkg ('Dir Build)
outputDir SymbolicPath Pkg ('Dir Source)
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. a -> [a] -> [a]
: BuildInfo -> [SymbolicPath Pkg ('Dir Source)]
hsSourceDirs BuildInfo
bi)
SymbolicPath Pkg ('Dir Build)
outputDir
Bool
isSrcDist
(RelativePath Source 'File -> RelativePath Source 'File
forall (allowAbsolute :: AllowAbsolute) from.
SymbolicPathX allowAbsolute from 'File
-> SymbolicPathX allowAbsolute from 'File
dropExtensionsSymbolicPath (RelativePath Source 'File -> RelativePath Source 'File)
-> RelativePath Source 'File -> RelativePath Source 'File
forall a b. (a -> b) -> a -> b
$ RelativePath Source 'File
exePath)
Verbosity
verbosity
[Suffix]
builtinSuffixes
[(Suffix, PreProcessor)]
biHandlers
Bool
False
preprocessFile
:: Maybe (SymbolicPath CWD (Dir Pkg))
-> [SymbolicPath Pkg (Dir Source)]
-> SymbolicPath Pkg (Dir Build)
-> Bool
-> RelativePath Source File
-> Verbosity
-> [Suffix]
-> [(Suffix, PreProcessor)]
-> Bool
-> IO ()
preprocessFile :: Maybe (SymbolicPath CWD ('Dir Pkg))
-> [SymbolicPath Pkg ('Dir Source)]
-> SymbolicPath Pkg ('Dir Build)
-> Bool
-> RelativePath Source 'File
-> Verbosity
-> [Suffix]
-> [(Suffix, PreProcessor)]
-> Bool
-> IO ()
preprocessFile Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [SymbolicPath Pkg ('Dir Source)]
searchLoc SymbolicPath Pkg ('Dir Build)
buildLoc Bool
forSDist RelativePath Source 'File
baseFile Verbosity
verbosity [Suffix]
builtinSuffixes [(Suffix, PreProcessor)]
handlers Bool
failOnMissing = do
psrcFiles <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPath Pkg ('Dir Source)]
-> RelativePath Source 'File
-> IO
(Maybe (SymbolicPath Pkg ('Dir Source), RelativePath Source 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO
(Maybe
(SymbolicPathX allowAbsolute Pkg ('Dir searchDir),
RelativePath searchDir 'File))
findFileCwdWithExtension' Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir (((Suffix, PreProcessor) -> Suffix)
-> [(Suffix, PreProcessor)] -> [Suffix]
forall a b. (a -> b) -> [a] -> [b]
map (Suffix, PreProcessor) -> Suffix
forall a b. (a, b) -> a
fst [(Suffix, PreProcessor)]
handlers) [SymbolicPath Pkg ('Dir Source)]
searchLoc RelativePath Source 'File
baseFile
case psrcFiles of
Maybe (SymbolicPath Pkg ('Dir Source), RelativePath Source 'File)
Nothing -> do
bsrcFiles <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPath Pkg ('Dir Source)]
-> RelativePath Source 'File
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
findFileCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Suffix]
builtinSuffixes (SymbolicPath Pkg ('Dir Source)
buildAsSrcLoc SymbolicPath Pkg ('Dir Source)
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. a -> [a] -> [a]
: [SymbolicPath Pkg ('Dir Source)]
searchLoc) RelativePath Source 'File
baseFile
case (bsrcFiles, failOnMissing) of
(Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
Nothing, Bool
True) ->
Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO ()) -> CabalException -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> CabalException
CantFindSourceForPreProcessFile (String -> CabalException) -> String -> CabalException
forall a b. (a -> b) -> a -> b
$
String
"can't find source for "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ RelativePath Source 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath RelativePath Source 'File
baseFile
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((SymbolicPath Pkg ('Dir Source) -> String)
-> [SymbolicPath Pkg ('Dir Source)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath Pkg ('Dir Source) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath [SymbolicPath Pkg ('Dir Source)]
searchLoc)
(Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File), Bool)
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just (SymbolicPath Pkg ('Dir Source)
psrcLoc, RelativePath Source 'File
psrcRelFile) -> do
let (String
srcStem, String
ext) = String -> (String, String)
splitExtension (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ RelativePath Source 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath RelativePath Source 'File
psrcRelFile
psrcFile :: SymbolicPathX 'AllowAbsolute Pkg 'File
psrcFile = SymbolicPath Pkg ('Dir Source)
psrcLoc SymbolicPath Pkg ('Dir Source)
-> RelativePath Source 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</> RelativePath Source 'File
psrcRelFile
pp :: PreProcessor
pp =
PreProcessor -> Maybe PreProcessor -> PreProcessor
forall a. a -> Maybe a -> a
fromMaybe
(String -> PreProcessor
forall a. HasCallStack => String -> a
error String
"Distribution.Simple.PreProcess: Just expected")
(Suffix -> [(Suffix, PreProcessor)] -> Maybe PreProcessor
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (String -> Suffix
Suffix (String -> Suffix) -> String -> Suffix
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. [a] -> [a]
safeTail String
ext) [(Suffix, PreProcessor)]
handlers)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
forSDist Bool -> Bool -> Bool
|| Bool
forSDist Bool -> Bool -> Bool
&& PreProcessor -> Bool
platformIndependent PreProcessor
pp) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
ppsrcFiles <- Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPath Pkg ('Dir Source)]
-> RelativePath Source 'File
-> IO (Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File))
forall searchDir (allowAbsolute :: AllowAbsolute).
Maybe (SymbolicPath CWD ('Dir Pkg))
-> [Suffix]
-> [SymbolicPathX allowAbsolute Pkg ('Dir searchDir)]
-> RelativePath searchDir 'File
-> IO (Maybe (SymbolicPathX allowAbsolute Pkg 'File))
findFileCwdWithExtension Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir [Suffix]
builtinSuffixes [SymbolicPath Pkg ('Dir Source)
buildAsSrcLoc] RelativePath Source 'File
baseFile
recomp <- case ppsrcFiles of
Maybe (SymbolicPathX 'AllowAbsolute Pkg 'File)
Nothing -> Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Just SymbolicPathX 'AllowAbsolute Pkg 'File
ppsrcFile ->
SymbolicPathX 'AllowAbsolute Pkg 'File -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
i SymbolicPathX 'AllowAbsolute Pkg 'File
psrcFile String -> String -> IO Bool
`moreRecentFile` SymbolicPathX 'AllowAbsolute Pkg 'File -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
i SymbolicPathX 'AllowAbsolute Pkg 'File
ppsrcFile
when recomp $ do
let destDir = SymbolicPath Pkg ('Dir Build) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
i SymbolicPath Pkg ('Dir Build)
buildLoc String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String -> String
takeDirectory String
srcStem
createDirectoryIfMissingVerbose verbosity True destDir
runPreProcessorWithHsBootHack
pp
(getSymbolicPath $ psrcLoc, getSymbolicPath $ psrcRelFile)
(getSymbolicPath $ buildLoc, srcStem <.> "hs")
where
i :: SymbolicPathX allowAbsolute Pkg to -> String
i = Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPathX allowAbsolute Pkg to -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir
buildAsSrcLoc :: SymbolicPath Pkg (Dir Source)
buildAsSrcLoc :: SymbolicPath Pkg ('Dir Source)
buildAsSrcLoc = SymbolicPath Pkg ('Dir Build) -> SymbolicPath Pkg ('Dir Source)
forall (allowAbsolute :: AllowAbsolute) from (to1 :: FileOrDir)
(to2 :: FileOrDir).
SymbolicPathX allowAbsolute from to1
-> SymbolicPathX allowAbsolute from to2
coerceSymbolicPath SymbolicPath Pkg ('Dir Build)
buildLoc
runPreProcessorWithHsBootHack :: PreProcessor -> (String, String) -> (String, String) -> IO ()
runPreProcessorWithHsBootHack
PreProcessor
pp
(String
inBaseDir, String
inRelativeFile)
(String
outBaseDir, String
outRelativeFile) = do
PreProcessor
-> (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor
PreProcessor
pp
(String
inBaseDir, String
inRelativeFile)
(String
outBaseDir, String
outRelativeFile)
Verbosity
verbosity
exists <- String -> IO Bool
doesFileExist String
inBoot
when exists $ copyFileVerbose verbosity inBoot outBoot
where
inBoot :: String
inBoot = String -> String -> String
replaceExtension String
inFile String
"hs-boot"
outBoot :: String
outBoot = String -> String -> String
replaceExtension String
outFile String
"hs-boot"
inFile :: String
inFile = String -> String
normalise (String
inBaseDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
inRelativeFile)
outFile :: String
outFile = String -> String
normalise (String
outBaseDir String -> String -> String
forall p q r. PathLike p q r => p -> q -> r
</> String
outRelativeFile)
ppGreenCard :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_ =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity ->
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> Program
-> ProgramDb
-> [String]
-> IO ()
forall to.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir to))
-> Program
-> ProgramDb
-> [String]
-> IO ()
runDbProgramCwd
Verbosity
verbosity
(LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi)
Program
greencardProgram
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
([String
"-tffi", String
"-o" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
outFile, String
inFile])
}
ppUnlit :: PreProcessor
ppUnlit :: PreProcessor
ppUnlit =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
True
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity ->
String -> (String -> IO ()) -> IO ()
forall a. String -> (String -> IO a) -> IO a
withUTF8FileContents String
inFile ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
contents ->
(String -> IO ())
-> (CabalException -> IO ())
-> Either String CabalException
-> IO ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> String -> IO ()
writeUTF8File String
outFile) (Verbosity -> CabalException -> IO ()
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity) (String -> String -> Either String CabalException
unlit String
inFile String
contents)
}
ppCpp :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp = [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpp' []
ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp' :: [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpp' [String]
extraArgs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
CompilerFlavor
GHC -> Program
-> (Version -> Bool)
-> [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
ghcProgram (Bool -> Version -> Bool
forall a b. a -> b -> a
const Bool
True) [String]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
CompilerFlavor
GHCJS -> Program
-> (Version -> Bool)
-> [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
ghcjsProgram (Bool -> Version -> Bool
forall a b. a -> b -> a
const Bool
True) [String]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
CompilerFlavor
_ -> [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpphs [String]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
where
cppArgs :: [String]
cppArgs = BuildInfo -> LocalBuildInfo -> [String]
getCppOptions BuildInfo
bi LocalBuildInfo
lbi
args :: [String]
args = [String]
cppArgs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
extraArgs
ppGhcCpp
:: Program
-> (Version -> Bool)
-> [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp :: Program
-> (Version -> Bool)
-> [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
program Version -> Bool
xHs [String]
extraArgs BuildInfo
_bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity -> do
(prog, version, _) <-
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion
Verbosity
verbosity
Program
program
VersionRange
anyVersion
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
runProgramCwd verbosity (mbWorkDirLBI lbi) prog $
["-E", "-cpp"]
++ (if xHs version then ["-x", "hs"] else [])
++ ["-optP-include", "-optP" ++ u (autogenComponentModulesDir lbi clbi </> makeRelativePathEx cppHeaderName)]
++ ["-o", outFile, inFile]
++ extraArgs
}
where
u :: SymbolicPath Pkg to -> FilePath
u :: forall (to :: FileOrDir). SymbolicPath Pkg to -> String
u = SymbolicPathX 'AllowAbsolute Pkg to -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPathCWD
ppCpphs :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpphs :: [String]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpphs [String]
extraArgs BuildInfo
_bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity -> do
(cpphsProg, cpphsVersion, _) <-
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion
Verbosity
verbosity
Program
cpphsProgram
VersionRange
anyVersion
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
runProgramCwd verbosity (mbWorkDirLBI lbi) cpphsProg $
("-O" ++ outFile)
: inFile
: "--noline"
: "--strip"
: ( if cpphsVersion >= mkVersion [1, 6]
then ["--include=" ++ u (autogenComponentModulesDir lbi clbi </> makeRelativePathEx cppHeaderName)]
else []
)
++ extraArgs
}
where
u :: SymbolicPath Pkg to -> FilePath
u :: forall (to :: FileOrDir). SymbolicPath Pkg to -> String
u = SymbolicPathX 'AllowAbsolute Pkg to -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPathCWD
ppHsc2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity -> do
(gccProg, _) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
gccProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
(hsc2hsProg, hsc2hsVersion, _) <-
requireProgramVersion
verbosity
hsc2hsProgram
anyVersion
(withPrograms lbi)
let runHsc2hs = Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> ConfiguredProgram
-> [String]
-> IO ()
forall to.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir to))
-> ConfiguredProgram
-> [String]
-> IO ()
runProgramCwd Verbosity
verbosity Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir ConfiguredProgram
hsc2hsProg
let isCross = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi Platform -> Platform -> Bool
forall a. Eq a => a -> a -> Bool
/= Platform
buildPlatform
prependCrossFlags = if Bool
isCross then (String
"-x" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:) else [String] -> [String]
forall a. a -> a
id
let hsc2hsSupportsResponseFiles = Version
hsc2hsVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
0, Int
68, Int
4]
pureArgs = Version -> ConfiguredProgram -> String -> String -> [String]
genPureArgs Version
hsc2hsVersion ConfiguredProgram
gccProg String
inFile String
outFile
if hsc2hsSupportsResponseFiles
then
withResponseFile
verbosity
defaultTempFileOptions
mbWorkDir
(makeSymbolicPath $ takeDirectory outFile)
"hsc2hs-response.txt"
Nothing
pureArgs
( \String
responseFileName ->
[String] -> IO ()
runHsc2hs ([String] -> [String]
prependCrossFlags [String
"@" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
responseFileName])
)
else runHsc2hs (prependCrossFlags pureArgs)
}
where
u :: SymbolicPathX allowAbs Pkg to -> FilePath
u :: forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u = SymbolicPathX allowAbs Pkg to -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPathCWD
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
genPureArgs :: Version -> ConfiguredProgram -> String -> String -> [String]
genPureArgs :: Version -> ConfiguredProgram -> String -> String -> [String]
genPureArgs Version
hsc2hsVersion ConfiguredProgram
gccProg String
inFile String
outFile =
[ String
"--cflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| String
opt <-
ConfiguredProgram -> [String]
programDefaultArgs ConfiguredProgram
gccProg
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> [String]
programOverrideArgs ConfiguredProgram
gccProg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--lflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| String
opt <-
ConfiguredProgram -> [String]
programDefaultArgs ConfiguredProgram
gccProg
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> [String]
programOverrideArgs ConfiguredProgram
gccProg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
what String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"=-F" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| Bool
isOSX
, String
opt <- [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ((InstalledPackageInfo -> [String])
-> [InstalledPackageInfo] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap InstalledPackageInfo -> [String]
Installed.frameworkDirs [InstalledPackageInfo]
pkgs)
, String
what <- [String
"--cflag", String
"--lflag"]
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--lflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arg
| Bool
isOSX
, String
opt <- (SymbolicPathX 'OnlyRelative Framework 'File -> String)
-> [SymbolicPathX 'OnlyRelative Framework 'File] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPathX 'OnlyRelative Framework 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath (BuildInfo -> [SymbolicPathX 'OnlyRelative Framework 'File]
PD.frameworks BuildInfo
bi) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (InstalledPackageInfo -> [String])
-> [InstalledPackageInfo] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap InstalledPackageInfo -> [String]
Installed.frameworks [InstalledPackageInfo]
pkgs
, String
arg <- [String
"-framework", String
opt]
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"--cflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | String
opt <- LocalBuildInfo -> [String]
platformDefines LocalBuildInfo
lbi]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"--cflag=-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPathX 'AllowAbsolute Pkg ('Dir Include) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
dir | SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
dir <- BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
PD.includeDirs BuildInfo
bi]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--cflag=-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 2) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u (LocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
buildDir LocalBuildInfo
lbi SymbolicPath Pkg ('Dir Build)
-> SymbolicPathX 'OnlyRelative Build (ZonkAny 2)
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 2)
forall p q r. PathLike p q r => p -> q -> r
</> SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
-> SymbolicPathX 'OnlyRelative Build (ZonkAny 2)
forall (allowAbsolute :: AllowAbsolute) from1 (to1 :: FileOrDir)
from2 (to2 :: FileOrDir).
SymbolicPathX allowAbsolute from1 to1
-> SymbolicPathX allowAbsolute from2 to2
unsafeCoerceSymbolicPath SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
relDir)
| SymbolicPathX 'OnlyRelative Pkg ('Dir Include)
relDir <- (SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
-> Maybe (SymbolicPathX 'OnlyRelative Pkg ('Dir Include)))
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
-> Maybe (SymbolicPathX 'OnlyRelative Pkg ('Dir Include))
forall from (to :: FileOrDir).
SymbolicPath from to -> Maybe (RelativePath from to)
symbolicPathRelative_maybe ([SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)])
-> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
-> [SymbolicPathX 'OnlyRelative Pkg ('Dir Include)]
forall a b. (a -> b) -> a -> b
$ BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
PD.includeDirs BuildInfo
bi
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--cflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| String
opt <-
BuildInfo -> [String]
PD.ccOptions BuildInfo
bi
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [String]
PD.cppOptions BuildInfo
bi
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--cflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| String
opt <-
[ String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPath Pkg ('Dir Source) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u (LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi)
, String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPath Pkg ('Dir Source) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u (LocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenPackageModulesDir LocalBuildInfo
lbi)
, String
"-include"
, SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 3) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u (SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 3) -> String)
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 3) -> String
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo
-> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi SymbolicPath Pkg ('Dir Source)
-> RelativePath Source (ZonkAny 3)
-> SymbolicPathX 'AllowAbsolute Pkg (ZonkAny 3)
forall p q r. PathLike p q r => p -> q -> r
</> String -> RelativePath Source (ZonkAny 3)
forall from (to :: FileOrDir).
HasCallStack =>
String -> RelativePath from to
makeRelativePathEx String
cppHeaderName
]
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--lflag=-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)
opt
| SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)
opt <-
if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
then BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)]
PD.extraLibDirsStatic BuildInfo
bi
else BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)]
PD.extraLibDirs BuildInfo
bi
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--lflag=-Wl,-R," String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib) -> String
forall {allowAbsolute :: AllowAbsolute} {to :: FileOrDir}.
SymbolicPathX allowAbsolute Pkg to -> String
u SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)
opt
| Bool
isELF
, SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)
opt <-
if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
then BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)]
PD.extraLibDirsStatic BuildInfo
bi
else BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Lib)]
PD.extraLibDirs BuildInfo
bi
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"--lflag=-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | String
opt <- BuildInfo -> [String]
PD.extraLibs BuildInfo
bi]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"--lflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | String
opt <- BuildInfo -> [String]
PD.ldOptions BuildInfo
bi]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--cflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| InstalledPackageInfo
pkg <- [InstalledPackageInfo]
pkgs
, String
opt <-
[String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | String
opt <- InstalledPackageInfo -> [String]
Installed.includeDirs InstalledPackageInfo
pkg]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ InstalledPackageInfo -> [String]
Installed.ccOptions InstalledPackageInfo
pkg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"--lflag=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| InstalledPackageInfo
pkg <- [InstalledPackageInfo]
pkgs
, String
opt <-
[String
"-L" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | String
opt <- InstalledPackageInfo -> [String]
Installed.libraryDirs InstalledPackageInfo
pkg]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"-Wl,-R," String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt | Bool
isELF, String
opt <- InstalledPackageInfo -> [String]
Installed.libraryDirs InstalledPackageInfo
pkg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [ String
"-l" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt
| String
opt <-
if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
then InstalledPackageInfo -> [String]
Installed.extraLibrariesStatic InstalledPackageInfo
pkg
else InstalledPackageInfo -> [String]
Installed.extraLibraries InstalledPackageInfo
pkg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ InstalledPackageInfo -> [String]
Installed.ldOptions InstalledPackageInfo
pkg
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
preccldFlags
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [String]
hsc2hsOptions BuildInfo
bi
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
postccldFlags
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-o", String
outFile, String
inFile]
where
ccldFlags :: [String]
ccldFlags =
[ String
"--cc=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> String
programPath ConfiguredProgram
gccProg
, String
"--ld=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> String
programPath ConfiguredProgram
gccProg
]
([String]
preccldFlags, [String]
postccldFlags)
| Version
hsc2hsVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
0, Int
68, Int
8] = ([String]
ccldFlags, [])
| Bool
otherwise = ([], [String]
ccldFlags)
hacked_index :: InstalledPackageIndex
hacked_index = InstalledPackageIndex -> InstalledPackageIndex
packageHacks (LocalBuildInfo -> InstalledPackageIndex
installedPkgs LocalBuildInfo
lbi)
pkgs :: [InstalledPackageInfo]
pkgs = InstalledPackageIndex -> [InstalledPackageInfo]
forall a. PackageInstalled a => PackageIndex a -> [a]
PackageIndex.topologicalOrder (InstalledPackageIndex -> [InstalledPackageInfo])
-> InstalledPackageIndex -> [InstalledPackageInfo]
forall a b. (a -> b) -> a -> b
$
case InstalledPackageIndex
-> [UnitId]
-> Either InstalledPackageIndex [(InstalledPackageInfo, [UnitId])]
PackageIndex.dependencyClosure
InstalledPackageIndex
hacked_index
(((UnitId, MungedPackageId) -> UnitId)
-> [(UnitId, MungedPackageId)] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (UnitId, MungedPackageId) -> UnitId
forall a b. (a, b) -> a
fst (ComponentLocalBuildInfo -> [(UnitId, MungedPackageId)]
componentPackageDeps ComponentLocalBuildInfo
clbi)) of
Left InstalledPackageIndex
index' -> InstalledPackageIndex
index'
Right [(InstalledPackageInfo, [UnitId])]
inf ->
String -> InstalledPackageIndex
forall a. HasCallStack => String -> a
error (String
"ppHsc2hs: broken closure: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(InstalledPackageInfo, [UnitId])] -> String
forall a. Show a => a -> String
show [(InstalledPackageInfo, [UnitId])]
inf)
isOSX :: Bool
isOSX = case OS
buildOS of OS
OSX -> Bool
True; OS
_ -> Bool
False
isELF :: Bool
isELF = case OS
buildOS of OS
OSX -> Bool
False; OS
Windows -> Bool
False; OS
AIX -> Bool
False; OS
_ -> Bool
True
packageHacks :: InstalledPackageIndex -> InstalledPackageIndex
packageHacks = case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
CompilerFlavor
GHC -> InstalledPackageIndex -> InstalledPackageIndex
hackRtsPackage
CompilerFlavor
GHCJS -> InstalledPackageIndex -> InstalledPackageIndex
hackRtsPackage
CompilerFlavor
_ -> InstalledPackageIndex -> InstalledPackageIndex
forall a. a -> a
id
hackRtsPackage :: InstalledPackageIndex -> InstalledPackageIndex
hackRtsPackage InstalledPackageIndex
index =
case InstalledPackageIndex
-> PackageName -> [(Version, [InstalledPackageInfo])]
forall a. PackageIndex a -> PackageName -> [(Version, [a])]
PackageIndex.lookupPackageName InstalledPackageIndex
index (String -> PackageName
mkPackageName String
"rts") of
[(Version
_, [InstalledPackageInfo
rts])] ->
InstalledPackageInfo
-> InstalledPackageIndex -> InstalledPackageIndex
PackageIndex.insert InstalledPackageInfo
rts{Installed.ldOptions = []} InstalledPackageIndex
index
[(Version, [InstalledPackageInfo])]
_ -> String -> InstalledPackageIndex
forall a. HasCallStack => String -> a
error String
"No (or multiple) ghc rts package is registered!!"
ppHsc2hsExtras :: PreProcessorExtras
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Source)
buildBaseDir = do
fs <- String -> IO [String]
getDirectoryContentsRecursive (String -> IO [String]) -> String -> IO [String]
forall a b. (a -> b) -> a -> b
$ Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Source) -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Source)
buildBaseDir
let hscCFiles = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String
"_hsc.c" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf`) [String]
fs
return $ map makeRelativePathEx hscCFiles
ppC2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor =
\(String
inBaseDir, String
inRelativeFile)
(String
outBaseDir, String
outRelativeFile)
Verbosity
verbosity -> do
(c2hsProg, _, _) <-
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion
Verbosity
verbosity
Program
c2hsProgram
(Version -> VersionRange
orLaterVersion ([Int] -> Version
mkVersion [Int
0, Int
15]))
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
(gccProg, _) <- requireProgram verbosity gccProgram (withPrograms lbi)
runProgramCwd verbosity mbWorkDir c2hsProg $
["--cpp=" ++ programPath gccProg, "--cppopts=-E"]
++ ["--cppopts=" ++ opt | opt <- getCppOptions bi lbi]
++ ["--cppopts=-include" ++ u (autogenComponentModulesDir lbi clbi </> makeRelativePathEx cppHeaderName)]
++ ["--include=" ++ outBaseDir]
++ [ "--cppopts=" ++ opt
| pkg <- pkgs
, opt <-
["-I" ++ opt | opt <- Installed.includeDirs pkg]
++ [ opt | opt@('-' : c : _) <- Installed.ccOptions pkg,
c `elem` "DIU"
]
]
++ [ "--output-dir=" ++ outBaseDir
, "--output=" ++ outRelativeFile
, inBaseDir </> inRelativeFile
]
}
where
pkgs :: [InstalledPackageInfo]
pkgs = InstalledPackageIndex -> [InstalledPackageInfo]
forall a. PackageInstalled a => PackageIndex a -> [a]
PackageIndex.topologicalOrder (LocalBuildInfo -> InstalledPackageIndex
installedPkgs LocalBuildInfo
lbi)
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
u :: SymbolicPath Pkg to -> FilePath
u :: forall (to :: FileOrDir). SymbolicPath Pkg to -> String
u = SymbolicPathX 'AllowAbsolute Pkg to -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPathCWD
ppC2hsExtras :: PreProcessorExtras
Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Source)
buildBaseDir = do
fs <- String -> IO [String]
getDirectoryContentsRecursive (String -> IO [String]) -> String -> IO [String]
forall a b. (a -> b) -> a -> b
$ Maybe (SymbolicPath CWD ('Dir Pkg))
-> SymbolicPath Pkg ('Dir Source) -> String
forall from (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
Maybe (SymbolicPath CWD ('Dir from))
-> SymbolicPathX allowAbsolute from to -> String
interpretSymbolicPath Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Source)
buildBaseDir
return $
map makeRelativePathEx $
filter (\String
p -> String -> String
takeExtensions String
p String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
".chs.c") fs
getCppOptions :: BuildInfo -> LocalBuildInfo -> [String]
getCppOptions :: BuildInfo -> LocalBuildInfo -> [String]
getCppOptions BuildInfo
bi LocalBuildInfo
lbi =
LocalBuildInfo -> [String]
platformDefines LocalBuildInfo
lbi
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [String]
cppOptions BuildInfo
bi
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-I" String -> String -> String
forall a. [a] -> [a] -> [a]
++ SymbolicPathX 'AllowAbsolute Pkg ('Dir Include) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
dir | SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)
dir <- BuildInfo -> [SymbolicPathX 'AllowAbsolute Pkg ('Dir Include)]
PD.includeDirs BuildInfo
bi]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
opt | opt :: String
opt@(Char
'-' : Char
c : String
_) <- BuildInfo -> [String]
PD.ccOptions BuildInfo
bi [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [String]
PD.cxxOptions BuildInfo
bi, Char
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
"DIU"]
platformDefines :: LocalBuildInfo -> [String]
platformDefines :: LocalBuildInfo -> [String]
platformDefines LocalBuildInfo
lbi =
case Compiler -> CompilerFlavor
compilerFlavor Compiler
comp of
CompilerFlavor
GHC ->
[String
"-D__GLASGOW_HASKELL__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
versionInt Version
version]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_BUILD_OS=1"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arch String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_BUILD_ARCH=1"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
os' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_OS=1") [String]
osStr
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
arch' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arch' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_ARCH=1") [String]
archStr
CompilerFlavor
GHCJS ->
[String]
compatGlasgowHaskell
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-D__GHCJS__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
versionInt Version
version]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_BUILD_OS=1"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arch String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_BUILD_ARCH=1"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
os' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_OS=1") [String]
osStr
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
arch' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arch' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_ARCH=1") [String]
archStr
HaskellSuite{} ->
[String
"-D__HASKELL_SUITE__"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
os' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
os' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_OS=1") [String]
osStr
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
arch' -> String
"-D" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
arch' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_HOST_ARCH=1") [String]
archStr
CompilerFlavor
_ -> []
where
comp :: Compiler
comp = LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi
Platform Arch
hostArch OS
hostOS = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi
version :: Version
version = Compiler -> Version
compilerVersion Compiler
comp
compatGlasgowHaskell :: [String]
compatGlasgowHaskell =
[String] -> (Version -> [String]) -> Maybe Version -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
[]
(\Version
v -> [String
"-D__GLASGOW_HASKELL__=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
versionInt Version
v])
(CompilerFlavor -> Compiler -> Maybe Version
compilerCompatVersion CompilerFlavor
GHC Compiler
comp)
versionInt :: Version -> String
versionInt :: Version -> String
versionInt Version
v = case Version -> [Int]
versionNumbers Version
v of
[] -> String
"1"
[Int
n] -> Int -> String
forall a. Show a => a -> String
show Int
n
Int
n1 : Int
n2 : [Int]
_ ->
let s1 :: String
s1 = Int -> String
forall a. Show a => a -> String
show Int
n1
s2 :: String
s2 = Int -> String
forall a. Show a => a -> String
show Int
n2
middle :: String
middle = case String
s2 of
Char
_ : Char
_ : String
_ -> String
""
String
_ -> String
"0"
in String
s1 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
middle String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s2
osStr :: [String]
osStr = case OS
hostOS of
OS
Linux -> [String
"linux"]
OS
Windows -> [String
"mingw32"]
OS
OSX -> [String
"darwin"]
OS
FreeBSD -> [String
"freebsd"]
OS
OpenBSD -> [String
"openbsd"]
OS
NetBSD -> [String
"netbsd"]
OS
DragonFly -> [String
"dragonfly"]
OS
Solaris -> [String
"solaris2"]
OS
AIX -> [String
"aix"]
OS
HPUX -> [String
"hpux"]
OS
IRIX -> [String
"irix"]
OS
HaLVM -> []
OS
IOS -> [String
"ios"]
OS
Android -> [String
"android"]
OS
Ghcjs -> [String
"ghcjs"]
OS
Wasi -> [String
"wasi"]
OS
Hurd -> [String
"hurd"]
OS
Haiku -> [String
"haiku"]
OtherOS String
_ -> []
archStr :: [String]
archStr = case Arch
hostArch of
Arch
I386 -> [String
"i386"]
Arch
X86_64 -> [String
"x86_64"]
Arch
PPC -> [String
"powerpc"]
Arch
PPC64 -> [String
"powerpc64"]
Arch
PPC64LE -> [String
"powerpc64le"]
Arch
Sparc -> [String
"sparc"]
Arch
Sparc64 -> [String
"sparc64"]
Arch
Arm -> [String
"arm"]
Arch
AArch64 -> [String
"aarch64"]
Arch
Mips -> [String
"mips"]
Arch
SH -> []
Arch
IA64 -> [String
"ia64"]
Arch
S390 -> [String
"s390"]
Arch
S390X -> [String
"s390x"]
Arch
Alpha -> [String
"alpha"]
Arch
Hppa -> [String
"hppa"]
Arch
Rs6000 -> [String
"rs6000"]
Arch
M68k -> [String
"m68k"]
Arch
Vax -> [String
"vax"]
Arch
RISCV64 -> [String
"riscv64"]
Arch
LoongArch64 -> [String
"loongarch64"]
Arch
JavaScript -> [String
"javascript"]
Arch
Wasm32 -> [String
"wasm32"]
OtherArch String
_ -> []
ppHappy :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_ = PreProcessor
pp{platformIndependent = True}
where
pp :: PreProcessor
pp = LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
happyProgram (CompilerFlavor -> [String]
hcFlags CompilerFlavor
hc)
hc :: CompilerFlavor
hc = Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
hcFlags :: CompilerFlavor -> [String]
hcFlags CompilerFlavor
GHC = [String
"-agc"]
hcFlags CompilerFlavor
GHCJS = [String
"-agc"]
hcFlags CompilerFlavor
_ = []
ppAlex :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_ = PreProcessor
pp{platformIndependent = True}
where
pp :: PreProcessor
pp = LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
alexProgram (CompilerFlavor -> [String]
hcFlags CompilerFlavor
hc)
hc :: CompilerFlavor
hc = Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
hcFlags :: CompilerFlavor -> [String]
hcFlags CompilerFlavor
GHC = [String
"-g"]
hcFlags CompilerFlavor
GHCJS = [String
"-g"]
hcFlags CompilerFlavor
_ = []
standardPP :: LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP :: LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
prog [String]
args =
PreProcessor
{ platformIndependent :: Bool
platformIndependent = Bool
False
, ppOrdering :: Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
ppOrdering = Verbosity
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> IO [ModuleName]
forall path. Verbosity -> [path] -> [ModuleName] -> IO [ModuleName]
unsorted
, runPreProcessor :: (String, String) -> (String, String) -> Verbosity -> IO ()
runPreProcessor = (String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ()
mkSimplePreProcessor ((String -> String -> Verbosity -> IO ())
-> (String, String) -> (String, String) -> Verbosity -> IO ())
-> (String -> String -> Verbosity -> IO ())
-> (String, String)
-> (String, String)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \String
inFile String
outFile Verbosity
verbosity ->
Verbosity
-> Maybe (SymbolicPath CWD ('Dir Pkg))
-> Program
-> ProgramDb
-> [String]
-> IO ()
forall to.
Verbosity
-> Maybe (SymbolicPath CWD ('Dir to))
-> Program
-> ProgramDb
-> [String]
-> IO ()
runDbProgramCwd
Verbosity
verbosity
(LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi)
Program
prog
(LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
([String]
args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-o", String
outFile, String
inFile])
}
ppSuffixes :: [PPSuffixHandler] -> [Suffix]
ppSuffixes :: [PPSuffixHandler] -> [Suffix]
ppSuffixes = (PPSuffixHandler -> Suffix) -> [PPSuffixHandler] -> [Suffix]
forall a b. (a -> b) -> [a] -> [b]
map PPSuffixHandler -> Suffix
forall a b. (a, b) -> a
fst
knownSuffixHandlers :: [PPSuffixHandler]
knownSuffixHandlers :: [PPSuffixHandler]
knownSuffixHandlers =
[ (String -> Suffix
Suffix String
"gc", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard)
, (String -> Suffix
Suffix String
"chs", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs)
, (String -> Suffix
Suffix String
"hsc", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs)
, (String -> Suffix
Suffix String
"x", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex)
, (String -> Suffix
Suffix String
"y", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy)
, (String -> Suffix
Suffix String
"ly", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy)
, (String -> Suffix
Suffix String
"cpphs", BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp)
]
knownExtrasHandlers :: [PreProcessorExtras]
knownExtrasHandlers :: [PreProcessorExtras]
knownExtrasHandlers = [PreProcessorExtras
ppC2hsExtras, PreProcessorExtras
ppHsc2hsExtras]
preprocessExtras
:: Verbosity
-> Component
-> LocalBuildInfo
-> IO [SymbolicPath Pkg File]
Verbosity
verbosity Component
comp LocalBuildInfo
lbi = case Component
comp of
CLib Library
_ -> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp (SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
buildDir LocalBuildInfo
lbi
(CExe exe :: Executable
exe@Executable{}) -> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp (SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> Executable -> SymbolicPath Pkg ('Dir Build)
exeBuildDir LocalBuildInfo
lbi Executable
exe
(CFLib flib :: ForeignLib
flib@ForeignLib{}) -> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp (SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> ForeignLib -> SymbolicPath Pkg ('Dir Build)
flibBuildDir LocalBuildInfo
lbi ForeignLib
flib
CTest TestSuite
test ->
case TestSuite -> TestSuiteInterface
testInterface TestSuite
test of
TestSuiteUnsupported TestType
tt ->
Verbosity
-> CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ TestType -> CabalException
NoSupportPreProcessingTestExtras TestType
tt
TestSuiteInterface
_ -> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp (SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> TestSuite -> SymbolicPath Pkg ('Dir Build)
testBuildDir LocalBuildInfo
lbi TestSuite
test
CBench Benchmark
bm ->
case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
BenchmarkUnsupported BenchmarkType
tt ->
Verbosity
-> CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a1 a.
(HasCallStack, Show a1, Typeable a1,
Exception (VerboseException a1)) =>
Verbosity -> a1 -> IO a
dieWithException Verbosity
verbosity (CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> CabalException -> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ BenchmarkType -> CabalException
NoSupportPreProcessingBenchmarkExtras BenchmarkType
tt
BenchmarkInterface
_ -> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp (SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> Benchmark -> SymbolicPath Pkg ('Dir Build)
benchmarkBuildDir LocalBuildInfo
lbi Benchmark
bm
where
pp :: SymbolicPath Pkg (Dir Build) -> IO [SymbolicPath Pkg File]
pp :: SymbolicPath Pkg ('Dir Build)
-> IO [SymbolicPathX 'AllowAbsolute Pkg 'File]
pp SymbolicPath Pkg ('Dir Build)
builddir = do
let dir :: SymbolicPath Pkg (Dir Source)
dir :: SymbolicPath Pkg ('Dir Source)
dir = SymbolicPath Pkg ('Dir Build) -> SymbolicPath 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
mbWorkDir :: Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir = LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDirLBI LocalBuildInfo
lbi
b <- String -> IO Bool
doesDirectoryExist (LocalBuildInfo -> SymbolicPath Pkg ('Dir Source) -> String
forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir).
LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> String
interpretSymbolicPathLBI LocalBuildInfo
lbi SymbolicPath Pkg ('Dir Source)
dir)
if b
then do
xs <- for knownExtrasHandlers $ withLexicalCallStack $ \PreProcessorExtras
f -> PreProcessorExtras
f Maybe (SymbolicPath CWD ('Dir Pkg))
mbWorkDir SymbolicPath Pkg ('Dir Source)
dir
let not_subs =
(RelativePath Source 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File)
-> [RelativePath Source 'File]
-> [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> [a] -> [b]
map (SymbolicPath Pkg ('Dir Source)
dir SymbolicPath Pkg ('Dir Source)
-> RelativePath Source 'File
-> SymbolicPathX 'AllowAbsolute Pkg 'File
forall p q r. PathLike p q r => p -> q -> r
</>) ([RelativePath Source 'File]
-> [SymbolicPathX 'AllowAbsolute Pkg 'File])
-> [RelativePath Source 'File]
-> [SymbolicPathX 'AllowAbsolute Pkg 'File]
forall a b. (a -> b) -> a -> b
$
(RelativePath Source 'File -> Bool)
-> [RelativePath Source 'File] -> [RelativePath Source 'File]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> Bool
not_sub (String -> Bool)
-> (RelativePath Source 'File -> String)
-> RelativePath Source 'File
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelativePath Source 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath) ([RelativePath Source 'File] -> [RelativePath Source 'File])
-> [RelativePath Source 'File] -> [RelativePath Source 'File]
forall a b. (a -> b) -> a -> b
$
[[RelativePath Source 'File]] -> [RelativePath Source 'File]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[RelativePath Source 'File]]
xs
return not_subs
else pure []
not_sub :: String -> Bool
not_sub String
p = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Bool -> Bool
not (String
pre String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
p) | String
pre <- [String]
component_dirs]
component_dirs :: [String]
component_dirs = PackageDescription -> [String]
component_names (LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi)
component_names :: PackageDescription -> [String]
component_names PackageDescription
pkg_descr =
(UnqualComponentName -> String)
-> [UnqualComponentName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UnqualComponentName -> String
unUnqualComponentName ([UnqualComponentName] -> [String])
-> [UnqualComponentName] -> [String]
forall a b. (a -> b) -> a -> b
$
(Library -> Maybe UnqualComponentName)
-> [Library] -> [UnqualComponentName]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (LibraryName -> Maybe UnqualComponentName
libraryNameString (LibraryName -> Maybe UnqualComponentName)
-> (Library -> LibraryName) -> Library -> Maybe UnqualComponentName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> LibraryName
libName) (PackageDescription -> [Library]
subLibraries PackageDescription
pkg_descr)
[UnqualComponentName]
-> [UnqualComponentName] -> [UnqualComponentName]
forall a. [a] -> [a] -> [a]
++ (Executable -> UnqualComponentName)
-> [Executable] -> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map Executable -> UnqualComponentName
exeName (PackageDescription -> [Executable]
executables PackageDescription
pkg_descr)
[UnqualComponentName]
-> [UnqualComponentName] -> [UnqualComponentName]
forall a. [a] -> [a] -> [a]
++ (TestSuite -> UnqualComponentName)
-> [TestSuite] -> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map TestSuite -> UnqualComponentName
testName (PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg_descr)
[UnqualComponentName]
-> [UnqualComponentName] -> [UnqualComponentName]
forall a. [a] -> [a] -> [a]
++ (Benchmark -> UnqualComponentName)
-> [Benchmark] -> [UnqualComponentName]
forall a b. (a -> b) -> [a] -> [b]
map Benchmark -> UnqualComponentName
benchmarkName (PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg_descr)