Skip to content

Commit bb2f2e1

Browse files
committed
Add compiler to PackageId
(cherry picked from commit 79b31e1)
1 parent 409e01f commit bb2f2e1

File tree

27 files changed

+83
-57
lines changed

27 files changed

+83
-57
lines changed

Cabal-syntax/src/Distribution/Compiler.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ instance (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a) where
174174
-- ------------------------------------------------------------
175175

176176
data CompilerId = CompilerId CompilerFlavor Version
177-
deriving (Eq, Generic, Ord, Read, Show)
177+
deriving (Eq, Generic, Ord, Read, Show, Data)
178178

179179
instance Binary CompilerId
180180
instance Structured CompilerId

Cabal-syntax/src/Distribution/PackageDescription/FieldGrammar.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ import Prelude ()
7474

7575
import Distribution.CabalSpecVersion
7676
import Distribution.Compat.Newtype (Newtype, pack', unpack')
77-
import Distribution.Compiler (CompilerFlavor (..), PerCompilerFlavor (..))
77+
import Distribution.Compiler (CompilerFlavor (..), PerCompilerFlavor (..), CompilerId)
7878
import Distribution.FieldGrammar
7979
import Distribution.Fields
8080
import Distribution.ModuleName (ModuleName)
@@ -101,6 +101,7 @@ packageDescriptionFieldGrammar
101101
, c (Identity BuildType)
102102
, c (Identity PackageName)
103103
, c (Identity Version)
104+
, c (Identity CompilerId)
104105
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
105106
, forall from to. c (List VCat (RelativePathNT from to) (RelativePath from to))
106107
, c (List FSep TestedWith (CompilerFlavor, VersionRange))
@@ -150,6 +151,7 @@ packageDescriptionFieldGrammar =
150151
PackageIdentifier
151152
<$> uniqueField "name" L.pkgName
152153
<*> uniqueField "version" L.pkgVersion
154+
<*> optionalField "compiler" L.pkgCompiler
153155

154156
licenseFilesGrammar =
155157
(++)

Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -16,10 +16,10 @@ import Prelude ()
1616

1717
import Distribution.Backpack
1818
import Distribution.Compat.Graph (IsNode (..))
19-
import Distribution.Compiler (CompilerId)
19+
import Distribution.Compiler (CompilerId, buildCompilerId)
2020
import Distribution.License
2121
import Distribution.ModuleName
22-
import Distribution.Package hiding (installedUnitId)
22+
import Distribution.Package hiding (installedUnitId, pkgCompiler)
2323
import Distribution.Types.AbiDependency
2424
import Distribution.Types.ExposedModule
2525
import Distribution.Types.LibraryName
@@ -121,8 +121,8 @@ instance IsNode InstalledPackageInfo where
121121
nodeNeighbors = depends
122122

123123
mungedPackageId :: InstalledPackageInfo -> MungedPackageId
124-
mungedPackageId ipi =
125-
MungedPackageId (mungedPackageName ipi) (packageVersion ipi)
124+
mungedPackageId ipi@InstalledPackageInfo{pkgCompiler = comp} =
125+
MungedPackageId (mungedPackageName ipi) (packageVersion ipi) comp
126126

127127
-- | Returns the munged package name, which we write into @name@ for
128128
-- compatibility with old versions of GHC.
@@ -132,7 +132,7 @@ mungedPackageName ipi = MungedPackageName (packageName ipi) (sourceLibName ipi)
132132
emptyInstalledPackageInfo :: InstalledPackageInfo
133133
emptyInstalledPackageInfo =
134134
InstalledPackageInfo
135-
{ sourcePackageId = PackageIdentifier (mkPackageName "") nullVersion
135+
{ sourcePackageId = PackageIdentifier (mkPackageName "") nullVersion Nothing
136136
, sourceLibName = LMainLibName
137137
, installedComponentId_ = mkComponentId ""
138138
, installedUnitId = mkUnitId ""

Cabal-syntax/src/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ import Distribution.FieldGrammar
2020
import Distribution.FieldGrammar.FieldDescrs
2121
import Distribution.License
2222
import Distribution.ModuleName
23-
import Distribution.Package
23+
import Distribution.Package hiding (pkgCompiler)
2424
import Distribution.Parsec
2525
import Distribution.Pretty
2626
import Distribution.Types.LibraryName
@@ -38,7 +38,7 @@ import qualified Text.PrettyPrint as Disp
3838
import Distribution.Types.InstalledPackageInfo
3939

4040
import qualified Distribution.Types.InstalledPackageInfo.Lens as L
41-
import qualified Distribution.Types.PackageId.Lens as L
41+
import qualified Distribution.Types.PackageId.Lens as L hiding (pkgCompiler)
4242

4343
-- Note: GHC goes nuts and inlines everything,
4444
-- One can see e.g. in -ddump-simpl-stats:
@@ -133,7 +133,7 @@ ipiFieldGrammar =
133133
InstalledPackageInfo
134134
-- _basicPkgName is not used
135135
-- setMaybePackageId says it can be no-op.
136-
(PackageIdentifier pn _basicVersion)
136+
(PackageIdentifier pn _basicVersion _basicCompilerId)
137137
(combineLibraryName ln _basicLibName)
138138
(mkComponentId "") -- installedComponentId_, not in use
139139
_basicLibVisibility
@@ -256,6 +256,7 @@ data Basic = Basic
256256
, _basicPkgName :: Maybe PackageName
257257
, _basicLibName :: LibraryName
258258
, _basicLibVisibility :: LibraryVisibility
259+
, _basicCompilerId :: Maybe CompilerId
259260
}
260261

261262
basic :: Lens' InstalledPackageInfo Basic
@@ -268,14 +269,16 @@ basic f ipi = g <$> f b
268269
(maybePackageName ipi)
269270
(sourceLibName ipi)
270271
(libVisibility ipi)
272+
(pkgCompiler ipi)
271273

272-
g (Basic n v pn ln lv) =
274+
g (Basic n v pn ln lv compid) =
273275
ipi
274276
& setMungedPackageName n
275277
& L.sourcePackageId . L.pkgVersion .~ v
276278
& setMaybePackageName pn
277279
& L.sourceLibName .~ ln
278280
& L.libVisibility .~ lv
281+
& L.pkgCompiler .~ compid
279282

280283
basicName :: Lens' Basic MungedPackageName
281284
basicName f b = (\x -> b{_basicName = x}) <$> f (_basicName b)
@@ -319,7 +322,7 @@ basicFieldGrammar =
319322
<*> optionalField "lib-name" basicLibName
320323
<*> optionalFieldDef "visibility" basicLibVisibility LibraryVisibilityPrivate
321324
where
322-
mkBasic n v pn ln lv = Basic n v pn ln' lv'
325+
mkBasic n v pn ln lv = Basic n v pn ln' lv' Nothing
323326
where
324327
ln' = maybe LMainLibName LSubLibName ln
325328
-- Older GHCs (<8.8) always report installed libraries as private

Cabal-syntax/src/Distribution/Types/MungedPackageId.hs

Lines changed: 10 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ import Distribution.Types.LibraryName
1515
import Distribution.Types.MungedPackageName
1616
import Distribution.Types.PackageId
1717
import Distribution.Version (Version, nullVersion)
18+
import Distribution.Compiler (CompilerId)
1819

1920
import qualified Text.PrettyPrint as Disp
2021

@@ -27,6 +28,7 @@ data MungedPackageId = MungedPackageId
2728
-- 'MungedPackageName'.
2829
, mungedVersion :: Version
2930
-- ^ The version of this package / component, eg 1.2
31+
, mingledCompilerId :: Maybe CompilerId
3032
}
3133
deriving (Generic, Read, Show, Eq, Ord, Data)
3234

@@ -41,8 +43,9 @@ instance Structured MungedPackageId
4143
-- >>> prettyShow $ MungedPackageId (MungedPackageName "servant" (LSubLibName "lackey")) (mkVersion [0,1,2])
4244
-- "z-servant-z-lackey-0.1.2"
4345
instance Pretty MungedPackageId where
44-
pretty (MungedPackageId n v)
45-
| v == nullVersion = pretty n -- if no version, don't show version.
46+
pretty (MungedPackageId n v c)
47+
| v == nullVersion = pretty c <<>> Disp.char '-' <<>> pretty n -- if no version, don't show version.
48+
| Just c' <- c = pretty c' <<>> Disp.char '-' <<>> pretty n <<>> Disp.char '-' <<>> pretty v
4649
| otherwise = pretty n <<>> Disp.char '-' <<>> pretty v
4750

4851
-- |
@@ -66,15 +69,15 @@ instance Pretty MungedPackageId where
6669
-- Nothing
6770
instance Parsec MungedPackageId where
6871
parsec = do
69-
PackageIdentifier pn v <- parsec
70-
return $ MungedPackageId (decodeCompatPackageName pn) v
72+
PackageIdentifier pn v comp <- parsec
73+
return $ MungedPackageId (decodeCompatPackageName pn) v comp
7174

7275
instance NFData MungedPackageId where
73-
rnf (MungedPackageId name version) = rnf name `seq` rnf version
76+
rnf (MungedPackageId name version compiler) = rnf name `seq` rnf version `seq` rnf compiler
7477

7578
computeCompatPackageId :: PackageId -> LibraryName -> MungedPackageId
76-
computeCompatPackageId (PackageIdentifier pn vr) ln =
77-
MungedPackageId (MungedPackageName pn ln) vr
79+
computeCompatPackageId (PackageIdentifier pn vr comp) ln =
80+
MungedPackageId (MungedPackageName pn ln) vr comp
7881

7982
-- $setup
8083
-- >>> :seti -XOverloadedStrings

Cabal-syntax/src/Distribution/Types/PackageDescription.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -207,6 +207,7 @@ emptyPackageDescription =
207207
PackageIdentifier
208208
(mkPackageName "")
209209
nullVersion
210+
Nothing
210211
, licenseRaw = Right UnspecifiedLicense -- TODO:
211212
, licenseFiles = []
212213
, specVersion = CabalSpecV1_0

Cabal-syntax/src/Distribution/Types/PackageId.hs

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ import Distribution.Parsec (Parsec (..), simpleParsec)
1313
import Distribution.Pretty
1414
import Distribution.Types.PackageName
1515
import Distribution.Version (Version, nullVersion)
16+
import Distribution.Compiler (CompilerId)
1617

1718
import qualified Data.List.NonEmpty as NE
1819
import qualified Distribution.Compat.CharParsing as P
@@ -27,15 +28,17 @@ data PackageIdentifier = PackageIdentifier
2728
-- ^ The name of this package, eg. foo
2829
, pkgVersion :: Version
2930
-- ^ the version of this package, eg 1.2
31+
, pkgCompiler :: Maybe CompilerId
3032
}
3133
deriving (Generic, Read, Show, Eq, Ord, Data)
3234

3335
instance Binary PackageIdentifier
3436
instance Structured PackageIdentifier
3537

3638
instance Pretty PackageIdentifier where
37-
pretty (PackageIdentifier n v)
38-
| v == nullVersion = pretty n -- if no version, don't show version.
39+
pretty (PackageIdentifier n v c)
40+
| v == nullVersion = pretty c <<>> Disp.char '-' <<>> pretty n -- if no version, don't show version.
41+
| Just c' <- c = pretty c' <<>> Disp.char '-' <<>> pretty n <<>> Disp.char '-' <<>> pretty v
3942
| otherwise = pretty n <<>> Disp.char '-' <<>> pretty v
4043

4144
-- |
@@ -61,15 +64,16 @@ instance Pretty PackageIdentifier where
6164
-- Nothing
6265
instance Parsec PackageIdentifier where
6366
parsec = do
67+
comp <- parsec <* P.char '-'
6468
xs' <- P.sepByNonEmpty component (P.char '-')
6569
(v, xs) <- case simpleParsec (NE.last xs') of
6670
Nothing -> return (nullVersion, toList xs') -- all components are version
6771
Just v -> return (v, NE.init xs')
6872
if not (null xs) && all (\c -> all (/= '.') c && not (all isDigit c)) xs
69-
then return $ PackageIdentifier (mkPackageName (intercalate "-" xs)) v
73+
then return $ PackageIdentifier (mkPackageName (intercalate "-" xs)) v comp
7074
else fail "all digits or a dot in a portion of package name"
7175
where
7276
component = P.munch1 (\c -> isAlphaNum c || c == '.')
7377

7478
instance NFData PackageIdentifier where
75-
rnf (PackageIdentifier name version) = rnf name `seq` rnf version
79+
rnf (PackageIdentifier name version compiler) = rnf name `seq` rnf version `seq` rnf compiler

Cabal-syntax/src/Distribution/Types/PackageId/Lens.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Prelude ()
1010
import Distribution.Types.PackageId (PackageIdentifier)
1111
import Distribution.Types.PackageName (PackageName)
1212
import Distribution.Version (Version)
13+
import Distribution.Compiler (CompilerId)
1314

1415
import qualified Distribution.Types.PackageId as T
1516

@@ -20,3 +21,8 @@ pkgName f s = fmap (\x -> s{T.pkgName = x}) (f (T.pkgName s))
2021
pkgVersion :: Lens' PackageIdentifier Version
2122
pkgVersion f s = fmap (\x -> s{T.pkgVersion = x}) (f (T.pkgVersion s))
2223
{-# INLINE pkgVersion #-}
24+
25+
pkgCompiler :: Lens' PackageIdentifier (Maybe CompilerId)
26+
pkgCompiler f s = fmap (\x -> s{T.pkgCompiler = x}) (f (T.pkgCompiler s))
27+
{-# INLINE pkgCompiler #-}
28+

Cabal-syntax/src/Distribution/Types/PackageVersionConstraint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ instance Pretty PackageVersionConstraint where
5353
-- Just (PackageVersionConstraint (PackageName "foo") (ThisVersion (mkVersion [2,0])))
5454
instance Parsec PackageVersionConstraint where
5555
parsec = do
56-
PackageIdentifier name ver <- parsec
56+
PackageIdentifier name ver comp <- parsec
5757
if ver == nullVersion
5858
then do
5959
P.spaces
@@ -64,7 +64,7 @@ instance Parsec PackageVersionConstraint where
6464

6565
-- | @since 3.4.0.0
6666
thisPackageVersionConstraint :: PackageIdentifier -> PackageVersionConstraint
67-
thisPackageVersionConstraint (PackageIdentifier pn vr) =
67+
thisPackageVersionConstraint (PackageIdentifier pn vr comp) =
6868
PackageVersionConstraint pn (thisVersion vr)
6969

7070
-- | @since 3.4.0.0

Cabal/src/Distribution/Backpack/PreExistingComponent.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -71,9 +71,9 @@ instance HasMungedPackageId PreExistingComponent where
7171
mungedId = pc_munged_id
7272

7373
instance Package PreExistingComponent where
74-
packageId pec = PackageIdentifier (pc_pkgname pec) v
74+
packageId pec = PackageIdentifier (pc_pkgname pec) v compid
7575
where
76-
MungedPackageId _ v = pc_munged_id pec
76+
MungedPackageId _ v compid = pc_munged_id pec
7777

7878
instance HasUnitId PreExistingComponent where
7979
installedUnitId = pc_uid

0 commit comments

Comments
 (0)