1+ {-# LANGUAGE DeriveGeneric #-}
2+ {-# LANGUAGE GeneralizedNewtypeDeriving #-}
13{-# LANGUAGE OverloadedStrings #-}
24{-# OPTIONS_GHC -Wno-orphans #-}
35-- | Utilities for understanding @plan.json@.
46module 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
1623import Data.Aeson
1724import Data.Aeson.Types
1825import Control.Monad
26+ import GHC.Generics (Generic )
1927
2028-- TODO: index this
2129data 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
3847data 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+
4470instance 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
7299instance 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
80108instance 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+
92135data DistDirOrBinFile = DistDir FilePath | BinFile FilePath
93136
94137planDistDir :: Plan -> PackageName -> ComponentName -> DistDirOrBinFile
0 commit comments