{-# 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
                               )
    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.Test.LibV09
import Distribution.System
import Distribution.Text
import Distribution.Version
import Distribution.Verbosity
import Distribution.Types.ForeignLib
import Distribution.Types.UnqualComponentName
import System.Directory (doesFileExist)
import System.Info (os, arch)
import System.FilePath (splitExtension, dropExtensions, (</>), (<.>),
                        takeDirectory, normalise, replaceExtension,
                        takeExtensions)
data PreProcessor = PreProcessor {
  
  
  
  
  platformIndependent :: Bool,
  
  
  
  runPreProcessor :: (FilePath, FilePath) 
                  -> (FilePath, FilePath) 
                  -> Verbosity 
                  -> IO ()     
  }
type PreProcessorExtras = FilePath -> IO [FilePath]
mkSimplePreProcessor :: (FilePath -> FilePath -> Verbosity -> IO ())
                      -> (FilePath, FilePath)
                      -> (FilePath, FilePath) -> Verbosity -> IO ()
mkSimplePreProcessor simplePP
  (inBaseDir, inRelativeFile)
  (outBaseDir, outRelativeFile) verbosity = simplePP inFile outFile verbosity
  where inFile  = normalise (inBaseDir  </> inRelativeFile)
        outFile = normalise (outBaseDir </> outRelativeFile)
runSimplePreProcessor :: PreProcessor -> FilePath -> FilePath -> Verbosity
                      -> IO ()
runSimplePreProcessor pp inFile outFile verbosity =
  runPreProcessor pp (".", inFile) (".", outFile) verbosity
type PPSuffixHandler
    = (String, BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor)
preprocessComponent :: PackageDescription
                    -> Component
                    -> LocalBuildInfo
                    -> ComponentLocalBuildInfo
                    -> Bool
                    -> Verbosity
                    -> [PPSuffixHandler]
                    -> IO ()
preprocessComponent pd comp lbi clbi isSrcDist verbosity handlers = do
 
 
 setupMessage' verbosity "Preprocessing" (packageId pd)
    (componentLocalName clbi) (Nothing :: Maybe [(ModuleName, Module)])
 case comp of
  (CLib lib@Library{ libBuildInfo = bi }) -> do
    let dirs = hsSourceDirs bi ++ [autogenComponentModulesDir lbi clbi
                                  ,autogenPackageModulesDir lbi]
    for_ (map ModuleName.toFilePath $ allLibModules lib clbi) $
      pre dirs (componentBuildDir lbi clbi) (localHandlers bi)
  (CFLib flib@ForeignLib { foreignLibBuildInfo = bi, foreignLibName = nm }) -> do
    let nm' = unUnqualComponentName nm
    let flibDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
        dirs    = hsSourceDirs bi ++ [autogenComponentModulesDir lbi clbi
                                     ,autogenPackageModulesDir lbi]
    for_ (map ModuleName.toFilePath $ foreignLibModules flib) $
      pre dirs flibDir (localHandlers bi)
  (CExe exe@Executable { buildInfo = bi, exeName = nm }) -> do
    let nm' = unUnqualComponentName nm
    let exeDir = buildDir lbi </> nm' </> nm' ++ "-tmp"
        dirs   = hsSourceDirs bi ++ [autogenComponentModulesDir lbi clbi
                                    ,autogenPackageModulesDir lbi]
    for_ (map ModuleName.toFilePath $ otherModules bi) $
      pre dirs exeDir (localHandlers bi)
    pre (hsSourceDirs bi) exeDir (localHandlers bi) $
      dropExtensions (modulePath exe)
  CTest test@TestSuite{ testName = nm } -> do
    let nm' = unUnqualComponentName nm
    case testInterface test of
      TestSuiteExeV10 _ f ->
          preProcessTest test f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
      TestSuiteLibV09 _ _ -> do
          let testDir = buildDir lbi </> stubName test
                  </> stubName test ++ "-tmp"
          writeSimpleTestStub test testDir
          preProcessTest test (stubFilePath test) testDir
      TestSuiteUnsupported tt ->
          die' verbosity $ "No support for preprocessing test "
                        ++ "suite type " ++ display tt
  CBench bm@Benchmark{ benchmarkName = nm } -> do
    let nm' = unUnqualComponentName nm
    case benchmarkInterface bm of
      BenchmarkExeV10 _ f ->
          preProcessBench bm f $ buildDir lbi </> nm' </> nm' ++ "-tmp"
      BenchmarkUnsupported tt ->
          die' verbosity $ "No support for preprocessing benchmark "
                        ++ "type " ++ display tt
  where
    builtinHaskellSuffixes = ["hs", "lhs", "hsig", "lhsig"]
    builtinCSuffixes       = cSourceExtensions
    builtinSuffixes        = builtinHaskellSuffixes ++ builtinCSuffixes
    localHandlers bi = [(ext, h bi lbi clbi) | (ext, h) <- handlers]
    pre dirs dir lhndlrs fp =
      preprocessFile dirs dir isSrcDist fp verbosity builtinSuffixes lhndlrs
    preProcessTest test = preProcessComponent (testBuildInfo test)
                          (testModules test)
    preProcessBench bm = preProcessComponent (benchmarkBuildInfo bm)
                         (benchmarkModules bm)
    preProcessComponent bi modules exePath dir = do
        let biHandlers = localHandlers bi
            sourceDirs = hsSourceDirs bi ++ [ autogenComponentModulesDir lbi clbi
                                            , autogenPackageModulesDir lbi ]
        sequence_ [ preprocessFile sourceDirs dir isSrcDist
                (ModuleName.toFilePath modu) verbosity builtinSuffixes
                biHandlers
                | modu <- modules ]
        preprocessFile (dir : (hsSourceDirs bi)) dir isSrcDist
            (dropExtensions $ exePath) verbosity
            builtinSuffixes biHandlers
preprocessFile
    :: [FilePath]               
    -> FilePath                 
    -> Bool                     
    -> FilePath                 
    -> Verbosity                
    -> [String]                 
    -> [(String, PreProcessor)] 
    -> IO ()
preprocessFile searchLoc buildLoc forSDist baseFile verbosity builtinSuffixes handlers = do
    
    
    psrcFiles <- findFileWithExtension' (map fst handlers) searchLoc baseFile
    case psrcFiles of
        
        
        
        
        
        
        
      Nothing -> do
                 bsrcFiles <- findFileWithExtension builtinSuffixes (buildLoc : searchLoc) baseFile
                 case bsrcFiles of
                  Nothing ->
                    die' verbosity $ "can't find source for " ++ baseFile
                                  ++ " in " ++ intercalate ", " searchLoc
                  _       -> return ()
        
      Just (psrcLoc, psrcRelFile) -> do
            let (srcStem, ext) = splitExtension psrcRelFile
                psrcFile = psrcLoc </> psrcRelFile
                pp = fromMaybe (error "Distribution.Simple.PreProcess: Just expected")
                               (lookup (tailNotNull ext) handlers)
            
            
            
            
            
            
            
            
            
            when (not forSDist || forSDist && platformIndependent pp) $ do
              
              
              ppsrcFiles <- findFileWithExtension builtinSuffixes [buildLoc] baseFile
              recomp <- case ppsrcFiles of
                          Nothing -> return True
                          Just ppsrcFile ->
                              psrcFile `moreRecentFile` ppsrcFile
              when recomp $ do
                let destDir = buildLoc </> dirName srcStem
                createDirectoryIfMissingVerbose verbosity True destDir
                runPreProcessorWithHsBootHack pp
                   (psrcLoc, psrcRelFile)
                   (buildLoc, srcStem <.> "hs")
  where
    dirName = takeDirectory
    tailNotNull [] = []
    tailNotNull x  = tail x
    
    
    
    
    
    runPreProcessorWithHsBootHack pp
      (inBaseDir,  inRelativeFile)
      (outBaseDir, outRelativeFile) = do
        runPreProcessor pp
          (inBaseDir, inRelativeFile)
          (outBaseDir, outRelativeFile) verbosity
        exists <- doesFileExist inBoot
        when exists $ copyFileVerbose verbosity inBoot outBoot
      where
        inBoot  = replaceExtension inFile  "hs-boot"
        outBoot = replaceExtension outFile "hs-boot"
        inFile  = normalise (inBaseDir  </> inRelativeFile)
        outFile = normalise (outBaseDir </> outRelativeFile)
ppGreenCard :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGreenCard _ lbi _
    = PreProcessor {
        platformIndependent = False,
        runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity ->
          runDbProgram verbosity greencardProgram (withPrograms lbi)
              (["-tffi", "-o" ++ outFile, inFile])
      }
ppUnlit :: PreProcessor
ppUnlit =
  PreProcessor {
    platformIndependent = True,
    runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity ->
      withUTF8FileContents inFile $ \contents ->
        either (writeUTF8File outFile) (die' verbosity) (unlit inFile contents)
  }
ppCpp :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp = ppCpp' []
ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpp' extraArgs bi lbi clbi =
  case compilerFlavor (compiler lbi) of
    GHC   -> ppGhcCpp ghcProgram   (>= mkVersion [6,6])  args bi lbi clbi
    GHCJS -> ppGhcCpp ghcjsProgram (const True)          args bi lbi clbi
    _     -> ppCpphs  args bi lbi clbi
  where cppArgs = getCppOptions bi lbi
        args    = cppArgs ++ extraArgs
ppGhcCpp :: Program -> (Version -> Bool)
         -> [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppGhcCpp program xHs extraArgs _bi lbi clbi =
  PreProcessor {
    platformIndependent = False,
    runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity -> do
      (prog, version, _) <- requireProgramVersion verbosity
                              program anyVersion (withPrograms lbi)
      runProgram verbosity prog $
          ["-E", "-cpp"]
          
          
          
          
          
       ++ (if xHs version then ["-x", "hs"] else [])
       ++ [ "-optP-include", "-optP"++ (autogenComponentModulesDir lbi clbi </> cppHeaderName) ]
       ++ ["-o", outFile, inFile]
       ++ extraArgs
  }
ppCpphs :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppCpphs extraArgs _bi lbi clbi =
  PreProcessor {
    platformIndependent = False,
    runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity -> do
      (cpphsProg, cpphsVersion, _) <- requireProgramVersion verbosity
                                        cpphsProgram anyVersion (withPrograms lbi)
      runProgram verbosity cpphsProg $
          ("-O" ++ outFile) : inFile
        : "--noline" : "--strip"
        : (if cpphsVersion >= mkVersion [1,6]
             then ["--include="++ (autogenComponentModulesDir lbi clbi </> cppHeaderName)]
             else [])
        ++ extraArgs
  }
ppHsc2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHsc2hs bi lbi clbi =
  PreProcessor {
    platformIndependent = False,
    runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity -> do
      (gccProg, _) <- requireProgram verbosity gccProgram (withPrograms lbi)
      runDbProgram verbosity hsc2hsProgram (withPrograms lbi) $
          [ "--cc=" ++ programPath gccProg
          , "--ld=" ++ programPath gccProg ]
          
       ++ [ "--cflag=" ++ opt | opt <- programDefaultArgs  gccProg
                                    ++ programOverrideArgs gccProg ]
       ++ [ "--lflag=" ++ opt | opt <- programDefaultArgs  gccProg
                                    ++ programOverrideArgs gccProg ]
          
       ++ [ what ++ "=-F" ++ opt
          | isOSX
          , opt <- nub (concatMap Installed.frameworkDirs pkgs)
          , what <- ["--cflag", "--lflag"] ]
       ++ [ "--lflag=" ++ arg
          | isOSX
          , opt <- PD.frameworks bi ++ concatMap Installed.frameworks pkgs
          , arg <- ["-framework", opt] ]
          
          
          
          
       ++ [ "--cflag="   ++ opt | opt <- platformDefines lbi ]
          
       ++ [ "--cflag=-I" ++ dir | dir <- PD.includeDirs  bi ]
       ++ [ "--cflag=-I" ++ buildDir lbi </> dir | dir <- PD.includeDirs bi ]
       ++ [ "--cflag="   ++ opt | opt <- PD.ccOptions    bi
                                      ++ PD.cppOptions   bi ]
       ++ [ "--cflag="   ++ opt | opt <-
               [ "-I" ++ autogenComponentModulesDir lbi clbi,
                 "-I" ++ autogenPackageModulesDir lbi,
                 "-include", autogenComponentModulesDir lbi clbi </> cppHeaderName ] ]
       ++ [ "--lflag=-L" ++ opt | opt <- PD.extraLibDirs bi ]
       ++ [ "--lflag=-Wl,-R," ++ opt | isELF
                                , opt <- PD.extraLibDirs bi ]
       ++ [ "--lflag=-l" ++ opt | opt <- PD.extraLibs    bi ]
       ++ [ "--lflag="   ++ opt | opt <- PD.ldOptions    bi ]
          
       ++ [ "--cflag=" ++ opt
          | pkg <- pkgs
          , opt <- [ "-I" ++ opt | opt <- Installed.includeDirs pkg ]
                ++ [         opt | opt <- Installed.ccOptions   pkg ] ]
       ++ [ "--lflag=" ++ opt
          | pkg <- pkgs
          , opt <- [ "-L" ++ opt | opt <- Installed.libraryDirs    pkg ]
                ++ [ "-Wl,-R," ++ opt | isELF
                                 , opt <- Installed.libraryDirs    pkg ]
                ++ [ "-l" ++ opt | opt <- Installed.extraLibraries pkg ]
                ++ [         opt | opt <- Installed.ldOptions      pkg ] ]
       ++ ["-o", outFile, inFile]
  }
  where
    hacked_index = packageHacks (installedPkgs lbi)
    
    
    
    pkgs = PackageIndex.topologicalOrder $
           case PackageIndex.dependencyClosure hacked_index
                    (map fst (componentPackageDeps clbi)) of
            Left index' -> index'
            Right inf ->
                error ("ppHsc2hs: broken closure: " ++ show inf)
    isOSX = case buildOS of OSX -> True; _ -> False
    isELF = case buildOS of OSX -> False; Windows -> False; AIX -> False; _ -> True;
    packageHacks = case compilerFlavor (compiler lbi) of
      GHC   -> hackRtsPackage
      GHCJS -> hackRtsPackage
      _     -> id
    
    
    
    
    hackRtsPackage index =
      case PackageIndex.lookupPackageName index (mkPackageName "rts") of
        [(_, [rts])]
           -> PackageIndex.insert rts { Installed.ldOptions = [] } index
        _  -> error "No (or multiple) ghc rts package is registered!!"
ppHsc2hsExtras :: PreProcessorExtras
ppHsc2hsExtras buildBaseDir = filter ("_hsc.c" `isSuffixOf`) `fmap`
                              getDirectoryContentsRecursive buildBaseDir
ppC2hs :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppC2hs bi lbi clbi =
  PreProcessor {
    platformIndependent = False,
    runPreProcessor = \(inBaseDir, inRelativeFile)
                       (outBaseDir, outRelativeFile) verbosity -> do
      (c2hsProg, _, _) <- requireProgramVersion verbosity
                            c2hsProgram (orLaterVersion (mkVersion [0,15]))
                            (withPrograms lbi)
      (gccProg, _) <- requireProgram verbosity gccProgram (withPrograms lbi)
      runProgram verbosity c2hsProg $
          
           [ "--cpp=" ++ programPath gccProg, "--cppopts=-E" ]
        ++ [ "--cppopts=" ++ opt | opt <- getCppOptions bi lbi ]
        ++ [ "--cppopts=-include" ++ (autogenComponentModulesDir lbi clbi </> 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 = PackageIndex.topologicalOrder (installedPkgs lbi)
ppC2hsExtras :: PreProcessorExtras
ppC2hsExtras d = filter (\p -> takeExtensions p == ".chs.c") `fmap`
                 getDirectoryContentsRecursive d
getCppOptions :: BuildInfo -> LocalBuildInfo -> [String]
getCppOptions bi lbi
    = platformDefines lbi
   ++ cppOptions bi
   ++ ["-I" ++ dir | dir <- PD.includeDirs bi]
   ++ [opt | opt@('-':c:_) <- PD.ccOptions bi, c `elem` "DIU"]
platformDefines :: LocalBuildInfo -> [String]
platformDefines lbi =
  case compilerFlavor comp of
    GHC  ->
      ["-D__GLASGOW_HASKELL__=" ++ versionInt version] ++
      ["-D" ++ os   ++ "_BUILD_OS=1"] ++
      ["-D" ++ arch ++ "_BUILD_ARCH=1"] ++
      map (\os'   -> "-D" ++ os'   ++ "_HOST_OS=1")   osStr ++
      map (\arch' -> "-D" ++ arch' ++ "_HOST_ARCH=1") archStr
    GHCJS ->
      compatGlasgowHaskell ++
      ["-D__GHCJS__=" ++ versionInt version] ++
      ["-D" ++ os   ++ "_BUILD_OS=1"] ++
      ["-D" ++ arch ++ "_BUILD_ARCH=1"] ++
      map (\os'   -> "-D" ++ os'   ++ "_HOST_OS=1")   osStr ++
      map (\arch' -> "-D" ++ arch' ++ "_HOST_ARCH=1") archStr
    JHC  -> ["-D__JHC__=" ++ versionInt version]
    HaskellSuite {} ->
      ["-D__HASKELL_SUITE__"] ++
        map (\os'   -> "-D" ++ os'   ++ "_HOST_OS=1")   osStr ++
        map (\arch' -> "-D" ++ arch' ++ "_HOST_ARCH=1") archStr
    _    -> []
  where
    comp = compiler lbi
    Platform hostArch hostOS = hostPlatform lbi
    version = compilerVersion comp
    compatGlasgowHaskell =
      maybe [] (\v -> ["-D__GLASGOW_HASKELL__=" ++ versionInt v])
               (compilerCompatVersion GHC comp)
    
    
    
    versionInt :: Version -> String
    versionInt v = case versionNumbers v of
      [] -> "1"
      [n] -> show n
      n1:n2:_ ->
        
        
        let s1 = show n1
            s2 = show n2
            middle = case s2 of
                     _ : _ : _ -> ""
                     _         -> "0"
        in s1 ++ middle ++ s2
    osStr = case hostOS of
      Linux     -> ["linux"]
      Windows   -> ["mingw32"]
      OSX       -> ["darwin"]
      FreeBSD   -> ["freebsd"]
      OpenBSD   -> ["openbsd"]
      NetBSD    -> ["netbsd"]
      DragonFly -> ["dragonfly"]
      Solaris   -> ["solaris2"]
      AIX       -> ["aix"]
      HPUX      -> ["hpux"]
      IRIX      -> ["irix"]
      HaLVM     -> []
      IOS       -> ["ios"]
      Android   -> ["android"]
      Ghcjs     -> ["ghcjs"]
      Hurd      -> ["hurd"]
      OtherOS _ -> []
    archStr = case hostArch of
      I386        -> ["i386"]
      X86_64      -> ["x86_64"]
      PPC         -> ["powerpc"]
      PPC64       -> ["powerpc64"]
      Sparc       -> ["sparc"]
      Arm         -> ["arm"]
      Mips        -> ["mips"]
      SH          -> []
      IA64        -> ["ia64"]
      S390        -> ["s390"]
      Alpha       -> ["alpha"]
      Hppa        -> ["hppa"]
      Rs6000      -> ["rs6000"]
      M68k        -> ["m68k"]
      Vax         -> ["vax"]
      JavaScript  -> ["javascript"]
      OtherArch _ -> []
ppHappy :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppHappy _ lbi _ = pp { platformIndependent = True }
  where pp = standardPP lbi happyProgram (hcFlags hc)
        hc = compilerFlavor (compiler lbi)
        hcFlags GHC = ["-agc"]
        hcFlags GHCJS = ["-agc"]
        hcFlags _ = []
ppAlex :: BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
ppAlex _ lbi _ = pp { platformIndependent = True }
  where pp = standardPP lbi alexProgram (hcFlags hc)
        hc = compilerFlavor (compiler lbi)
        hcFlags GHC = ["-g"]
        hcFlags GHCJS = ["-g"]
        hcFlags _ = []
standardPP :: LocalBuildInfo -> Program -> [String] -> PreProcessor
standardPP lbi prog args =
  PreProcessor {
    platformIndependent = False,
    runPreProcessor = mkSimplePreProcessor $ \inFile outFile verbosity ->
      runDbProgram verbosity prog (withPrograms lbi)
                           (args ++ ["-o", outFile, inFile])
  }
ppSuffixes :: [ PPSuffixHandler ] -> [String]
ppSuffixes = map fst
knownSuffixHandlers :: [ PPSuffixHandler ]
knownSuffixHandlers =
  [ ("gc",     ppGreenCard)
  , ("chs",    ppC2hs)
  , ("hsc",    ppHsc2hs)
  , ("x",      ppAlex)
  , ("y",      ppHappy)
  , ("ly",     ppHappy)
  , ("cpphs",  ppCpp)
  ]
knownExtrasHandlers :: [ PreProcessorExtras ]
knownExtrasHandlers = [ ppC2hsExtras, ppHsc2hsExtras ]
preprocessExtras :: Verbosity
                 -> Component
                 -> LocalBuildInfo
                 -> IO [FilePath]
preprocessExtras verbosity comp lbi = case comp of
  CLib _ -> pp $ buildDir lbi
  (CExe Executable { exeName = nm }) -> do
    let nm' = unUnqualComponentName nm
    pp $ buildDir lbi </> nm' </> nm' ++ "-tmp"
  (CFLib ForeignLib { foreignLibName = nm }) -> do
    let nm' = unUnqualComponentName nm
    pp $ buildDir lbi </> nm' </> nm' ++ "-tmp"
  CTest test -> do
    let nm' = unUnqualComponentName $ testName test
    case testInterface test of
      TestSuiteExeV10 _ _ ->
          pp $ buildDir lbi </> nm' </> nm' ++ "-tmp"
      TestSuiteLibV09 _ _ ->
          pp $ buildDir lbi </> stubName test </> stubName test ++ "-tmp"
      TestSuiteUnsupported tt -> die' verbosity $ "No support for preprocessing test "
                                    ++ "suite type " ++ display tt
  CBench bm -> do
    let nm' = unUnqualComponentName $ benchmarkName bm
    case benchmarkInterface bm of
      BenchmarkExeV10 _ _ ->
          pp $ buildDir lbi </> nm' </> nm' ++ "-tmp"
      BenchmarkUnsupported tt ->
          die' verbosity $ "No support for preprocessing benchmark "
                        ++ "type " ++ display tt
  where
    pp :: FilePath -> IO [FilePath]
    pp dir = (map (dir </>) . filter not_sub . concat)
          <$> for knownExtrasHandlers
                (withLexicalCallStack (\f -> f dir))
    
    
    
    
    
    
    
    
    
    not_sub p = and [ not (pre `isPrefixOf` p) | pre <- component_dirs ]
    component_dirs = component_names (localPkgDescr lbi)
    
    component_names pkg_descr = fmap unUnqualComponentName $
        mapMaybe libName (subLibraries pkg_descr) ++
        map exeName (executables pkg_descr) ++
        map testName (testSuites pkg_descr) ++
        map benchmarkName (benchmarks pkg_descr)