{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.PreProcess (preprocessComponent, preprocessExtras,
                                knownSuffixHandlers, ppSuffixes,
                                PPSuffixHandler, PreProcessor(..),
                                mkSimplePreProcessor, runSimplePreProcessor,
                                ppCpp, ppCpp', ppGreenCard, ppC2hs, ppHsc2hs,
                                ppHappy, ppAlex, ppUnlit, platformDefines,
                                unsorted
                               )
    where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Compat.Stack
import Distribution.Simple.PreProcess.Unlit
import Distribution.Backpack.DescribeUnitId
import Distribution.Package
import qualified Distribution.ModuleName as ModuleName
import Distribution.ModuleName (ModuleName)
import Distribution.PackageDescription as PD
import qualified Distribution.InstalledPackageInfo as Installed
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.CCompiler
import Distribution.Simple.Compiler
import Distribution.Simple.LocalBuildInfo
import Distribution.Simple.BuildPaths
import Distribution.Simple.Utils
import Distribution.Simple.Program
import Distribution.Simple.Program.ResponseFile
import Distribution.Simple.Test.LibV09
import Distribution.System
import Distribution.Types.PackageName.Magic
import Distribution.Pretty
import Distribution.Version
import Distribution.Verbosity
import Distribution.Utils.Path
import System.Directory (doesFileExist, doesDirectoryExist)
import System.Info (os, arch)
import System.FilePath (splitExtension, dropExtensions, (</>), (<.>),
                        takeDirectory, normalise, replaceExtension,
                        takeExtensions)
data PreProcessor = PreProcessor {
  
  
  
  
  PreProcessor -> Bool
platformIndependent :: Bool,
  
  
  
  
  
  
  PreProcessor
-> Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering :: Verbosity
             -> [FilePath] 
             -> [ModuleName] 
             -> IO [ModuleName], 
  PreProcessor
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
runPreProcessor :: (FilePath, FilePath) 
                  -> (FilePath, FilePath) 
                  -> Verbosity 
                  -> IO ()     
  }
unsorted :: Verbosity
         -> [FilePath]
         -> [ModuleName]
         -> IO [ModuleName]
unsorted :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted Verbosity
_ [FilePath]
_ [ModuleName]
ms = [ModuleName] -> IO [ModuleName]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [ModuleName]
ms
type  = FilePath -> IO [FilePath]
mkSimplePreProcessor :: (FilePath -> FilePath -> Verbosity -> IO ())
                      -> (FilePath, FilePath)
                      -> (FilePath, FilePath) -> Verbosity -> IO ()
mkSimplePreProcessor :: (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor FilePath -> FilePath -> Verbosity -> IO ()
simplePP
  (FilePath
inBaseDir, FilePath
inRelativeFile)
  (FilePath
outBaseDir, FilePath
outRelativeFile) Verbosity
verbosity = FilePath -> FilePath -> Verbosity -> IO ()
simplePP FilePath
inFile FilePath
outFile Verbosity
verbosity
  where inFile :: FilePath
inFile  = FilePath -> FilePath
normalise (FilePath
inBaseDir  FilePath -> FilePath -> FilePath
</> FilePath
inRelativeFile)
        outFile :: FilePath
outFile = FilePath -> FilePath
normalise (FilePath
outBaseDir FilePath -> FilePath -> FilePath
</> FilePath
outRelativeFile)
runSimplePreProcessor :: PreProcessor -> FilePath -> FilePath -> Verbosity
                      -> IO ()
runSimplePreProcessor :: PreProcessor -> FilePath -> FilePath -> Verbosity -> IO ()
runSimplePreProcessor PreProcessor
pp FilePath
inFile FilePath
outFile Verbosity
verbosity =
  PreProcessor
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
runPreProcessor PreProcessor
pp (FilePath
".", FilePath
inFile) (FilePath
".", FilePath
outFile) Verbosity
verbosity
type PPSuffixHandler
    = (String, 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
-> FilePath
-> PackageIdentifier
-> ComponentName
-> Maybe [(ModuleName, Module)]
-> IO ()
forall a.
Pretty a =>
Verbosity
-> FilePath
-> PackageIdentifier
-> ComponentName
-> Maybe [(ModuleName, a)]
-> IO ()
setupMessage' Verbosity
verbosity FilePath
"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 :: [FilePath]
dirs = (SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
               [ LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi ,LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi]
      let hndlrs :: [(FilePath, PreProcessor)]
hndlrs = BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi
      [ModuleName]
mods <- Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall (t :: * -> *) a.
Foldable t =>
Verbosity
-> [FilePath]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [FilePath]
dirs [(FilePath, PreProcessor)]
hndlrs (Library -> ComponentLocalBuildInfo -> [ModuleName]
allLibModules Library
lib ComponentLocalBuildInfo
clbi)
      [FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ((ModuleName -> FilePath) -> [ModuleName] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> FilePath
ModuleName.toFilePath [ModuleName]
mods) ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
        [FilePath]
-> FilePath -> [(FilePath, PreProcessor)] -> FilePath -> IO ()
pre [FilePath]
dirs (LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
componentBuildDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi) [(FilePath, PreProcessor)]
hndlrs
    (CFLib flib :: ForeignLib
flib@ForeignLib { foreignLibBuildInfo :: ForeignLib -> BuildInfo
foreignLibBuildInfo = BuildInfo
bi, foreignLibName :: ForeignLib -> UnqualComponentName
foreignLibName = UnqualComponentName
nm }) -> do
      let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
      let flibDir :: FilePath
flibDir = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
          dirs :: [FilePath]
dirs    = (SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                                       ,LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi]
      let hndlrs :: [(FilePath, PreProcessor)]
hndlrs = BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi
      [ModuleName]
mods <- Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall (t :: * -> *) a.
Foldable t =>
Verbosity
-> [FilePath]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [FilePath]
dirs [(FilePath, PreProcessor)]
hndlrs (ForeignLib -> [ModuleName]
foreignLibModules ForeignLib
flib)
      [FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ((ModuleName -> FilePath) -> [ModuleName] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> FilePath
ModuleName.toFilePath [ModuleName]
mods) ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
        [FilePath]
-> FilePath -> [(FilePath, PreProcessor)] -> FilePath -> IO ()
pre [FilePath]
dirs FilePath
flibDir [(FilePath, PreProcessor)]
hndlrs
    (CExe exe :: Executable
exe@Executable { buildInfo :: Executable -> BuildInfo
buildInfo = BuildInfo
bi, exeName :: Executable -> UnqualComponentName
exeName = UnqualComponentName
nm }) -> do
      let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
      let exeDir :: FilePath
exeDir = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
          dirs :: [FilePath]
dirs   = (SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                                      ,LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi]
      let hndlrs :: [(FilePath, PreProcessor)]
hndlrs = BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi
      [ModuleName]
mods <- Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> [ModuleName]
-> IO [ModuleName]
forall (t :: * -> *) a.
Foldable t =>
Verbosity
-> [FilePath]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
verbosity [FilePath]
dirs [(FilePath, PreProcessor)]
hndlrs (BuildInfo -> [ModuleName]
otherModules BuildInfo
bi)
      [FilePath] -> (FilePath -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ((ModuleName -> FilePath) -> [ModuleName] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> FilePath
ModuleName.toFilePath [ModuleName]
mods) ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$
        [FilePath]
-> FilePath -> [(FilePath, PreProcessor)] -> FilePath -> IO ()
pre [FilePath]
dirs FilePath
exeDir [(FilePath, PreProcessor)]
hndlrs
      [FilePath]
-> FilePath -> [(FilePath, PreProcessor)] -> FilePath -> IO ()
pre ((SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi)) FilePath
exeDir (BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath -> FilePath
dropExtensions (Executable -> FilePath
modulePath Executable
exe)
    CTest test :: TestSuite
test@TestSuite{ testName :: TestSuite -> UnqualComponentName
testName = UnqualComponentName
nm } -> do
      let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
      case TestSuite -> TestSuiteInterface
testInterface TestSuite
test of
        TestSuiteExeV10 Version
_ FilePath
f ->
            TestSuite -> FilePath -> FilePath -> IO ()
preProcessTest TestSuite
test FilePath
f (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
        TestSuiteLibV09 Version
_ ModuleName
_ -> do
            let testDir :: FilePath
testDir = LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
test
                    FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
test FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
            TestSuite -> FilePath -> IO ()
writeSimpleTestStub TestSuite
test FilePath
testDir
            TestSuite -> FilePath -> FilePath -> IO ()
preProcessTest TestSuite
test (TestSuite -> FilePath
stubFilePath TestSuite
test) FilePath
testDir
        TestSuiteUnsupported TestType
tt ->
            Verbosity -> FilePath -> IO ()
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"No support for preprocessing test "
                          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"suite type " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ TestType -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow TestType
tt
    CBench bm :: Benchmark
bm@Benchmark{ benchmarkName :: Benchmark -> UnqualComponentName
benchmarkName = UnqualComponentName
nm } -> do
      let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
      case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
        BenchmarkExeV10 Version
_ FilePath
f ->
            Benchmark -> FilePath -> FilePath -> IO ()
preProcessBench Benchmark
bm FilePath
f (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
        BenchmarkUnsupported BenchmarkType
tt ->
            Verbosity -> FilePath -> IO ()
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"No support for preprocessing benchmark "
                          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"type " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow BenchmarkType
tt
  where
    orderingFromHandlers :: Verbosity
-> [FilePath]
-> t (a, PreProcessor)
-> [ModuleName]
-> IO [ModuleName]
orderingFromHandlers Verbosity
v [FilePath]
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 -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering PreProcessor
pp Verbosity
v [FilePath]
d [ModuleName]
acc) [ModuleName]
mods t (a, PreProcessor)
hndlrs
    builtinHaskellSuffixes :: [FilePath]
builtinHaskellSuffixes = [FilePath
"hs", FilePath
"lhs", FilePath
"hsig", FilePath
"lhsig"]
    builtinCSuffixes :: [FilePath]
builtinCSuffixes       = [FilePath]
cSourceExtensions
    builtinSuffixes :: [FilePath]
builtinSuffixes        = [FilePath]
builtinHaskellSuffixes [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
builtinCSuffixes
    localHandlers :: BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi = [(FilePath
ext, BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
h BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi) | (FilePath
ext, BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
h) <- [PPSuffixHandler]
handlers]
    pre :: [FilePath]
-> FilePath -> [(FilePath, PreProcessor)] -> FilePath -> IO ()
pre [FilePath]
dirs FilePath
dir [(FilePath, PreProcessor)]
lhndlrs FilePath
fp =
      [SymbolicPath PackageDir SourceDir]
-> FilePath
-> Bool
-> FilePath
-> Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> Bool
-> IO ()
preprocessFile ((FilePath -> SymbolicPath PackageDir SourceDir)
-> [FilePath] -> [SymbolicPath PackageDir SourceDir]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> SymbolicPath PackageDir SourceDir
forall from to. FilePath -> SymbolicPath from to
unsafeMakeSymbolicPath [FilePath]
dirs) FilePath
dir Bool
isSrcDist FilePath
fp Verbosity
verbosity [FilePath]
builtinSuffixes [(FilePath, PreProcessor)]
lhndlrs Bool
True
    preProcessTest :: TestSuite -> FilePath -> FilePath -> IO ()
preProcessTest TestSuite
test = BuildInfo -> [ModuleName] -> FilePath -> FilePath -> IO ()
preProcessComponent (TestSuite -> BuildInfo
testBuildInfo TestSuite
test)
                          (TestSuite -> [ModuleName]
testModules TestSuite
test)
    preProcessBench :: Benchmark -> FilePath -> FilePath -> IO ()
preProcessBench Benchmark
bm = BuildInfo -> [ModuleName] -> FilePath -> FilePath -> IO ()
preProcessComponent (Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bm)
                         (Benchmark -> [ModuleName]
benchmarkModules Benchmark
bm)
    preProcessComponent
        :: BuildInfo
        -> [ModuleName]
        -> FilePath
        -> FilePath
        -> IO ()
    preProcessComponent :: BuildInfo -> [ModuleName] -> FilePath -> FilePath -> IO ()
preProcessComponent BuildInfo
bi [ModuleName]
modules FilePath
exePath FilePath
dir = do
        let biHandlers :: [(FilePath, PreProcessor)]
biHandlers = BuildInfo -> [(FilePath, PreProcessor)]
localHandlers BuildInfo
bi
            sourceDirs :: [FilePath]
sourceDirs = (SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath (BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
                                            , LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi ]
        [IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ [SymbolicPath PackageDir SourceDir]
-> FilePath
-> Bool
-> FilePath
-> Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> Bool
-> IO ()
preprocessFile ((FilePath -> SymbolicPath PackageDir SourceDir)
-> [FilePath] -> [SymbolicPath PackageDir SourceDir]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> SymbolicPath PackageDir SourceDir
forall from to. FilePath -> SymbolicPath from to
unsafeMakeSymbolicPath [FilePath]
sourceDirs) FilePath
dir Bool
isSrcDist
                (ModuleName -> FilePath
ModuleName.toFilePath ModuleName
modu) Verbosity
verbosity [FilePath]
builtinSuffixes
                [(FilePath, PreProcessor)]
biHandlers Bool
False
                | ModuleName
modu <- [ModuleName]
modules ]
        
        
        
        [SymbolicPath PackageDir SourceDir]
-> FilePath
-> Bool
-> FilePath
-> Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> Bool
-> IO ()
preprocessFile (FilePath -> SymbolicPath PackageDir SourceDir
forall from to. FilePath -> SymbolicPath from to
unsafeMakeSymbolicPath FilePath
dir SymbolicPath PackageDir SourceDir
-> [SymbolicPath PackageDir SourceDir]
-> [SymbolicPath PackageDir SourceDir]
forall a. a -> [a] -> [a]
: BuildInfo -> [SymbolicPath PackageDir SourceDir]
hsSourceDirs BuildInfo
bi) FilePath
dir Bool
isSrcDist
            (FilePath -> FilePath
dropExtensions (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
exePath) Verbosity
verbosity
            [FilePath]
builtinSuffixes [(FilePath, PreProcessor)]
biHandlers Bool
False
preprocessFile
    :: [SymbolicPath PackageDir SourceDir] 
    -> FilePath                 
    -> Bool                     
    -> FilePath                 
    -> Verbosity                
    -> [String]                 
    -> [(String, PreProcessor)] 
    -> Bool                     
    -> IO ()
preprocessFile :: [SymbolicPath PackageDir SourceDir]
-> FilePath
-> Bool
-> FilePath
-> Verbosity
-> [FilePath]
-> [(FilePath, PreProcessor)]
-> Bool
-> IO ()
preprocessFile [SymbolicPath PackageDir SourceDir]
searchLoc FilePath
buildLoc Bool
forSDist FilePath
baseFile Verbosity
verbosity [FilePath]
builtinSuffixes [(FilePath, PreProcessor)]
handlers Bool
failOnMissing = do
    
    
    Maybe (FilePath, FilePath)
psrcFiles <- [FilePath]
-> [FilePath] -> FilePath -> IO (Maybe (FilePath, FilePath))
findFileWithExtension' (((FilePath, PreProcessor) -> FilePath)
-> [(FilePath, PreProcessor)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath, PreProcessor) -> FilePath
forall a b. (a, b) -> a
fst [(FilePath, PreProcessor)]
handlers) ((SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath [SymbolicPath PackageDir SourceDir]
searchLoc) FilePath
baseFile
    case Maybe (FilePath, FilePath)
psrcFiles of
        
        
        
        
        
        
        
      Maybe (FilePath, FilePath)
Nothing -> do
                 Maybe FilePath
bsrcFiles <- [FilePath] -> [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileWithExtension [FilePath]
builtinSuffixes (FilePath
buildLoc FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath [SymbolicPath PackageDir SourceDir]
searchLoc) FilePath
baseFile
                 case (Maybe FilePath
bsrcFiles, Bool
failOnMissing) of
                  (Maybe FilePath
Nothing, Bool
True) ->
                    Verbosity -> FilePath -> IO ()
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"can't find source for " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
baseFile
                                  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", " ((SymbolicPath PackageDir SourceDir -> FilePath)
-> [SymbolicPath PackageDir SourceDir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map SymbolicPath PackageDir SourceDir -> FilePath
forall from to. SymbolicPath from to -> FilePath
getSymbolicPath [SymbolicPath PackageDir SourceDir]
searchLoc)
                  (Maybe FilePath, Bool)
_       -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        
      Just (FilePath
psrcLoc, FilePath
psrcRelFile) -> do
            let (FilePath
srcStem, FilePath
ext) = FilePath -> (FilePath, FilePath)
splitExtension FilePath
psrcRelFile
                psrcFile :: FilePath
psrcFile = FilePath
psrcLoc FilePath -> FilePath -> FilePath
</> FilePath
psrcRelFile
                pp :: PreProcessor
pp = PreProcessor -> Maybe PreProcessor -> PreProcessor
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> PreProcessor
forall a. HasCallStack => FilePath -> a
error FilePath
"Distribution.Simple.PreProcess: Just expected")
                               (FilePath -> [(FilePath, PreProcessor)] -> Maybe PreProcessor
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (FilePath -> FilePath
forall a. [a] -> [a]
safeTail FilePath
ext) [(FilePath, 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
              
              
              Maybe FilePath
ppsrcFiles <- [FilePath] -> [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileWithExtension [FilePath]
builtinSuffixes [FilePath
buildLoc] FilePath
baseFile
              Bool
recomp <- case Maybe FilePath
ppsrcFiles of
                          Maybe FilePath
Nothing -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
                          Just FilePath
ppsrcFile ->
                              FilePath
psrcFile FilePath -> FilePath -> IO Bool
`moreRecentFile` FilePath
ppsrcFile
              Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
recomp (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                let destDir :: FilePath
destDir = FilePath
buildLoc FilePath -> FilePath -> FilePath
</> FilePath -> FilePath
dirName FilePath
srcStem
                Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True FilePath
destDir
                PreProcessor
-> (FilePath, FilePath) -> (FilePath, FilePath) -> IO ()
runPreProcessorWithHsBootHack PreProcessor
pp
                   (FilePath
psrcLoc, FilePath
psrcRelFile)
                   (FilePath
buildLoc, FilePath
srcStem FilePath -> FilePath -> FilePath
<.> FilePath
"hs")
  where
    dirName :: FilePath -> FilePath
dirName = FilePath -> FilePath
takeDirectory
    
    
    
    
    
    runPreProcessorWithHsBootHack :: PreProcessor
-> (FilePath, FilePath) -> (FilePath, FilePath) -> IO ()
runPreProcessorWithHsBootHack PreProcessor
pp
      (FilePath
inBaseDir,  FilePath
inRelativeFile)
      (FilePath
outBaseDir, FilePath
outRelativeFile) = do
        PreProcessor
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
runPreProcessor PreProcessor
pp
          (FilePath
inBaseDir, FilePath
inRelativeFile)
          (FilePath
outBaseDir, FilePath
outRelativeFile) Verbosity
verbosity
        Bool
exists <- FilePath -> IO Bool
doesFileExist FilePath
inBoot
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
exists (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Verbosity -> FilePath -> FilePath -> IO ()
copyFileVerbose Verbosity
verbosity FilePath
inBoot FilePath
outBoot
      where
        inBoot :: FilePath
inBoot  = FilePath -> FilePath -> FilePath
replaceExtension FilePath
inFile  FilePath
"hs-boot"
        outBoot :: FilePath
outBoot = FilePath -> FilePath -> FilePath
replaceExtension FilePath
outFile FilePath
"hs-boot"
        inFile :: FilePath
inFile  = FilePath -> FilePath
normalise (FilePath
inBaseDir  FilePath -> FilePath -> FilePath
</> FilePath
inRelativeFile)
        outFile :: FilePath
outFile = FilePath -> FilePath
normalise (FilePath
outBaseDir FilePath -> FilePath -> FilePath
</> FilePath
outRelativeFile)
ppGreenCard :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_
    = PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
        platformIndependent :: Bool
platformIndependent = Bool
False,
        ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
        runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity ->
          Verbosity -> Program -> ProgramDb -> [FilePath] -> IO ()
runDbProgram Verbosity
verbosity Program
greencardProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
              ([FilePath
"-tffi", FilePath
"-o" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outFile, FilePath
inFile])
      }
ppUnlit :: PreProcessor
ppUnlit :: PreProcessor
ppUnlit =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
True,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity ->
      FilePath -> (FilePath -> IO ()) -> IO ()
forall a. FilePath -> (FilePath -> IO a) -> IO a
withUTF8FileContents FilePath
inFile ((FilePath -> IO ()) -> IO ()) -> (FilePath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
contents ->
        (FilePath -> IO ())
-> (FilePath -> IO ()) -> Either FilePath FilePath -> IO ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> FilePath -> IO ()
writeUTF8File FilePath
outFile) (Verbosity -> FilePath -> IO ()
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity) (FilePath -> FilePath -> Either FilePath FilePath
unlit FilePath
inFile FilePath
contents)
  }
ppCpp :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp = [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpp' []
ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp' :: [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpp' [FilePath]
extraArgs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
  case Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi) of
    CompilerFlavor
GHC   -> Program
-> (Version -> Bool)
-> [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
ghcProgram   (Bool -> Version -> Bool
forall a b. a -> b -> a
const Bool
True) [FilePath]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
    CompilerFlavor
GHCJS -> Program
-> (Version -> Bool)
-> [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
ghcjsProgram (Bool -> Version -> Bool
forall a b. a -> b -> a
const Bool
True) [FilePath]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
    CompilerFlavor
_     -> [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpphs  [FilePath]
args BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi
  where cppArgs :: [FilePath]
cppArgs = BuildInfo -> LocalBuildInfo -> [FilePath]
getCppOptions BuildInfo
bi LocalBuildInfo
lbi
        args :: [FilePath]
args    = [FilePath]
cppArgs [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
extraArgs
ppGhcCpp :: Program -> (Version -> Bool)
         -> [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGhcCpp :: Program
-> (Version -> Bool)
-> [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppGhcCpp Program
program Version -> Bool
xHs [FilePath]
extraArgs BuildInfo
_bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
False,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity -> do
      (ConfiguredProgram
prog, Version
version, ProgramDb
_) <- Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion Verbosity
verbosity
                              Program
program VersionRange
anyVersion (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
      Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
prog ([FilePath] -> IO ()) -> [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$
          [FilePath
"-E", FilePath
"-cpp"]
          
          
          
          
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ (if Version -> Bool
xHs Version
version then [FilePath
"-x", FilePath
"hs"] else [])
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"-optP-include", FilePath
"-optP"FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> FilePath -> FilePath
</> FilePath
cppHeaderName) ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"-o", FilePath
outFile, FilePath
inFile]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
extraArgs
  }
ppCpphs :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpphs :: [FilePath]
-> BuildInfo
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> PreProcessor
ppCpphs [FilePath]
extraArgs BuildInfo
_bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
False,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity -> do
      (ConfiguredProgram
cpphsProg, Version
cpphsVersion, ProgramDb
_) <- Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion Verbosity
verbosity
                                        Program
cpphsProgram VersionRange
anyVersion (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
      Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
cpphsProg ([FilePath] -> IO ()) -> [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$
          (FilePath
"-O" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outFile) FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
inFile
        FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"--noline" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"--strip"
        FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: (if Version
cpphsVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
1,Int
6]
             then [FilePath
"--include="FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> FilePath -> FilePath
</> FilePath
cppHeaderName)]
             else [])
        [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
extraArgs
  }
ppHsc2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
False,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity -> do
      (ConfiguredProgram
gccProg, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
gccProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
      (ConfiguredProgram
hsc2hsProg, Version
hsc2hsVersion, ProgramDb
_) <- Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)
requireProgramVersion Verbosity
verbosity
                                          Program
hsc2hsProgram VersionRange
anyVersion (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
      
      let isCross :: Bool
isCross = LocalBuildInfo -> Platform
hostPlatform LocalBuildInfo
lbi Platform -> Platform -> Bool
forall a. Eq a => a -> a -> Bool
/= Platform
buildPlatform
          prependCrossFlags :: [FilePath] -> [FilePath]
prependCrossFlags = if Bool
isCross then (FilePath
"-x"FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:) else [FilePath] -> [FilePath]
forall a. a -> a
id
      let hsc2hsSupportsResponseFiles :: Bool
hsc2hsSupportsResponseFiles = Version
hsc2hsVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
0,Int
68,Int
4]
          pureArgs :: [FilePath]
pureArgs = Version -> ConfiguredProgram -> FilePath -> FilePath -> [FilePath]
genPureArgs Version
hsc2hsVersion ConfiguredProgram
gccProg FilePath
inFile FilePath
outFile
      if Bool
hsc2hsSupportsResponseFiles
      then Verbosity
-> TempFileOptions
-> FilePath
-> FilePath
-> Maybe TextEncoding
-> [FilePath]
-> (FilePath -> IO ())
-> IO ()
forall a.
Verbosity
-> TempFileOptions
-> FilePath
-> FilePath
-> Maybe TextEncoding
-> [FilePath]
-> (FilePath -> IO a)
-> IO a
withResponseFile
             Verbosity
verbosity
             TempFileOptions
defaultTempFileOptions
             (FilePath -> FilePath
takeDirectory FilePath
outFile)
             FilePath
"hsc2hs-response.txt"
             Maybe TextEncoding
forall a. Maybe a
Nothing
             [FilePath]
pureArgs
             (\FilePath
responseFileName ->
                Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
hsc2hsProg ([FilePath] -> [FilePath]
prependCrossFlags [FilePath
"@"FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
responseFileName]))
      else Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
hsc2hsProg ([FilePath] -> [FilePath]
prependCrossFlags [FilePath]
pureArgs)
  }
  where
    
    
    genPureArgs :: Version -> ConfiguredProgram -> String -> String -> [String]
    genPureArgs :: Version -> ConfiguredProgram -> FilePath -> FilePath -> [FilePath]
genPureArgs Version
hsc2hsVersion ConfiguredProgram
gccProg FilePath
inFile FilePath
outFile =
          
          [ FilePath
"--cflag=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- ConfiguredProgram -> [FilePath]
programDefaultArgs  ConfiguredProgram
gccProg
                                    [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> [FilePath]
programOverrideArgs ConfiguredProgram
gccProg ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- ConfiguredProgram -> [FilePath]
programDefaultArgs  ConfiguredProgram
gccProg
                                    [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> [FilePath]
programOverrideArgs ConfiguredProgram
gccProg ]
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
what FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"=-F" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | Bool
isOSX
          , FilePath
opt <- [FilePath] -> [FilePath]
forall a. Eq a => [a] -> [a]
nub ((InstalledPackageInfo -> [FilePath])
-> [InstalledPackageInfo] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap InstalledPackageInfo -> [FilePath]
Installed.frameworkDirs [InstalledPackageInfo]
pkgs)
          , FilePath
what <- [FilePath
"--cflag", FilePath
"--lflag"] ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arg
          | Bool
isOSX
          , FilePath
opt <- BuildInfo -> [FilePath]
PD.frameworks BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ (InstalledPackageInfo -> [FilePath])
-> [InstalledPackageInfo] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap InstalledPackageInfo -> [FilePath]
Installed.frameworks [InstalledPackageInfo]
pkgs
          , FilePath
arg <- [FilePath
"-framework", FilePath
opt] ]
          
          
          
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag="   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- LocalBuildInfo -> [FilePath]
platformDefines LocalBuildInfo
lbi ]
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag=-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
dir | FilePath
dir <- BuildInfo -> [FilePath]
PD.includeDirs  BuildInfo
bi ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag=-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
dir | FilePath
dir <- BuildInfo -> [FilePath]
PD.includeDirs BuildInfo
bi ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag="   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- BuildInfo -> [FilePath]
PD.ccOptions    BuildInfo
bi
                                      [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
PD.cppOptions   BuildInfo
bi
                                      
                                      
                                      
                                      
                                      
                                      
                                      
                                      
                                      ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag="   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <-
               [ FilePath
"-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi,
                 FilePath
"-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ LocalBuildInfo -> FilePath
autogenPackageModulesDir LocalBuildInfo
lbi,
                 FilePath
"-include", LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> FilePath -> FilePath
</> FilePath
cppHeaderName ] ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=-L" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | FilePath
opt <-
              if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
                then BuildInfo -> [FilePath]
PD.extraLibDirsStatic BuildInfo
bi
                else BuildInfo -> [FilePath]
PD.extraLibDirs BuildInfo
bi
          ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=-Wl,-R," FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | Bool
isELF
          , FilePath
opt <-
              if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
                then BuildInfo -> [FilePath]
PD.extraLibDirsStatic BuildInfo
bi
                else BuildInfo -> [FilePath]
PD.extraLibDirs BuildInfo
bi
          ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=-l" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- BuildInfo -> [FilePath]
PD.extraLibs    BuildInfo
bi ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag="   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- BuildInfo -> [FilePath]
PD.ldOptions    BuildInfo
bi ]
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cflag=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | InstalledPackageInfo
pkg <- [InstalledPackageInfo]
pkgs
          , FilePath
opt <- [ FilePath
"-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.includeDirs InstalledPackageInfo
pkg ]
                [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [         FilePath
opt | FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.ccOptions   InstalledPackageInfo
pkg ] ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--lflag=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | InstalledPackageInfo
pkg <- [InstalledPackageInfo]
pkgs
          , FilePath
opt <- [ FilePath
"-L" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.libraryDirs    InstalledPackageInfo
pkg ]
                [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"-Wl,-R," FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | Bool
isELF
                                 , FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.libraryDirs    InstalledPackageInfo
pkg ]
                [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"-l" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
                   | FilePath
opt <-
                       if LocalBuildInfo -> Bool
withFullyStaticExe LocalBuildInfo
lbi
                         then InstalledPackageInfo -> [FilePath]
Installed.extraLibrariesStatic InstalledPackageInfo
pkg
                         else InstalledPackageInfo -> [FilePath]
Installed.extraLibraries InstalledPackageInfo
pkg
                   ]
                [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [         FilePath
opt | FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.ldOptions      InstalledPackageInfo
pkg ] ]
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
preccldFlags
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
hsc2hsOptions BuildInfo
bi
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
postccldFlags
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"-o", FilePath
outFile, FilePath
inFile]
      where
        
        
        
        
        ccldFlags :: [FilePath]
ccldFlags =
          [ FilePath
"--cc=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> FilePath
programPath ConfiguredProgram
gccProg
          , FilePath
"--ld=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> FilePath
programPath ConfiguredProgram
gccProg
          ]
        ([FilePath]
preccldFlags, [FilePath]
postccldFlags)
          | Version
hsc2hsVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int] -> Version
mkVersion [Int
0,Int
68,Int
8] = ([FilePath]
ccldFlags, [])
          | Bool
otherwise                           = ([], [FilePath]
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 ->
                FilePath -> InstalledPackageIndex
forall a. HasCallStack => FilePath -> a
error (FilePath
"ppHsc2hs: broken closure: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [(InstalledPackageInfo, [UnitId])] -> FilePath
forall a. Show a => a -> FilePath
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 (FilePath -> PackageName
mkPackageName FilePath
"rts") of
        [(Version
_, [InstalledPackageInfo
rts])]
           -> InstalledPackageInfo
-> InstalledPackageIndex -> InstalledPackageIndex
PackageIndex.insert InstalledPackageInfo
rts { ldOptions :: [FilePath]
Installed.ldOptions = [] } InstalledPackageIndex
index
        [(Version, [InstalledPackageInfo])]
_  -> FilePath -> InstalledPackageIndex
forall a. HasCallStack => FilePath -> a
error FilePath
"No (or multiple) ghc rts package is registered!!"
ppHsc2hsExtras :: PreProcessorExtras
 FilePath
buildBaseDir = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath
"_hsc.c" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf`) ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                              PreProcessorExtras
getDirectoryContentsRecursive FilePath
buildBaseDir
ppC2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs BuildInfo
bi LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
False,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = \(FilePath
inBaseDir, FilePath
inRelativeFile)
                       (FilePath
outBaseDir, FilePath
outRelativeFile) Verbosity
verbosity -> do
      (ConfiguredProgram
c2hsProg, Version
_, ProgramDb
_) <- 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)
      (ConfiguredProgram
gccProg, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
gccProgram (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
      Verbosity -> ConfiguredProgram -> [FilePath] -> IO ()
runProgram Verbosity
verbosity ConfiguredProgram
c2hsProg ([FilePath] -> IO ()) -> [FilePath] -> IO ()
forall a b. (a -> b) -> a -> b
$
          
           [ FilePath
"--cpp=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ConfiguredProgram -> FilePath
programPath ConfiguredProgram
gccProg, FilePath
"--cppopts=-E" ]
        [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cppopts=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- BuildInfo -> LocalBuildInfo -> [FilePath]
getCppOptions BuildInfo
bi LocalBuildInfo
lbi ]
        [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cppopts=-include" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (LocalBuildInfo -> ComponentLocalBuildInfo -> FilePath
autogenComponentModulesDir LocalBuildInfo
lbi ComponentLocalBuildInfo
clbi FilePath -> FilePath -> FilePath
</> FilePath
cppHeaderName) ]
        [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--include=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outBaseDir ]
          
       [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--cppopts=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt
          | InstalledPackageInfo
pkg <- [InstalledPackageInfo]
pkgs
          , FilePath
opt <- [ FilePath
"-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
opt | FilePath
opt <- InstalledPackageInfo -> [FilePath]
Installed.includeDirs InstalledPackageInfo
pkg ]
                [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [         FilePath
opt | opt :: FilePath
opt@(Char
'-':Char
c:FilePath
_) <- InstalledPackageInfo -> [FilePath]
Installed.ccOptions InstalledPackageInfo
pkg
                                                 
                                                 
                                                 
                                                 
                                                 
                                                 
                                                 
                                                 
                                                 
                                 , Char
c Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
"DIU" ] ]
          
          
           
        [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [ FilePath
"--output-dir=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outBaseDir
           , FilePath
"--output=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outRelativeFile
           , FilePath
inBaseDir FilePath -> FilePath -> FilePath
</> FilePath
inRelativeFile ]
  }
  where
    pkgs :: [InstalledPackageInfo]
pkgs = InstalledPackageIndex -> [InstalledPackageInfo]
forall a. PackageInstalled a => PackageIndex a -> [a]
PackageIndex.topologicalOrder (LocalBuildInfo -> InstalledPackageIndex
installedPkgs LocalBuildInfo
lbi)
ppC2hsExtras :: PreProcessorExtras
 FilePath
d = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FilePath
p -> FilePath -> FilePath
takeExtensions FilePath
p FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
".chs.c") ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                 PreProcessorExtras
getDirectoryContentsRecursive FilePath
d
getCppOptions :: BuildInfo -> LocalBuildInfo -> [String]
getCppOptions :: BuildInfo -> LocalBuildInfo -> [FilePath]
getCppOptions BuildInfo
bi LocalBuildInfo
lbi
    = LocalBuildInfo -> [FilePath]
platformDefines LocalBuildInfo
lbi
   [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
cppOptions BuildInfo
bi
   [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"-I" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
dir | FilePath
dir <- BuildInfo -> [FilePath]
PD.includeDirs BuildInfo
bi]
   [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
opt | opt :: FilePath
opt@(Char
'-':Char
c:FilePath
_) <- BuildInfo -> [FilePath]
PD.ccOptions BuildInfo
bi [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ BuildInfo -> [FilePath]
PD.cxxOptions BuildInfo
bi, Char
c Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
"DIU"]
platformDefines :: LocalBuildInfo -> [String]
platformDefines :: LocalBuildInfo -> [FilePath]
platformDefines LocalBuildInfo
lbi =
  case Compiler -> CompilerFlavor
compilerFlavor Compiler
comp of
    CompilerFlavor
GHC  ->
      [FilePath
"-D__GLASGOW_HASKELL__=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
versionInt Version
version] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      [FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
os   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_BUILD_OS=1"] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      [FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arch FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_BUILD_ARCH=1"] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
os'   -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
os'   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_OS=1")   [FilePath]
osStr [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
arch' -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arch' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_ARCH=1") [FilePath]
archStr
    CompilerFlavor
GHCJS ->
      [FilePath]
compatGlasgowHaskell [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      [FilePath
"-D__GHCJS__=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
versionInt Version
version] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      [FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
os   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_BUILD_OS=1"] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      [FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arch FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_BUILD_ARCH=1"] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
os'   -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
os'   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_OS=1")   [FilePath]
osStr [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
      (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
arch' -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arch' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_ARCH=1") [FilePath]
archStr
    HaskellSuite {} ->
      [FilePath
"-D__HASKELL_SUITE__"] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
        (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
os'   -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
os'   FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_OS=1")   [FilePath]
osStr [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++
        (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\FilePath
arch' -> FilePath
"-D" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
arch' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"_HOST_ARCH=1") [FilePath]
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 :: [FilePath]
compatGlasgowHaskell =
      [FilePath]
-> (Version -> [FilePath]) -> Maybe Version -> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Version
v -> [FilePath
"-D__GLASGOW_HASKELL__=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
versionInt Version
v])
               (CompilerFlavor -> Compiler -> Maybe Version
compilerCompatVersion CompilerFlavor
GHC Compiler
comp)
    
    
    
    versionInt :: Version -> String
    versionInt :: Version -> FilePath
versionInt Version
v = case Version -> [Int]
versionNumbers Version
v of
      [] -> FilePath
"1"
      [Int
n] -> Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n
      Int
n1:Int
n2:[Int]
_ ->
        
        
        let s1 :: FilePath
s1 = Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n1
            s2 :: FilePath
s2 = Int -> FilePath
forall a. Show a => a -> FilePath
show Int
n2
            middle :: FilePath
middle = case FilePath
s2 of
                     Char
_ : Char
_ : FilePath
_ -> FilePath
""
                     FilePath
_         -> FilePath
"0"
        in FilePath
s1 FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
middle FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
s2
    osStr :: [FilePath]
osStr = case OS
hostOS of
      OS
Linux     -> [FilePath
"linux"]
      OS
Windows   -> [FilePath
"mingw32"]
      OS
OSX       -> [FilePath
"darwin"]
      OS
FreeBSD   -> [FilePath
"freebsd"]
      OS
OpenBSD   -> [FilePath
"openbsd"]
      OS
NetBSD    -> [FilePath
"netbsd"]
      OS
DragonFly -> [FilePath
"dragonfly"]
      OS
Solaris   -> [FilePath
"solaris2"]
      OS
AIX       -> [FilePath
"aix"]
      OS
HPUX      -> [FilePath
"hpux"]
      OS
IRIX      -> [FilePath
"irix"]
      OS
HaLVM     -> []
      OS
IOS       -> [FilePath
"ios"]
      OS
Android   -> [FilePath
"android"]
      OS
Ghcjs     -> [FilePath
"ghcjs"]
      OS
Wasi      -> [FilePath
"wasi"]
      OS
Hurd      -> [FilePath
"hurd"]
      OtherOS FilePath
_ -> []
    archStr :: [FilePath]
archStr = case Arch
hostArch of
      Arch
I386        -> [FilePath
"i386"]
      Arch
X86_64      -> [FilePath
"x86_64"]
      Arch
PPC         -> [FilePath
"powerpc"]
      Arch
PPC64       -> [FilePath
"powerpc64"]
      Arch
Sparc       -> [FilePath
"sparc"]
      Arch
Arm         -> [FilePath
"arm"]
      Arch
AArch64     -> [FilePath
"aarch64"]
      Arch
Mips        -> [FilePath
"mips"]
      Arch
SH          -> []
      Arch
IA64        -> [FilePath
"ia64"]
      Arch
S390        -> [FilePath
"s390"]
      Arch
S390X       -> [FilePath
"s390x"]
      Arch
Alpha       -> [FilePath
"alpha"]
      Arch
Hppa        -> [FilePath
"hppa"]
      Arch
Rs6000      -> [FilePath
"rs6000"]
      Arch
M68k        -> [FilePath
"m68k"]
      Arch
Vax         -> [FilePath
"vax"]
      Arch
JavaScript  -> [FilePath
"javascript"]
      Arch
Wasm32      -> [FilePath
"wasm32"]
      OtherArch FilePath
_ -> []
ppHappy :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_ = PreProcessor
pp { platformIndependent :: Bool
platformIndependent = Bool
True }
  where pp :: PreProcessor
pp = LocalBuildInfo -> Program -> [FilePath] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
happyProgram (CompilerFlavor -> [FilePath]
hcFlags CompilerFlavor
hc)
        hc :: CompilerFlavor
hc = Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
        hcFlags :: CompilerFlavor -> [FilePath]
hcFlags CompilerFlavor
GHC = [FilePath
"-agc"]
        hcFlags CompilerFlavor
GHCJS = [FilePath
"-agc"]
        hcFlags CompilerFlavor
_ = []
ppAlex :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex :: BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex BuildInfo
_ LocalBuildInfo
lbi ComponentLocalBuildInfo
_ = PreProcessor
pp { platformIndependent :: Bool
platformIndependent = Bool
True }
  where pp :: PreProcessor
pp = LocalBuildInfo -> Program -> [FilePath] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
alexProgram (CompilerFlavor -> [FilePath]
hcFlags CompilerFlavor
hc)
        hc :: CompilerFlavor
hc = Compiler -> CompilerFlavor
compilerFlavor (LocalBuildInfo -> Compiler
compiler LocalBuildInfo
lbi)
        hcFlags :: CompilerFlavor -> [FilePath]
hcFlags CompilerFlavor
GHC = [FilePath
"-g"]
        hcFlags CompilerFlavor
GHCJS = [FilePath
"-g"]
        hcFlags CompilerFlavor
_ = []
standardPP :: LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP :: LocalBuildInfo -> Program -> [FilePath] -> PreProcessor
standardPP LocalBuildInfo
lbi Program
prog [FilePath]
args =
  PreProcessor :: Bool
-> (Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName])
-> ((FilePath, FilePath)
    -> (FilePath, FilePath) -> Verbosity -> IO ())
-> PreProcessor
PreProcessor {
    platformIndependent :: Bool
platformIndependent = Bool
False,
    ppOrdering :: Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
ppOrdering = Verbosity -> [FilePath] -> [ModuleName] -> IO [ModuleName]
unsorted,
    runPreProcessor :: (FilePath, FilePath) -> (FilePath, FilePath) -> Verbosity -> IO ()
runPreProcessor = (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
mkSimplePreProcessor ((FilePath -> FilePath -> Verbosity -> IO ())
 -> (FilePath, FilePath)
 -> (FilePath, FilePath)
 -> Verbosity
 -> IO ())
-> (FilePath -> FilePath -> Verbosity -> IO ())
-> (FilePath, FilePath)
-> (FilePath, FilePath)
-> Verbosity
-> IO ()
forall a b. (a -> b) -> a -> b
$ \FilePath
inFile FilePath
outFile Verbosity
verbosity ->
      Verbosity -> Program -> ProgramDb -> [FilePath] -> IO ()
runDbProgram Verbosity
verbosity Program
prog (LocalBuildInfo -> ProgramDb
withPrograms LocalBuildInfo
lbi)
                           ([FilePath]
args [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"-o", FilePath
outFile, FilePath
inFile])
  }
ppSuffixes :: [ PPSuffixHandler ] -> [String]
ppSuffixes :: [PPSuffixHandler] -> [FilePath]
ppSuffixes = (PPSuffixHandler -> FilePath) -> [PPSuffixHandler] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map PPSuffixHandler -> FilePath
forall a b. (a, b) -> a
fst
knownSuffixHandlers :: [ PPSuffixHandler ]
knownSuffixHandlers :: [PPSuffixHandler]
knownSuffixHandlers =
  [ (FilePath
"gc",     BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard)
  , (FilePath
"chs",    BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs)
  , (FilePath
"hsc",    BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs)
  , (FilePath
"x",      BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex)
  , (FilePath
"y",      BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy)
  , (FilePath
"ly",     BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy)
  , (FilePath
"cpphs",  BuildInfo
-> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp)
  ]
knownExtrasHandlers :: [ PreProcessorExtras ]
knownExtrasHandlers :: [PreProcessorExtras]
knownExtrasHandlers = [ PreProcessorExtras
ppC2hsExtras, PreProcessorExtras
ppHsc2hsExtras ]
preprocessExtras :: Verbosity
                 -> Component
                 -> LocalBuildInfo
                 -> IO [FilePath]
 Verbosity
verbosity Component
comp LocalBuildInfo
lbi = case Component
comp of
  CLib Library
_ -> PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi
  (CExe Executable { exeName :: Executable -> UnqualComponentName
exeName = UnqualComponentName
nm }) -> do
    let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
    PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
  (CFLib ForeignLib { foreignLibName :: ForeignLib -> UnqualComponentName
foreignLibName = UnqualComponentName
nm }) -> do
    let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
nm
    PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
  CTest TestSuite
test -> do
    let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ TestSuite -> UnqualComponentName
testName TestSuite
test
    case TestSuite -> TestSuiteInterface
testInterface TestSuite
test of
      TestSuiteExeV10 Version
_ FilePath
_ ->
          PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
      TestSuiteLibV09 Version
_ ModuleName
_ ->
          PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
test FilePath -> FilePath -> FilePath
</> TestSuite -> FilePath
stubName TestSuite
test FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
      TestSuiteUnsupported TestType
tt ->
        Verbosity -> PreProcessorExtras
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ FilePath
"No support for preprocessing test suite type " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
                         TestType -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow TestType
tt
  CBench Benchmark
bm -> do
    let nm' :: FilePath
nm' = UnqualComponentName -> FilePath
unUnqualComponentName (UnqualComponentName -> FilePath)
-> UnqualComponentName -> FilePath
forall a b. (a -> b) -> a -> b
$ Benchmark -> UnqualComponentName
benchmarkName Benchmark
bm
    case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
bm of
      BenchmarkExeV10 Version
_ FilePath
_ ->
          PreProcessorExtras
pp PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ LocalBuildInfo -> FilePath
buildDir LocalBuildInfo
lbi FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
</> FilePath
nm' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-tmp"
      BenchmarkUnsupported BenchmarkType
tt ->
          Verbosity -> PreProcessorExtras
forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity PreProcessorExtras -> PreProcessorExtras
forall a b. (a -> b) -> a -> b
$ FilePath
"No support for preprocessing benchmark "
                        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"type " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow BenchmarkType
tt
  where
    pp :: FilePath -> IO [FilePath]
    pp :: PreProcessorExtras
pp FilePath
dir = do
        Bool
b <- FilePath -> IO Bool
doesDirectoryExist FilePath
dir
        if Bool
b
         then ((FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
dir FilePath -> FilePath -> FilePath
</>) ([FilePath] -> [FilePath])
-> ([[FilePath]] -> [FilePath]) -> [[FilePath]] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
not_sub ([FilePath] -> [FilePath])
-> ([[FilePath]] -> [FilePath]) -> [[FilePath]] -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat)
                 ([[FilePath]] -> [FilePath]) -> IO [[FilePath]] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [PreProcessorExtras]
-> (PreProcessorExtras -> IO [FilePath]) -> IO [[FilePath]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [PreProcessorExtras]
knownExtrasHandlers
                     ((PreProcessorExtras -> WithCallStack (IO [FilePath]))
-> WithCallStack (PreProcessorExtras -> IO [FilePath])
forall a b.
(a -> WithCallStack (IO b)) -> WithCallStack (a -> IO b)
withLexicalCallStack (\PreProcessorExtras
f -> PreProcessorExtras
f FilePath
dir))
         else [FilePath] -> IO [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    
    
    
    
    
    
    
    
    
    not_sub :: FilePath -> Bool
not_sub FilePath
p = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ Bool -> Bool
not (FilePath
pre FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
p) | FilePath
pre <- [FilePath]
component_dirs ]
    component_dirs :: [FilePath]
component_dirs = PackageDescription -> [FilePath]
component_names (LocalBuildInfo -> PackageDescription
localPkgDescr LocalBuildInfo
lbi)
    
    component_names :: PackageDescription -> [FilePath]
component_names PackageDescription
pkg_descr = (UnqualComponentName -> FilePath)
-> [UnqualComponentName] -> [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UnqualComponentName -> FilePath
unUnqualComponentName ([UnqualComponentName] -> [FilePath])
-> [UnqualComponentName] -> [FilePath]
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)