Skip to content

Commit 7d6219f

Browse files
authored
Merge pull request #10256 from mpickering/wip/working-dir-path-mp
Collection of patches to do with --working-dir
2 parents 1e93e57 + addcd41 commit 7d6219f

File tree

72 files changed

+567
-432
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

72 files changed

+567
-432
lines changed

Cabal-QuickCheck/src/Test/QuickCheck/Instances/Cabal.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE TypeOperators #-}
3+
{-# LANGUAGE FlexibleInstances #-}
34
{-# OPTIONS_GHC -fno-warn-orphans #-}
45
module Test.QuickCheck.Instances.Cabal () where
56

@@ -18,7 +19,7 @@ import Distribution.Compat.NonEmptySet (NonEmptySet)
1819
import Distribution.Compiler
1920
import Distribution.FieldGrammar.Newtypes
2021
import Distribution.ModuleName
21-
import Distribution.Simple.Compiler (DebugInfoLevel (..), OptimisationLevel (..), PackageDB (..), ProfDetailLevel (..), knownProfDetailLevels)
22+
import Distribution.Simple.Compiler
2223
import Distribution.Simple.Flag (Flag (..))
2324
import Distribution.Simple.InstallDirs
2425
import Distribution.Simple.Setup (HaddockTarget (..), TestShowDetails (..), DumpBuildInfo)
@@ -476,7 +477,7 @@ instance Arbitrary TestShowDetails where
476477
-- PackageDB
477478
-------------------------------------------------------------------------------
478479

479-
instance Arbitrary PackageDB where
480+
instance Arbitrary (PackageDBX FilePath) where
480481
arbitrary = oneof [ pure GlobalPackageDB
481482
, pure UserPackageDB
482483
, SpecificPackageDB <$> arbitraryShortPath

Cabal-syntax/src/Distribution/Utils/Path.hs

Lines changed: 43 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -30,14 +30,17 @@ module Distribution.Utils.Path
3030
, Tix
3131
, Tmp
3232
, Response
33+
, PkgConf
3334

3435
-- * Symbolic paths
3536
, RelativePath
3637
, SymbolicPath
38+
, AbsolutePath (..)
3739
, SymbolicPathX -- NB: constructor not exposed, to retain type safety.
3840

3941
-- ** Symbolic path API
4042
, getSymbolicPath
43+
, getAbsolutePath
4144
, sameDirectory
4245
, makeRelativePathEx
4346
, makeSymbolicPath
@@ -47,6 +50,7 @@ module Distribution.Utils.Path
4750
, relativeSymbolicPath
4851
, symbolicPathRelative_maybe
4952
, interpretSymbolicPath
53+
, interpretSymbolicPathAbsolute
5054

5155
-- ** General filepath API
5256
, (</>)
@@ -59,7 +63,7 @@ module Distribution.Utils.Path
5963
-- ** Working directory handling
6064
, interpretSymbolicPathCWD
6165
, absoluteWorkingDir
62-
, tryMakeRelativeToWorkingDir
66+
, tryMakeRelative
6367

6468
-- ** Module names
6569
, moduleNameSymbolicPath
@@ -214,6 +218,11 @@ type RelativePath = SymbolicPathX 'OnlyRelative
214218
-- until we interpret them (using e.g. 'interpretSymbolicPath').
215219
type SymbolicPath = SymbolicPathX 'AllowAbsolute
216220

221+
newtype AbsolutePath (to :: FileOrDir) = AbsolutePath (forall from. SymbolicPath from to)
222+
223+
unsafeMakeAbsolutePath :: FilePath -> AbsolutePath to
224+
unsafeMakeAbsolutePath fp = AbsolutePath (makeSymbolicPath fp)
225+
217226
instance Binary (SymbolicPathX allowAbsolute from to)
218227
instance
219228
(Typeable allowAbsolute, Typeable from, Typeable to)
@@ -289,7 +298,7 @@ moduleNameSymbolicPath modNm = SymbolicPath $ ModuleName.toFilePath modNm
289298
-- (because the program might expect certain paths to be relative).
290299
--
291300
-- See Note [Symbolic paths] in Distribution.Utils.Path.
292-
interpretSymbolicPath :: Maybe (SymbolicPath CWD (Dir Pkg)) -> SymbolicPathX allowAbsolute Pkg to -> FilePath
301+
interpretSymbolicPath :: Maybe (SymbolicPath CWD (Dir from)) -> SymbolicPathX allowAbsolute from to -> FilePath
293302
interpretSymbolicPath mbWorkDir (SymbolicPath p) =
294303
-- Note that this properly handles an absolute symbolic path,
295304
-- because if @q@ is absolute, then @p </> q = q@.
@@ -316,9 +325,15 @@ interpretSymbolicPath mbWorkDir (SymbolicPath p) =
316325
-- appropriate to use 'interpretSymbolicPathCWD' to provide its arguments.
317326
--
318327
-- See Note [Symbolic paths] in Distribution.Utils.Path.
319-
interpretSymbolicPathCWD :: SymbolicPathX allowAbsolute Pkg to -> FilePath
328+
interpretSymbolicPathCWD :: SymbolicPathX allowAbsolute from to -> FilePath
320329
interpretSymbolicPathCWD (SymbolicPath p) = p
321330

331+
getAbsolutePath :: AbsolutePath to -> FilePath
332+
getAbsolutePath (AbsolutePath p) = getSymbolicPath p
333+
334+
interpretSymbolicPathAbsolute :: AbsolutePath (Dir Pkg) -> SymbolicPathX allowAbsolute Pkg to -> FilePath
335+
interpretSymbolicPathAbsolute (AbsolutePath p) sym = interpretSymbolicPath (Just p) sym
336+
322337
-- | Change what a symbolic path is pointing to.
323338
coerceSymbolicPath :: SymbolicPathX allowAbsolute from to1 -> SymbolicPathX allowAbsolute from to2
324339
coerceSymbolicPath = coerce
@@ -342,17 +357,19 @@ symbolicPathRelative_maybe (SymbolicPath fp) =
342357
else Just $ SymbolicPath fp
343358

344359
-- | Absolute path to the current working directory.
345-
absoluteWorkingDir :: Maybe (SymbolicPath CWD to) -> IO FilePath
346-
absoluteWorkingDir Nothing = Directory.getCurrentDirectory
347-
absoluteWorkingDir (Just wd) = Directory.makeAbsolute $ getSymbolicPath wd
360+
absoluteWorkingDir :: Maybe (SymbolicPath CWD to) -> IO (AbsolutePath to)
361+
absoluteWorkingDir Nothing = unsafeMakeAbsolutePath <$> Directory.getCurrentDirectory
362+
absoluteWorkingDir (Just wd) = unsafeMakeAbsolutePath <$> Directory.makeAbsolute (getSymbolicPath wd)
348363

349-
-- | Try to make a path relative to the current working directory.
364+
-- | Try to make a symbolic path relative.
365+
--
366+
-- This function does nothing if the path is already relative.
350367
--
351368
-- NB: this function may fail to make the path relative.
352-
tryMakeRelativeToWorkingDir :: Maybe (SymbolicPath CWD (Dir dir)) -> SymbolicPath dir to -> IO (SymbolicPath dir to)
353-
tryMakeRelativeToWorkingDir mbWorkDir (SymbolicPath fp) = do
354-
wd <- absoluteWorkingDir mbWorkDir
355-
return $ SymbolicPath (FilePath.makeRelative wd fp)
369+
tryMakeRelative :: Maybe (SymbolicPath CWD (Dir dir)) -> SymbolicPath dir to -> IO (SymbolicPath dir to)
370+
tryMakeRelative mbWorkDir (SymbolicPath fp) = do
371+
AbsolutePath wd <- absoluteWorkingDir mbWorkDir
372+
return $ SymbolicPath (FilePath.makeRelative (getSymbolicPath wd) fp)
356373

357374
-------------------------------------------------------------------------------
358375

@@ -422,6 +439,16 @@ instance
422439
where
423440
SymbolicPath p1 </> SymbolicPath p2 = SymbolicPath (p1 </> p2)
424441

442+
instance
443+
(b1 ~ 'Dir b2, c2 ~ c3, midAbsolute ~ OnlyRelative)
444+
=> PathLike
445+
(AbsolutePath b1)
446+
(SymbolicPathX midAbsolute b2 c2)
447+
(AbsolutePath c3)
448+
where
449+
AbsolutePath (SymbolicPath p1) </> SymbolicPath p2 =
450+
unsafeMakeAbsolutePath (p1 </> p2)
451+
425452
--------------------------------------------------------------------------------
426453
-- Abstract directory locations.
427454

@@ -499,3 +526,8 @@ data Tmp
499526
--
500527
-- See Note [Symbolic paths] in Distribution.Utils.Path.
501528
data Response
529+
530+
-- | Abstract directory: directory for pkg-config files.
531+
--
532+
-- See Note [Symbolic paths] in Distribution.Utils.Path.
533+
data PkgConf

Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,4 +34,4 @@ md5CheckGenericPackageDescription proxy = md5Check proxy
3434

3535
md5CheckLocalBuildInfo :: Proxy LocalBuildInfo -> Assertion
3636
md5CheckLocalBuildInfo proxy = md5Check proxy
37-
0x2c8550e1552f68bf169fafbfcd8f845a
37+
0x94827844fdb1afedee525061749fb16f

Cabal-tests/tests/custom-setup/CabalDoctestSetup.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ import Distribution.Simple
103103
(UserHooks (..), autoconfUserHooks, defaultMainWithHooks,
104104
simpleUserHooks)
105105
import Distribution.Simple.Compiler
106-
(CompilerFlavor (GHC), CompilerId (..), PackageDB (..), compilerId)
106+
(CompilerFlavor (GHC), CompilerId (..), PackageDB, PackageDBX (..), compilerId)
107107
import Distribution.Simple.LocalBuildInfo
108108
(ComponentLocalBuildInfo (componentPackageDeps), LocalBuildInfo,
109109
compiler, withExeLBI, withLibLBI, withPackageDB, withTestLBI
@@ -119,8 +119,6 @@ import Distribution.Simple.Utils
119119
import Distribution.Text
120120
(display)
121121
import Distribution.Verbosity
122-
import System.FilePath
123-
((</>))
124122

125123
import qualified Data.Foldable as F
126124
(for_)
@@ -160,7 +158,9 @@ import Distribution.Package
160158
import Distribution.Utils.Path
161159
( SymbolicPathX
162160
, makeSymbolicPath
163-
, makeRelativePathEx )
161+
, makeRelativePathEx
162+
, interpretSymbolicPathCWD
163+
, (</>))
164164
import qualified Distribution.Utils.Path as Cabal
165165
(getSymbolicPath)
166166
import Distribution.Simple.Utils
@@ -336,7 +336,7 @@ generateBuildModule testSuiteName flags pkg lbi = do
336336
let distPref = fromFlag (buildDistPref flags)
337337

338338
-- Package DBs & environments
339-
let dbStack = withPackageDB lbi ++ [ SpecificPackageDB $ toFilePath distPref </> "package.conf.inplace" ]
339+
let dbStack = withPackageDB lbi ++ [ SpecificPackageDB $ distPref </> makeRelativePathEx "package.conf.inplace" ]
340340
let dbFlags = "-hide-all-packages" : packageDbArgs dbStack
341341
let envFlags
342342
| ghcCanBeToldToIgnorePkgEnvs = [ "-package-env=-" ]
@@ -539,7 +539,7 @@ generateBuildModule testSuiteName flags pkg lbi = do
539539
: concatMap specific dbs
540540
_ -> ierror
541541
where
542-
specific (SpecificPackageDB db) = [ "-package-conf=" ++ db ]
542+
specific (SpecificPackageDB db) = [ "-package-conf=" ++ interpretSymbolicPathCWD db ]
543543
specific _ = ierror
544544
ierror = error $ "internal error: unexpected package db stack: "
545545
++ show dbstack
@@ -557,7 +557,7 @@ generateBuildModule testSuiteName flags pkg lbi = do
557557
dbs -> "-clear-package-db"
558558
: concatMap single dbs
559559
where
560-
single (SpecificPackageDB db) = [ "-package-db=" ++ db ]
560+
single (SpecificPackageDB db) = [ "-package-db=" ++ interpretSymbolicPathCWD db ]
561561
single GlobalPackageDB = [ "-global-package-db" ]
562562
single UserPackageDB = [ "-user-package-db" ]
563563
isSpecific (SpecificPackageDB _) = True

Cabal/src/Distribution/PackageDescription/Check/Warning.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ import Distribution.Types.PackageName (PackageName)
4747
import Distribution.Types.TestType (TestType, knownTestTypes)
4848
import Distribution.Types.UnqualComponentName
4949
import Distribution.Types.Version (Version)
50-
import Distribution.Utils.Path
50+
import Distribution.Utils.Path (FileOrDir (..), Pkg, RelativePath, getSymbolicPath)
5151
import Language.Haskell.Extension (Extension)
5252

5353
import qualified Data.Either as Either

Cabal/src/Distribution/Simple.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -550,7 +550,7 @@ cleanAction globalFlags hooks flags args = do
550550
flags' =
551551
flags{cleanCommonFlags = common'}
552552

553-
mbWorkDirFlag = cleanWorkingDir flags
553+
mbWorkDirFlag = cleanWorkingDir flags'
554554
mbWorkDir = flagToMaybe mbWorkDirFlag
555555

556556
pbi <- preClean hooks args flags'

Cabal/src/Distribution/Simple/Build.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -275,7 +275,6 @@ dumpBuildInfo
275275
-- ^ Flags that the user passed to build
276276
-> IO ()
277277
dumpBuildInfo verbosity distPref dumpBuildInfoFlag pkg_descr lbi flags = do
278-
let mbWorkDir = flagToMaybe $ buildWorkingDir flags
279278
when shouldDumpBuildInfo $ do
280279
-- Changing this line might break consumers of the dumped build info.
281280
-- Announce changes on mailing lists!
@@ -289,13 +288,12 @@ dumpBuildInfo verbosity distPref dumpBuildInfoFlag pkg_descr lbi flags = do
289288
activeTargets
290289
)
291290

292-
wdir <- absoluteWorkingDir mbWorkDir
293-
294291
(compilerProg, _) <- case flavorToProgram (compilerFlavor (compiler lbi)) of
295292
Nothing ->
296293
dieWithException verbosity $ UnknownCompilerFlavor (compilerFlavor (compiler lbi))
297294
Just program -> requireProgram verbosity program (withPrograms lbi)
298295

296+
wdir <- absoluteWorkingDirLBI lbi
299297
let (warns, json) = mkBuildInfo wdir pkg_descr lbi flags (compilerProg, compiler lbi) activeTargets
300298
buildInfoText = renderJson json
301299
unless (null warns) $
@@ -791,7 +789,7 @@ testSuiteLibV09AsLibAndExe
791789
-> TestSuite
792790
-> ComponentLocalBuildInfo
793791
-> LocalBuildInfo
794-
-> FilePath
792+
-> AbsolutePath (Dir Pkg)
795793
-- ^ absolute inplace dir
796794
-> SymbolicPath Pkg (Dir Dist)
797795
-> ( PackageDescription
@@ -911,7 +909,7 @@ createInternalPackageDB verbosity lbi distPref = do
911909
existsAlready <- doesPackageDBExist dbPath
912910
when existsAlready $ deletePackageDB dbPath
913911
createPackageDB verbosity (compiler lbi) (withPrograms lbi) False dbPath
914-
return (SpecificPackageDB dbPath)
912+
return (SpecificPackageDB dbRelPath)
915913
where
916914
dbRelPath = internalPackageDBPath lbi distPref
917915
dbPath = interpretSymbolicPathLBI lbi dbRelPath

Cabal/src/Distribution/Simple/Compiler.hs

Lines changed: 56 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,9 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE DeriveDataTypeable #-}
3+
{-# LANGUAGE DeriveFoldable #-}
4+
{-# LANGUAGE DeriveFunctor #-}
35
{-# LANGUAGE DeriveGeneric #-}
6+
{-# LANGUAGE DeriveTraversable #-}
47

58
-----------------------------------------------------------------------------
69

@@ -35,11 +38,21 @@ module Distribution.Simple.Compiler
3538
, compilerInfo
3639

3740
-- * Support for package databases
38-
, PackageDB (..)
41+
, PackageDB
3942
, PackageDBStack
43+
, PackageDBCWD
44+
, PackageDBStackCWD
45+
, PackageDBX (..)
46+
, PackageDBStackX
47+
, PackageDBS
48+
, PackageDBStackS
4049
, registrationPackageDB
4150
, absolutePackageDBPaths
4251
, absolutePackageDBPath
52+
, interpretPackageDB
53+
, interpretPackageDBStack
54+
, coercePackageDB
55+
, coercePackageDBStack
4356

4457
-- * Support for optimisation levels
4558
, OptimisationLevel (..)
@@ -95,7 +108,6 @@ import Language.Haskell.Extension
95108

96109
import qualified Data.Map as Map (lookup)
97110
import System.Directory (canonicalizePath)
98-
import System.FilePath (isRelative)
99111

100112
data Compiler = Compiler
101113
{ compilerId :: CompilerId
@@ -181,15 +193,17 @@ compilerInfo c =
181193
-- the file system. This can be used to build isolated environments of
182194
-- packages, for example to build a collection of related packages
183195
-- without installing them globally.
184-
data PackageDB
196+
--
197+
-- Abstracted over
198+
data PackageDBX fp
185199
= GlobalPackageDB
186200
| UserPackageDB
187201
| -- | NB: the path might be relative or it might be absolute
188-
SpecificPackageDB FilePath
189-
deriving (Eq, Generic, Ord, Show, Read, Typeable)
202+
SpecificPackageDB fp
203+
deriving (Eq, Generic, Ord, Show, Read, Typeable, Functor, Foldable, Traversable)
190204

191-
instance Binary PackageDB
192-
instance Structured PackageDB
205+
instance Binary fp => Binary (PackageDBX fp)
206+
instance Structured fp => Structured (PackageDBX fp)
193207

194208
-- | We typically get packages from several databases, and stack them
195209
-- together. This type lets us be explicit about that stacking. For example
@@ -206,11 +220,20 @@ instance Structured PackageDB
206220
-- we can use several custom package dbs and the user package db together.
207221
--
208222
-- When it comes to writing, the top most (last) package is used.
209-
type PackageDBStack = [PackageDB]
223+
type PackageDBStackX from = [PackageDBX from]
224+
225+
type PackageDB = PackageDBX (SymbolicPath Pkg (Dir PkgDB))
226+
type PackageDBStack = PackageDBStackX (SymbolicPath Pkg (Dir PkgDB))
227+
228+
type PackageDBS from = PackageDBX (SymbolicPath from (Dir PkgDB))
229+
type PackageDBStackS from = PackageDBStackX (SymbolicPath from (Dir PkgDB))
230+
231+
type PackageDBCWD = PackageDBX FilePath
232+
type PackageDBStackCWD = PackageDBStackX FilePath
210233

211234
-- | Return the package that we should register into. This is the package db at
212235
-- the top of the stack.
213-
registrationPackageDB :: PackageDBStack -> PackageDB
236+
registrationPackageDB :: PackageDBStackX from -> PackageDBX from
214237
registrationPackageDB dbs = case safeLast dbs of
215238
Nothing -> error "internal error: empty package db set"
216239
Just p -> p
@@ -230,10 +253,30 @@ absolutePackageDBPath _ GlobalPackageDB = return GlobalPackageDB
230253
absolutePackageDBPath _ UserPackageDB = return UserPackageDB
231254
absolutePackageDBPath mbWorkDir (SpecificPackageDB db) = do
232255
let db' =
233-
if isRelative db
234-
then interpretSymbolicPath mbWorkDir (makeRelativePathEx db)
235-
else db
236-
SpecificPackageDB <$> canonicalizePath db'
256+
case symbolicPathRelative_maybe db of
257+
Nothing -> getSymbolicPath db
258+
Just rel_path -> interpretSymbolicPath mbWorkDir rel_path
259+
SpecificPackageDB . makeSymbolicPath <$> canonicalizePath db'
260+
261+
interpretPackageDB :: Maybe (SymbolicPath CWD (Dir Pkg)) -> PackageDB -> PackageDBCWD
262+
interpretPackageDB _ GlobalPackageDB = GlobalPackageDB
263+
interpretPackageDB _ UserPackageDB = UserPackageDB
264+
interpretPackageDB mbWorkDir (SpecificPackageDB db) =
265+
SpecificPackageDB (interpretSymbolicPath mbWorkDir db)
266+
267+
interpretPackageDBStack :: Maybe (SymbolicPath CWD (Dir Pkg)) -> PackageDBStack -> PackageDBStackCWD
268+
interpretPackageDBStack mbWorkDir = map (interpretPackageDB mbWorkDir)
269+
270+
-- | Transform a package db using a FilePath into one using symbolic paths.
271+
coercePackageDB :: PackageDBCWD -> PackageDBX (SymbolicPath CWD (Dir PkgDB))
272+
coercePackageDB GlobalPackageDB = GlobalPackageDB
273+
coercePackageDB UserPackageDB = UserPackageDB
274+
coercePackageDB (SpecificPackageDB db) = SpecificPackageDB (makeSymbolicPath db)
275+
276+
coercePackageDBStack
277+
:: [PackageDBCWD]
278+
-> [PackageDBX (SymbolicPath CWD (Dir PkgDB))]
279+
coercePackageDBStack = map coercePackageDB
237280

238281
-- ------------------------------------------------------------
239282

0 commit comments

Comments
 (0)