Skip to content

Commit

Permalink
Return Maybe Platform as part of compiler configure, and place it in …
Browse files Browse the repository at this point in the history
…LocalBuildInfo as hostPlatform.

GHC infers the platform form ghc --info using new 'platformFromTriple' function. Other compilers return Nothing, which triggers fallback to old behavior of using buildPlatform. hostPlatform is then threaded through to initialPathTemplateEnv.
  • Loading branch information
lukexi committed Mar 1, 2013
1 parent 69af83e commit 7a0941c
Show file tree
Hide file tree
Showing 20 changed files with 129 additions and 80 deletions.
3 changes: 2 additions & 1 deletion Cabal/Distribution/Simple/Bench.hs
Expand Up @@ -152,5 +152,6 @@ benchOption pkg_descr lbi bm template =
fromPathTemplate $ substPathTemplate env template fromPathTemplate $ substPathTemplate env template
where where
env = initialPathTemplateEnv env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi) ++ (PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
(LBI.hostPlatform lbi) ++
[(BenchmarkNameVar, toPathTemplate $ PD.benchmarkName bm)] [(BenchmarkNameVar, toPathTemplate $ PD.benchmarkName bm)]
37 changes: 20 additions & 17 deletions Cabal/Distribution/Simple/Configure.hs
Expand Up @@ -115,7 +115,7 @@ import Distribution.Simple.Utils
, withFileContents, writeFileAtomic , withFileContents, writeFileAtomic
, withTempFile ) , withTempFile )
import Distribution.System import Distribution.System
( OS(..), buildOS, Arch(..), buildArch, buildPlatform ) ( OS(..), buildOS, Arch(..), Platform(..), buildPlatform )
import Distribution.Version import Distribution.Version
( Version(..), anyVersion, orLaterVersion, withinRange, isAnyVersion ) ( Version(..), anyVersion, orLaterVersion, withinRange, isAnyVersion )
import Distribution.Verbosity import Distribution.Verbosity
Expand All @@ -137,7 +137,7 @@ import Control.Monad
import Data.List import Data.List
( nub, partition, isPrefixOf, inits ) ( nub, partition, isPrefixOf, inits )
import Data.Maybe import Data.Maybe
( isNothing, catMaybes ) ( isNothing, catMaybes, fromMaybe )
import Data.Monoid import Data.Monoid
( Monoid(..) ) ( Monoid(..) )
import System.Directory import System.Directory
Expand Down Expand Up @@ -287,7 +287,7 @@ configure (pkg_descr0, pbi) cfg
(configPackageDBs cfg) (configPackageDBs cfg)


-- detect compiler -- detect compiler
(comp, programsConfig') <- configCompiler (comp, compPlatform, programsConfig') <- configCompiler
(flagToMaybe $ configHcFlavor cfg) (flagToMaybe $ configHcFlavor cfg)
(flagToMaybe $ configHcPath cfg) (flagToMaybe $ configHcPkg cfg) (flagToMaybe $ configHcPath cfg) (flagToMaybe $ configHcPkg cfg)
programsConfig (lessVerbose verbosity) programsConfig (lessVerbose verbosity)
Expand Down Expand Up @@ -340,7 +340,7 @@ configure (pkg_descr0, pbi) cfg
case finalizePackageDescription case finalizePackageDescription
(configConfigurationsFlags cfg) (configConfigurationsFlags cfg)
dependencySatisfiable dependencySatisfiable
Distribution.System.buildPlatform compPlatform
(compilerId comp) (compilerId comp)
(configConstraints cfg) (configConstraints cfg)
pkg_descr0'' pkg_descr0''
Expand Down Expand Up @@ -492,6 +492,7 @@ configure (pkg_descr0, pbi) cfg
-- did they would go here. -- did they would go here.
installDirTemplates = installDirs, installDirTemplates = installDirs,
compiler = comp, compiler = comp,
hostPlatform = compPlatform,
buildDir = buildDir', buildDir = buildDir',
scratchDir = fromFlagOrDefault scratchDir = fromFlagOrDefault
(distPref </> "scratch") (distPref </> "scratch")
Expand Down Expand Up @@ -792,7 +793,7 @@ ccLdOptionsBuildInfo cflags ldflags =
-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
-- Determining the compiler details -- Determining the compiler details


configCompilerAux :: ConfigFlags -> IO (Compiler, ProgramConfiguration) configCompilerAux :: ConfigFlags -> IO (Compiler, Platform, ProgramConfiguration)
configCompilerAux cfg = configCompiler (flagToMaybe $ configHcFlavor cfg) configCompilerAux cfg = configCompiler (flagToMaybe $ configHcFlavor cfg)
(flagToMaybe $ configHcPath cfg) (flagToMaybe $ configHcPath cfg)
(flagToMaybe $ configHcPkg cfg) (flagToMaybe $ configHcPkg cfg)
Expand All @@ -805,18 +806,19 @@ configCompilerAux cfg = configCompiler (flagToMaybe $ configHcFlavor cfg)


configCompiler :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath configCompiler :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> Verbosity -> ProgramConfiguration -> Verbosity
-> IO (Compiler, ProgramConfiguration) -> IO (Compiler, Platform, ProgramConfiguration)
configCompiler Nothing _ _ _ _ = die "Unknown compiler" configCompiler Nothing _ _ _ _ = die "Unknown compiler"
configCompiler (Just hcFlavor) hcPath hcPkg conf verbosity = do configCompiler (Just hcFlavor) hcPath hcPkg conf verbosity = do
case hcFlavor of (comp, maybePlatform, programsConfig) <- case hcFlavor of
GHC -> GHC.configure verbosity hcPath hcPkg conf GHC -> GHC.configure verbosity hcPath hcPkg conf
JHC -> JHC.configure verbosity hcPath hcPkg conf JHC -> JHC.configure verbosity hcPath hcPkg conf
LHC -> do (_,ghcConf) <- GHC.configure verbosity Nothing hcPkg conf LHC -> do (_, _, ghcConf) <- GHC.configure verbosity Nothing hcPkg conf
LHC.configure verbosity hcPath Nothing ghcConf LHC.configure verbosity hcPath Nothing ghcConf
Hugs -> Hugs.configure verbosity hcPath hcPkg conf Hugs -> Hugs.configure verbosity hcPath hcPkg conf
NHC -> NHC.configure verbosity hcPath hcPkg conf NHC -> NHC.configure verbosity hcPath hcPkg conf
UHC -> UHC.configure verbosity hcPath hcPkg conf UHC -> UHC.configure verbosity hcPath hcPkg conf
_ -> die "Unknown compiler" _ -> die "Unknown compiler"
return (comp, fromMaybe buildPlatform maybePlatform, programsConfig)




-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
Expand Down Expand Up @@ -1030,7 +1032,7 @@ checkForeignDeps pkg lbi verbosity = do
hcDefines comp = hcDefines comp =
case compilerFlavor comp of case compilerFlavor comp of
GHC -> GHC ->
let ghcOS = case buildOS of let ghcOS = case hostOS of
Linux -> ["linux"] Linux -> ["linux"]
Windows -> ["mingw32"] Windows -> ["mingw32"]
OSX -> ["darwin"] OSX -> ["darwin"]
Expand All @@ -1044,7 +1046,7 @@ checkForeignDeps pkg lbi verbosity = do
HaLVM -> [] HaLVM -> []
IOS -> ["ios"] IOS -> ["ios"]
OtherOS _ -> [] OtherOS _ -> []
ghcArch = case buildArch of ghcArch = case hostArch of
I386 -> ["i386"] I386 -> ["i386"]
X86_64 -> ["x86_64"] X86_64 -> ["x86_64"]
PPC -> ["powerpc"] PPC -> ["powerpc"]
Expand All @@ -1069,6 +1071,7 @@ checkForeignDeps pkg lbi verbosity = do
Hugs -> ["-D__HUGS__"] Hugs -> ["-D__HUGS__"]
_ -> [] _ -> []
where where
Platform hostArch hostOS = hostPlatform lbi
version = compilerVersion comp version = compilerVersion comp
-- TODO: move this into the compiler abstraction -- TODO: move this into the compiler abstraction
-- FIXME: this forces GHC's crazy 4.8.2 -> 408 convention on all -- FIXME: this forces GHC's crazy 4.8.2 -> 408 convention on all
Expand Down
9 changes: 7 additions & 2 deletions Cabal/Distribution/Simple/GHC.hs
Expand Up @@ -138,6 +138,7 @@ import System.FilePath ( (</>), (<.>), takeExtension,
import System.IO (hClose, hPutStrLn) import System.IO (hClose, hPutStrLn)
import System.Environment (getEnv) import System.Environment (getEnv)
import Distribution.Compat.Exception (catchExit, catchIO) import Distribution.Compat.Exception (catchExit, catchIO)
import Distribution.System (Platform, buildPlatform, platformFromTriple)


getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)] getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)]
getGhcInfo verbosity ghcProg = getGhcInfo verbosity ghcProg =
Expand All @@ -158,7 +159,7 @@ getGhcInfo verbosity ghcProg =
-- Configuring -- Configuring


configure :: Verbosity -> Maybe FilePath -> Maybe FilePath configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration) -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
configure verbosity hcPath hcPkgPath conf0 = do configure verbosity hcPath hcPkgPath conf0 = do


(ghcProg, ghcVersion, conf1) <- (ghcProg, ghcVersion, conf1) <-
Expand Down Expand Up @@ -196,8 +197,12 @@ configure verbosity hcPath hcPkgPath conf0 = do
compilerLanguages = languages, compilerLanguages = languages,
compilerExtensions = extensions compilerExtensions = extensions
} }
compPlatform = targetPlatform ghcInfo
conf4 = configureToolchain ghcProg ghcInfo conf3 -- configure gcc and ld conf4 = configureToolchain ghcProg ghcInfo conf3 -- configure gcc and ld
return (comp, conf4) return (comp, compPlatform, conf4)

targetPlatform :: [(String, String)] -> Maybe Platform
targetPlatform ghcInfo = platformFromTriple =<< lookup "Target platform" ghcInfo


-- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find -- | Given something like /usr/local/bin/ghc-6.6.1(.exe) we try and find
-- the corresponding tool; e.g. if the tool is ghc-pkg, we try looking -- the corresponding tool; e.g. if the tool is ghc-pkg, we try looking
Expand Down
1 change: 1 addition & 0 deletions Cabal/Distribution/Simple/Haddock.hs
Expand Up @@ -530,6 +530,7 @@ haddockPackageFlags lbi clbi htmlTemplate = do
haddockTemplateEnv :: LocalBuildInfo -> PackageIdentifier -> PathTemplateEnv haddockTemplateEnv :: LocalBuildInfo -> PackageIdentifier -> PathTemplateEnv
haddockTemplateEnv lbi pkg_id = (PrefixVar, prefix (installDirTemplates lbi)) haddockTemplateEnv lbi pkg_id = (PrefixVar, prefix (installDirTemplates lbi))
: initialPathTemplateEnv pkg_id (compilerId (compiler lbi)) : initialPathTemplateEnv pkg_id (compilerId (compiler lbi))
(hostPlatform lbi)


-- -------------------------------------------------------------------------- -- --------------------------------------------------------------------------
-- hscolour support -- hscolour support
Expand Down
6 changes: 4 additions & 2 deletions Cabal/Distribution/Simple/Hugs.hs
Expand Up @@ -118,14 +118,15 @@ import System.Directory
import System.Exit import System.Exit
( ExitCode(ExitSuccess) ) ( ExitCode(ExitSuccess) )
import Distribution.Compat.Exception import Distribution.Compat.Exception
import Distribution.System ( Platform )


import qualified Data.ByteString.Lazy.Char8 as BS.Char8 import qualified Data.ByteString.Lazy.Char8 as BS.Char8


-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
-- Configuring -- Configuring


configure :: Verbosity -> Maybe FilePath -> Maybe FilePath configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration) -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do configure verbosity hcPath _hcPkgPath conf = do


(_ffihugsProg, conf') <- requireProgram verbosity ffihugsProgram (_ffihugsProg, conf') <- requireProgram verbosity ffihugsProgram
Expand All @@ -139,7 +140,8 @@ configure verbosity hcPath _hcPkgPath conf = do
compilerLanguages = hugsLanguages, compilerLanguages = hugsLanguages,
compilerExtensions = hugsLanguageExtensions compilerExtensions = hugsLanguageExtensions
} }
return (comp, conf'') compPlatform = Nothing
return (comp, compPlatform, conf'')


where where
hugsProgram' = hugsProgram { programFindVersion = getVersion } hugsProgram' = hugsProgram { programFindVersion = getVersion }
Expand Down
21 changes: 10 additions & 11 deletions Cabal/Distribution/Simple/InstallDirs.hs
Expand Up @@ -80,7 +80,7 @@ import System.FilePath (dropDrive)
import Distribution.Package import Distribution.Package
( PackageIdentifier, packageName, packageVersion ) ( PackageIdentifier, packageName, packageVersion )
import Distribution.System import Distribution.System
( OS(..), buildOS, Platform(..), buildPlatform ) ( OS(..), buildOS, Platform(..) )
import Distribution.Compiler import Distribution.Compiler
( CompilerId, CompilerFlavor(..) ) ( CompilerId, CompilerFlavor(..) )
import Distribution.Text import Distribution.Text
Expand Down Expand Up @@ -306,18 +306,18 @@ substituteInstallDirTemplates env dirs = dirs'
-- | Convert from abstract install directories to actual absolute ones by -- | Convert from abstract install directories to actual absolute ones by
-- substituting for all the variables in the abstract paths, to get real -- substituting for all the variables in the abstract paths, to get real
-- absolute path. -- absolute path.
absoluteInstallDirs :: PackageIdentifier -> CompilerId -> CopyDest absoluteInstallDirs :: PackageIdentifier -> CompilerId -> CopyDest -> Platform
-> InstallDirs PathTemplate -> InstallDirs PathTemplate
-> InstallDirs FilePath -> InstallDirs FilePath
absoluteInstallDirs pkgId compilerId copydest dirs = absoluteInstallDirs pkgId compilerId copydest platform dirs =
(case copydest of (case copydest of
CopyTo destdir -> fmap ((destdir </>) . dropDrive) CopyTo destdir -> fmap ((destdir </>) . dropDrive)
_ -> id) _ -> id)
. appendSubdirs (</>) . appendSubdirs (</>)
. fmap fromPathTemplate . fmap fromPathTemplate
$ substituteInstallDirTemplates env dirs $ substituteInstallDirTemplates env dirs
where where
env = initialPathTemplateEnv pkgId compilerId env = initialPathTemplateEnv pkgId compilerId platform




-- |The location prefix for the /copy/ command. -- |The location prefix for the /copy/ command.
Expand All @@ -332,10 +332,10 @@ data CopyDest
-- prevents us from making a relocatable package (also known as a \"prefix -- prevents us from making a relocatable package (also known as a \"prefix
-- independent\" package). -- independent\" package).
-- --
prefixRelativeInstallDirs :: PackageIdentifier -> CompilerId prefixRelativeInstallDirs :: PackageIdentifier -> CompilerId -> Platform
-> InstallDirTemplates -> InstallDirTemplates
-> InstallDirs (Maybe FilePath) -> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs pkgId compilerId dirs = prefixRelativeInstallDirs pkgId compilerId platform dirs =
fmap relative fmap relative
. appendSubdirs combinePathTemplate . appendSubdirs combinePathTemplate
$ -- substitute the path template into each other, except that we map $ -- substitute the path template into each other, except that we map
Expand All @@ -345,7 +345,7 @@ prefixRelativeInstallDirs pkgId compilerId dirs =
prefix = PathTemplate [Variable PrefixVar] prefix = PathTemplate [Variable PrefixVar]
} }
where where
env = initialPathTemplateEnv pkgId compilerId env = initialPathTemplateEnv pkgId compilerId platform


-- If it starts with $prefix then it's relative and produce the relative -- If it starts with $prefix then it's relative and produce the relative
-- path by stripping off $prefix/ or $prefix -- path by stripping off $prefix/ or $prefix
Expand Down Expand Up @@ -417,12 +417,11 @@ substPathTemplate environment (PathTemplate template) =
Nothing -> [component] Nothing -> [component]


-- | The initial environment has all the static stuff but no paths -- | The initial environment has all the static stuff but no paths
initialPathTemplateEnv :: PackageIdentifier -> CompilerId -> PathTemplateEnv initialPathTemplateEnv :: PackageIdentifier -> CompilerId -> Platform -> PathTemplateEnv
initialPathTemplateEnv pkgId compilerId = initialPathTemplateEnv pkgId compilerId platform =
packageTemplateEnv pkgId packageTemplateEnv pkgId
++ compilerTemplateEnv compilerId ++ compilerTemplateEnv compilerId
++ platformTemplateEnv buildPlatform -- platform should be param if we want ++ platformTemplateEnv platform
-- to do cross-platform configuation


packageTemplateEnv :: PackageIdentifier -> PathTemplateEnv packageTemplateEnv :: PackageIdentifier -> PathTemplateEnv
packageTemplateEnv pkgId = packageTemplateEnv pkgId =
Expand Down
6 changes: 4 additions & 2 deletions Cabal/Distribution/Simple/JHC.hs
Expand Up @@ -84,6 +84,7 @@ import Distribution.Text
( Text(parse), display ) ( Text(parse), display )
import Distribution.Compat.ReadP import Distribution.Compat.ReadP
( readP_to_S, string, skipSpaces ) ( readP_to_S, string, skipSpaces )
import Distribution.System ( Platform )


import Data.List ( nub ) import Data.List ( nub )
import Data.Char ( isSpace ) import Data.Char ( isSpace )
Expand All @@ -96,7 +97,7 @@ import qualified Data.ByteString.Lazy.Char8 as BS.Char8
-- Configuring -- Configuring


configure :: Verbosity -> Maybe FilePath -> Maybe FilePath configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration) -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do configure verbosity hcPath _hcPkgPath conf = do


(jhcProg, _, conf') <- requireProgramVersion verbosity (jhcProg, _, conf') <- requireProgramVersion verbosity
Expand All @@ -109,7 +110,8 @@ configure verbosity hcPath _hcPkgPath conf = do
compilerLanguages = jhcLanguages, compilerLanguages = jhcLanguages,
compilerExtensions = jhcLanguageExtensions compilerExtensions = jhcLanguageExtensions
} }
return (comp, conf') compPlatform = Nothing
return (comp, compPlatform, conf')


jhcLanguages :: [(Language, Flag)] jhcLanguages :: [(Language, Flag)]
jhcLanguages = [(Haskell98, "")] jhcLanguages = [(Haskell98, "")]
Expand Down
6 changes: 4 additions & 2 deletions Cabal/Distribution/Simple/LHC.hs
Expand Up @@ -123,12 +123,13 @@ import System.FilePath ( (</>), (<.>), takeExtension,
takeDirectory, replaceExtension ) takeDirectory, replaceExtension )
import System.IO (hClose, hPutStrLn) import System.IO (hClose, hPutStrLn)
import Distribution.Compat.Exception (catchExit, catchIO) import Distribution.Compat.Exception (catchExit, catchIO)
import Distribution.System ( Platform )


-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
-- Configuring -- Configuring


configure :: Verbosity -> Maybe FilePath -> Maybe FilePath configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration) -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
configure verbosity hcPath hcPkgPath conf = do configure verbosity hcPath hcPkgPath conf = do


(lhcProg, lhcVersion, conf') <- (lhcProg, lhcVersion, conf') <-
Expand All @@ -155,7 +156,8 @@ configure verbosity hcPath hcPkgPath conf = do
compilerExtensions = extensions compilerExtensions = extensions
} }
conf''' = configureToolchain lhcProg conf'' -- configure gcc and ld conf''' = configureToolchain lhcProg conf'' -- configure gcc and ld
return (comp, conf''') compPlatform = Nothing
return (comp, compPlatform, conf''')


-- | Adjust the way we find and configure gcc and ld -- | Adjust the way we find and configure gcc and ld
-- --
Expand Down
8 changes: 7 additions & 1 deletion Cabal/Distribution/Simple/LocalBuildInfo.hs
Expand Up @@ -102,7 +102,8 @@ import Distribution.Simple.Setup
( ConfigFlags ) ( ConfigFlags )
import Distribution.Text import Distribution.Text
( display ) ( display )

import Distribution.System
( Platform )
import Data.List (nub, find) import Data.List (nub, find)
import Data.Graph import Data.Graph
import Data.Tree (flatten) import Data.Tree (flatten)
Expand All @@ -124,6 +125,8 @@ data LocalBuildInfo = LocalBuildInfo {
--TODO: inplaceDirTemplates :: InstallDirs FilePath --TODO: inplaceDirTemplates :: InstallDirs FilePath
compiler :: Compiler, compiler :: Compiler,
-- ^ The compiler we're building with -- ^ The compiler we're building with
hostPlatform :: Platform,
-- ^ The platform we're building for
buildDir :: FilePath, buildDir :: FilePath,
-- ^ Where to build the package. -- ^ Where to build the package.
--TODO: eliminate hugs's scratchDir, use builddir --TODO: eliminate hugs's scratchDir, use builddir
Expand Down Expand Up @@ -400,6 +403,7 @@ absoluteInstallDirs pkg lbi copydest =
(packageId pkg) (packageId pkg)
(compilerId (compiler lbi)) (compilerId (compiler lbi))
copydest copydest
(hostPlatform lbi)
(installDirTemplates lbi) (installDirTemplates lbi)


-- |See 'InstallDirs.prefixRelativeInstallDirs' -- |See 'InstallDirs.prefixRelativeInstallDirs'
Expand All @@ -409,6 +413,7 @@ prefixRelativeInstallDirs pkg_descr lbi =
InstallDirs.prefixRelativeInstallDirs InstallDirs.prefixRelativeInstallDirs
(packageId pkg_descr) (packageId pkg_descr)
(compilerId (compiler lbi)) (compilerId (compiler lbi))
(hostPlatform lbi)
(installDirTemplates lbi) (installDirTemplates lbi)


substPathTemplate :: PackageId -> LocalBuildInfo substPathTemplate :: PackageId -> LocalBuildInfo
Expand All @@ -418,3 +423,4 @@ substPathTemplate pkgid lbi = fromPathTemplate
where env = initialPathTemplateEnv where env = initialPathTemplateEnv
pkgid pkgid
(compilerId (compiler lbi)) (compilerId (compiler lbi))
(hostPlatform lbi)
6 changes: 4 additions & 2 deletions Cabal/Distribution/Simple/NHC.hs
Expand Up @@ -104,12 +104,13 @@ import Data.Maybe ( catMaybes )
import Data.Monoid ( Monoid(..) ) import Data.Monoid ( Monoid(..) )
import Control.Monad ( when, unless ) import Control.Monad ( when, unless )
import Distribution.Compat.Exception import Distribution.Compat.Exception
import Distribution.System ( Platform )


-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
-- Configuring -- Configuring


configure :: Verbosity -> Maybe FilePath -> Maybe FilePath configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration) -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do configure verbosity hcPath _hcPkgPath conf = do


(_nhcProg, nhcVersion, conf') <- (_nhcProg, nhcVersion, conf') <-
Expand All @@ -134,7 +135,8 @@ configure verbosity hcPath _hcPkgPath conf = do
compilerLanguages = nhcLanguages, compilerLanguages = nhcLanguages,
compilerExtensions = nhcLanguageExtensions compilerExtensions = nhcLanguageExtensions
} }
return (comp, conf'''') compPlatform = Nothing
return (comp, compPlatform, conf'''')


nhcLanguages :: [(Language, Flag)] nhcLanguages :: [(Language, Flag)]
nhcLanguages = [(Haskell98, "-98")] nhcLanguages = [(Haskell98, "-98")]
Expand Down
5 changes: 4 additions & 1 deletion Cabal/Distribution/Simple/Test.hs
Expand Up @@ -430,6 +430,7 @@ testSuiteLogPath template pkg_descr lbi testLog =
where where
env = initialPathTemplateEnv env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi) (PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
(LBI.hostPlatform lbi)
++ [ (TestSuiteNameVar, toPathTemplate $ testSuiteName testLog) ++ [ (TestSuiteNameVar, toPathTemplate $ testSuiteName testLog)
, (TestSuiteResultVar, result) , (TestSuiteResultVar, result)
] ]
Expand All @@ -446,7 +447,8 @@ testOption pkg_descr lbi suite template =
fromPathTemplate $ substPathTemplate env template fromPathTemplate $ substPathTemplate env template
where where
env = initialPathTemplateEnv env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi) ++ (PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
(LBI.hostPlatform lbi) ++
[(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)]


packageLogPath :: PathTemplate packageLogPath :: PathTemplate
Expand All @@ -458,6 +460,7 @@ packageLogPath template pkg_descr lbi =
where where
env = initialPathTemplateEnv env = initialPathTemplateEnv
(PD.package pkg_descr) (compilerId $ LBI.compiler lbi) (PD.package pkg_descr) (compilerId $ LBI.compiler lbi)
(LBI.hostPlatform lbi)


-- | The filename of the source file for the stub executable associated with a -- | The filename of the source file for the stub executable associated with a
-- library 'TestSuite'. -- library 'TestSuite'.
Expand Down

0 comments on commit 7a0941c

Please sign in to comment.