2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE LambdaCase #-}
4 {-# LANGUAGE RankNTypes #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 -----------------------------------------------------------------------------
7 {-# OPTIONS_GHC -fno-warn-deprecations #-}
10 -- Module : Distribution.Simple.ConfigureScript
11 -- Copyright : Isaac Jones 2003-2005
14 -- Maintainer : cabal-devel@haskell.org
15 -- Portability : portable
16 module Distribution
.Simple
.ConfigureScript
20 import Distribution
.Compat
.Prelude
24 import Distribution
.PackageDescription
25 import Distribution
.Pretty
26 import Distribution
.Simple
.Errors
27 import Distribution
.Simple
.LocalBuildInfo
28 import Distribution
.Simple
.Program
29 import Distribution
.Simple
.Program
.Db
30 import Distribution
.Simple
.Setup
.Common
31 import Distribution
.Simple
.Setup
.Config
32 import Distribution
.Simple
.Utils
33 import Distribution
.System
(buildPlatform
)
34 import Distribution
.Utils
.NubList
35 import Distribution
.Verbosity
38 import System
.FilePath
45 #ifdef mingw32_HOST_OS
46 import System
.FilePath (normalise
, splitDrive
)
48 import Distribution
.Compat
.Directory
(makeAbsolute
)
49 import Distribution
.Compat
.Environment
(getEnvironment
)
50 import Distribution
.Compat
.GetShortPathName
(getShortPathName
)
52 import qualified Data
.List
.NonEmpty
as NonEmpty
53 import qualified Data
.Map
as Map
60 runConfigureScript verbosity flags lbi
= do
62 let programDb
= withPrograms lbi
63 (ccProg
, ccFlags
) <- configureCCompiler verbosity programDb
64 ccProgShort
<- getShortPathName ccProg
65 -- The C compiler's compilation and linker flags (e.g.
66 -- "C compiler flags" and "Gcc Linker flags" from GHC) have already
67 -- been merged into ccFlags, so we set both CFLAGS and LDFLAGS
69 -- We don't try and tell configure which ld to use, as we don't have
70 -- a way to pass its flags too
73 fromMaybe "." (takeDirectory
<$> cabalFilePath lbi
) </> "configure"
74 -- autoconf is fussy about filenames, and has a set of forbidden
75 -- characters that can't appear in the build directory, etc:
76 -- https://www.gnu.org/software/autoconf/manual/autoconf.html#File-System-Conventions
78 -- This has caused hard-to-debug failures in the past (#5368), so we
79 -- detect some cases early and warn with a clear message. Windows's
80 -- use of backslashes is problematic here, so we'll switch to
81 -- slashes, but we do still want to fail on backslashes in POSIX
84 -- TODO: We don't check for colons, tildes or leading dashes. We
85 -- also should check the builddir's path, destdir, and all other
87 let configureFile
' = toUnix configureFile
88 for_ badAutoconfCharacters
$ \(c
, cname
) ->
89 when (c `
elem` dropDrive configureFile
') $
92 [ "The path to the './configure' script, '"
94 , "', contains the character '"
99 , " This may cause the script to fail with an obscure error, or for"
100 , " building the package to fail later."
104 -- Convert a flag name to name of environment variable to represent its
105 -- value for the configure script.
106 flagEnvVar
:: FlagName
-> String
107 flagEnvVar flag
= "CABAL_FLAG_" ++ map f
(unFlagName flag
)
112 -- A map from such env vars to every flag name and value where the name
113 -- name maps to that that env var.
114 cabalFlagMap
:: Map
String (NonEmpty
(FlagName
, Bool))
118 [ (flagEnvVar flag
, (flag
, bool
) :|
[])
119 |
(flag
, bool
) <- unFlagAssignment
$ flagAssignment lbi
121 -- A map from env vars to flag names to the single flag we will go with
122 cabalFlagMapDeconflicted
:: Map
String (FlagName
, Bool) <-
123 flip Map
.traverseWithKey cabalFlagMap
$ \envVar
-> \case
124 -- No conflict: no problem
125 singleFlag
:|
[] -> pure singleFlag
126 -- Conflict: warn and discard all but first
127 collidingFlags
@(firstFlag
:| _
: _
) -> do
128 let quote s
= "'" ++ s
++ "'"
129 toName
= quote
. unFlagName
. fst
130 renderedList
= intercalate
", " $ NonEmpty
.toList
$ toName
<$> collidingFlags
135 , "all map to the same environment variable"
137 , "causing a collision."
138 , "The value first flag"
146 |
(envVar
, (_
, bool
)) <- Map
.toList cabalFlagMapDeconflicted
147 , let val
= if bool
then "1" else "0"
151 , Just
$ unwords [showFlagValue fv | fv
<- unFlagAssignment
$ flagAssignment lbi
]
154 let extraPath
= fromNubList
$ configProgramPathExtra flags
156 maybe (unwords ccFlags
) (++ (" " ++ unwords ccFlags
)) $
158 spSep
= [searchPathSeparator
]
161 (intercalate spSep extraPath
)
162 ((intercalate spSep extraPath
++ spSep
) ++)
165 ("CFLAGS", Just cflagsEnv
)
166 : [("PATH", Just pathEnv
) |
not (null extraPath
)]
168 hp
= hostPlatform lbi
169 maybeHostFlag
= if hp
== buildPlatform
then [] else ["--host=" ++ show (pretty hp
)]
170 args
' = configureFile
' : args
++ ["CC=" ++ ccProgShort
] ++ maybeHostFlag
171 shProg
= simpleProgram
"sh"
173 modifyProgramSearchPath
174 (\p
-> map ProgramSearchPathDir extraPath
++ p
)
178 `
fmap` configureProgram verbosity shProg progDb
179 case shConfiguredProg
of
181 runProgramInvocation verbosity
$
182 (programInvocation
(sh
{programOverrideEnv
= overEnv
}) args
')
183 { progInvokeCwd
= Just
(buildDir lbi
)
185 Nothing
-> dieWithException verbosity NotFoundMsg
187 args
= configureArgs backwardsCompatHack flags
188 backwardsCompatHack
= False
190 -- | Convert Windows path to Unix ones
191 toUnix
:: String -> String
192 #ifdef mingw32_HOST_OS
193 toUnix s
= let tmp
= normalise s
194 (l
, rest
) = case splitDrive tmp
of
196 (h
:_
, x
) -> ('/':h
:"/", x
)
197 parts
= splitDirectories rest
198 in l
++ intercalate
"/" parts
200 toUnix s
= intercalate
"/" $ splitDirectories s
203 badAutoconfCharacters
:: [(Char, String)]
204 badAutoconfCharacters
=
209 , ('"', "double quote
")
211 , ('$', "dollar sign
")
213 , ('\'', "single quote
")
214 , ('(', "left
bracket")
215 , (')', "right
bracket")
218 , ('<', "less
-than sign
")
219 , ('=', "equals sign
")
220 , ('>', "greater
-than sign
")
221 , ('?', "question mark
")
222 , ('[', "left square
bracket")
223 , ('\\', "backslash
")