Skip to content

Commit 538a5aa

Browse files
committed
Add revision information to plan.json
Closes #6186
1 parent d643706 commit 538a5aa

File tree

7 files changed

+112
-5
lines changed

7 files changed

+112
-5
lines changed

cabal-install/src/Distribution/Client/ProjectPlanOutput.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,8 @@ import Distribution.Verbosity
6666
import Distribution.Client.Compat.Prelude
6767
import Prelude ()
6868

69+
import Control.Monad ((<=<))
70+
6971
import qualified Data.ByteString.Builder as BB
7072
import qualified Data.ByteString.Lazy as BS
7173
import qualified Data.Map as Map
@@ -259,13 +261,24 @@ encodePlanAsJson distDirLayout elaboratedInstallPlan elaboratedSharedConfig =
259261
J.object
260262
[ "type" J..= J.String "remote-repo"
261263
, "uri" J..= J.String (show (remoteRepoURI repoRemote))
264+
, -- The x-revision field is a feature of remote repos,
265+
-- so we only output it for remote/secure repos, in the "repo" object.
266+
"pkg-revision" J..= J.Number (elaboratedPackageToRevision elab)
262267
]
263268
RepoSecure{..} ->
264269
J.object
265270
[ "type" J..= J.String "secure-repo"
266271
, "uri" J..= J.String (show (remoteRepoURI repoRemote))
272+
, "pkg-revision" J..= J.Number (elaboratedPackageToRevision elab)
267273
]
268274

275+
elaboratedPackageToRevision :: ElaboratedConfiguredPackage -> Double
276+
elaboratedPackageToRevision =
277+
fromMaybe 0
278+
. (readMaybe <=< lookup "x-revision")
279+
. PD.customFieldsPD
280+
. elabPkgDescription
281+
269282
sourceRepoToJ :: SourceRepoMaybe -> J.Value
270283
sourceRepoToJ SourceRepositoryPackage{..} =
271284
J.object $
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
import Distribution.Types.PackageName (PackageName, mkPackageName)
3+
import Test.Cabal.Prelude
4+
import Test.Cabal.DecodeShowBuildInfo
5+
import Test.Cabal.Plan
6+
import Data.Maybe (mapMaybe)
7+
8+
getRevisionFor :: PackageName -> InstallItem -> Maybe Revision
9+
getRevisionFor pkgName (AConfiguredGlobal configuredGlobal)
10+
| configuredGlobalPackageName configuredGlobal == pkgName =
11+
Just $ pkgRevision $ repo $ configuredGlobalPkgSrc configuredGlobal
12+
getRevisionFor _ _ = Nothing
13+
14+
main = cabalTest $ do
15+
withRemoteRepo "repo" $ do
16+
cabal "build" ["--dry-run", "all"]
17+
withPlan $ do
18+
Just plan <- testPlan `fmap` getTestEnv
19+
let [fooRev] = mapMaybe (getRevisionFor $ mkPackageName "foo") $ planInstallPlan plan
20+
let [barRev] = mapMaybe (getRevisionFor $ mkPackageName "bar") $ planInstallPlan plan
21+
assertEqual "revision of package foo" fooRev $ Revision 0
22+
assertEqual "revision of package bar" barRev $ Revision 1337
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
name: pkg
2+
version: 1.0
3+
build-type: Simple
4+
cabal-version: >= 1.2
5+
6+
executable my-exe
7+
main-is: Main.hs
8+
build-depends: base, foo, bar
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
name: bar
2+
version: 1.0
3+
build-type: Simple
4+
cabal-version: >= 1.2
5+
6+
library
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
name: foo
2+
version: 1.0
3+
build-type: Simple
4+
cabal-version: >= 1.2
5+
6+
library

cabal-testsuite/src/Test/Cabal/Plan.hs

Lines changed: 48 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,16 @@
1+
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
13
{-# LANGUAGE OverloadedStrings #-}
24
{-# OPTIONS_GHC -Wno-orphans #-}
35
-- | Utilities for understanding @plan.json@.
46
module Test.Cabal.Plan (
5-
Plan,
7+
Plan(..),
68
DistDirOrBinFile(..),
9+
InstallItem(..),
10+
ConfiguredGlobal(..),
11+
Revision(..),
12+
PkgSrc(..),
13+
Repo(..),
714
planDistDir,
815
buildInfoFile,
916
) where
@@ -16,6 +23,7 @@ import qualified Data.Text as Text
1623
import Data.Aeson
1724
import Data.Aeson.Types
1825
import Control.Monad
26+
import GHC.Generics (Generic)
1927

2028
-- TODO: index this
2129
data Plan = Plan { planInstallPlan :: [InstallItem] }
@@ -32,15 +40,33 @@ data ConfiguredInplace = ConfiguredInplace
3240
{ configuredInplaceDistDir :: FilePath
3341
, configuredInplaceBuildInfo :: Maybe FilePath
3442
, configuredInplacePackageName :: PackageName
35-
, configuredInplaceComponentName :: Maybe ComponentName }
43+
, configuredInplaceComponentName :: Maybe ComponentName
44+
, configuredInplacePkgSrc :: PkgSrc }
3645
deriving Show
3746

3847
data ConfiguredGlobal = ConfiguredGlobal
3948
{ configuredGlobalBinFile :: Maybe FilePath
4049
, configuredGlobalPackageName :: PackageName
41-
, configuredGlobalComponentName :: Maybe ComponentName }
50+
, configuredGlobalComponentName :: Maybe ComponentName
51+
, configuredGlobalPkgSrc :: PkgSrc }
4252
deriving Show
4353

54+
newtype Revision = Revision Int
55+
deriving (Show, Eq, FromJSON)
56+
57+
-- | A stripped-down 'Distribution.Client.Types.PackageLocation.PackageLocation'
58+
data PkgSrc
59+
= RepoTar { repo :: Repo }
60+
| PkgSrcOther
61+
deriving (Show, Generic)
62+
63+
-- | A stripped-down 'Distribution.Client.Types.Repo.Repo', plus revision information
64+
data Repo
65+
= LocalRepoNoIndex
66+
| RemoteRepo { pkgRevision :: Revision }
67+
| SecureRepo { pkgRevision :: Revision }
68+
deriving (Show, Generic)
69+
4470
instance FromJSON Plan where
4571
parseJSON (Object v) = fmap Plan (v .: "install-plan")
4672
parseJSON invalid = typeMismatch "Plan" invalid
@@ -66,15 +92,17 @@ instance FromJSON ConfiguredInplace where
6692
build_info <- v .:? "build-info"
6793
pkg_name <- v .: "pkg-name"
6894
component_name <- v .:? "component-name"
69-
return (ConfiguredInplace dist_dir build_info pkg_name component_name)
95+
pkg_src <- v .: "pkg-src"
96+
return (ConfiguredInplace dist_dir build_info pkg_name component_name pkg_src)
7097
parseJSON invalid = typeMismatch "ConfiguredInplace" invalid
7198

7299
instance FromJSON ConfiguredGlobal where
73100
parseJSON (Object v) = do
74101
bin_file <- v .:? "bin-file"
75102
pkg_name <- v .: "pkg-name"
76103
component_name <- v .:? "component-name"
77-
return (ConfiguredGlobal bin_file pkg_name component_name)
104+
pkg_src <- v .: "pkg-src"
105+
return (ConfiguredGlobal bin_file pkg_name component_name pkg_src)
78106
parseJSON invalid = typeMismatch "ConfiguredGlobal" invalid
79107

80108
instance FromJSON PackageName where
@@ -89,6 +117,21 @@ instance FromJSON ComponentName where
89117
where s = Text.unpack t
90118
parseJSON invalid = typeMismatch "ComponentName" invalid
91119

120+
instance FromJSON PkgSrc where
121+
parseJSON (Object v) = do
122+
t <- v .: "type"
123+
case t :: String of
124+
"repo-tar" -> RepoTar <$> v .: "repo"
125+
_ -> return PkgSrcOther
126+
parseJSON invalid = typeMismatch "PkgSrc" invalid
127+
128+
instance FromJSON Repo where
129+
parseJSON = genericParseJSON defaultOptions
130+
{ constructorTagModifier = camelTo2 '-'
131+
, fieldLabelModifier = camelTo2 '-'
132+
, sumEncoding = TaggedObject "type" ""
133+
}
134+
92135
data DistDirOrBinFile = DistDir FilePath | BinFile FilePath
93136

94137
planDistDir :: Plan -> PackageName -> ComponentName -> DistDirOrBinFile

changelog.d/pr-10980

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
synopsis: Added revision information to `plan.json`
2+
packages: cabal-install
3+
prs: #10980
4+
issues: #6186
5+
6+
description: {
7+
The contents of `x-revision` `.cabal` fields are now available in `plan.json`.
8+
They are located under `pkg-src.repo.pkg-revision`, have type `Number`, and are only available for `repo-tar` repositories of type `remote-repo` or `secure-repo`.
9+
}

0 commit comments

Comments
 (0)