1
1
{-# LANGUAGE CPP #-}
2
+ {-# LANGUAGE DataKinds #-}
2
3
{-# LANGUAGE FlexibleContexts #-}
3
4
{-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE RankNTypes #-}
@@ -23,19 +24,20 @@ import Prelude ()
23
24
-- local
24
25
import Distribution.PackageDescription
25
26
import Distribution.Pretty
27
+ import Distribution.Simple.Configure (findDistPrefOrDefault )
26
28
import Distribution.Simple.Errors
27
29
import Distribution.Simple.LocalBuildInfo
28
30
import Distribution.Simple.Program
29
31
import Distribution.Simple.Program.Db
30
32
import Distribution.Simple.Setup.Common
31
33
import Distribution.Simple.Setup.Config
32
34
import Distribution.Simple.Utils
33
- import Distribution.System (buildPlatform )
35
+ import Distribution.System (Platform , buildPlatform )
34
36
import Distribution.Utils.NubList
35
37
import Distribution.Utils.Path
36
- import Distribution.Verbosity
37
38
38
39
-- Base
40
+ import System.Directory (createDirectoryIfMissing , doesFileExist )
39
41
import qualified System.FilePath as FilePath
40
42
#ifdef mingw32_HOST_OS
41
43
import System.FilePath (normalise , splitDrive )
@@ -48,14 +50,25 @@ import qualified Data.List.NonEmpty as NonEmpty
48
50
import qualified Data.Map as Map
49
51
50
52
runConfigureScript
51
- :: Verbosity
52
- -> ConfigFlags
53
- -> LocalBuildInfo
53
+ :: ConfigFlags
54
+ -> FlagAssignment
55
+ -> ProgramDb
56
+ -> Platform
57
+ -- ^ host platform
54
58
-> IO ()
55
- runConfigureScript verbosity flags lbi = do
59
+ runConfigureScript cfg flags programDb hp = do
60
+ let commonCfg = configCommonFlags cfg
61
+ verbosity = fromFlag $ setupVerbosity commonCfg
62
+ dist_dir <- findDistPrefOrDefault $ setupDistPref commonCfg
63
+ let build_dir = dist_dir </> makeRelativePathEx " build"
64
+ mbWorkDir = flagToMaybe $ setupWorkingDir commonCfg
65
+ configureScriptPath = packageRoot commonCfg </> " configure"
66
+ confExists <- doesFileExist configureScriptPath
67
+ unless confExists $
68
+ dieWithException verbosity (ConfigureScriptNotFound configureScriptPath)
69
+ configureFile <-
70
+ makeAbsolute $ configureScriptPath
56
71
env <- getEnvironment
57
- let commonFlags = configCommonFlags flags
58
- programDb = withPrograms lbi
59
72
(ccProg, ccFlags) <- configureCCompiler verbosity programDb
60
73
ccProgShort <- getShortPathName ccProg
61
74
-- The C compiler's compilation and linker flags (e.g.
@@ -64,8 +77,8 @@ runConfigureScript verbosity flags lbi = do
64
77
-- to ccFlags
65
78
-- We don't try and tell configure which ld to use, as we don't have
66
79
-- a way to pass its flags too
67
- configureFile <-
68
- makeAbsolute $ packageRoot commonFlags </> " configure "
80
+
81
+ let configureFile' = toUnix configureFile
69
82
-- autoconf is fussy about filenames, and has a set of forbidden
70
83
-- characters that can't appear in the build directory, etc:
71
84
-- https://www.gnu.org/software/autoconf/manual/autoconf.html#File-System-Conventions
@@ -79,7 +92,6 @@ runConfigureScript verbosity flags lbi = do
79
92
-- TODO: We don't check for colons, tildes or leading dashes. We
80
93
-- also should check the builddir's path, destdir, and all other
81
94
-- paths as well.
82
- let configureFile' = toUnix configureFile
83
95
for_ badAutoconfCharacters $ \ (c, cname) ->
84
96
when (c `elem` FilePath. dropDrive configureFile') $
85
97
warn verbosity $
@@ -111,7 +123,7 @@ runConfigureScript verbosity flags lbi = do
111
123
Map. fromListWith
112
124
(<>)
113
125
[ (flagEnvVar flag, (flag, bool) :| [] )
114
- | (flag, bool) <- unFlagAssignment $ flagAssignment lbi
126
+ | (flag, bool) <- unFlagAssignment flags
115
127
]
116
128
-- A map from env vars to flag names to the single flag we will go with
117
129
cabalFlagMapDeconflicted :: Map String (FlagName , Bool ) <-
@@ -143,10 +155,10 @@ runConfigureScript verbosity flags lbi = do
143
155
]
144
156
++ [
145
157
( " CABAL_FLAGS"
146
- , Just $ unwords [showFlagValue fv | fv <- unFlagAssignment $ flagAssignment lbi ]
158
+ , Just $ unwords [showFlagValue fv | fv <- unFlagAssignment flags ]
147
159
)
148
160
]
149
- let extraPath = fromNubList $ configProgramPathExtra flags
161
+ let extraPath = fromNubList $ configProgramPathExtra cfg
150
162
let cflagsEnv =
151
163
maybe (unwords ccFlags) (++ (" " ++ unwords ccFlags)) $
152
164
lookup " CFLAGS" env
@@ -160,7 +172,6 @@ runConfigureScript verbosity flags lbi = do
160
172
(" CFLAGS" , Just cflagsEnv)
161
173
: [(" PATH" , Just pathEnv) | not (null extraPath)]
162
174
++ cabalFlagEnv
163
- hp = hostPlatform lbi
164
175
maybeHostFlag = if hp == buildPlatform then [] else [" --host=" ++ show (pretty hp)]
165
176
args' = configureFile' : args ++ [" CC=" ++ ccProgShort] ++ maybeHostFlag
166
177
shProg = simpleProgram " sh"
@@ -169,14 +180,16 @@ runConfigureScript verbosity flags lbi = do
169
180
lookupProgram shProg
170
181
`fmap` configureProgram verbosity shProg progDb
171
182
case shConfiguredProg of
172
- Just sh ->
183
+ Just sh -> do
184
+ let build_in = interpretSymbolicPath mbWorkDir build_dir
185
+ createDirectoryIfMissing True build_in
173
186
runProgramInvocation verbosity $
174
187
(programInvocation (sh{programOverrideEnv = overEnv}) args')
175
- { progInvokeCwd = Just (interpretSymbolicPathLBI lbi $ buildDir lbi)
188
+ { progInvokeCwd = Just build_in
176
189
}
177
190
Nothing -> dieWithException verbosity NotFoundMsg
178
191
where
179
- args = configureArgs backwardsCompatHack flags
192
+ args = configureArgs backwardsCompatHack cfg
180
193
backwardsCompatHack = False
181
194
182
195
-- | Convert Windows path to Unix ones
0 commit comments