Skip to content

Commit

Permalink
Add post-checkout-command
Browse files Browse the repository at this point in the history
- Resolve haskell#6684:
- Resolve haskell#6813: Update (and correct) source-repository-package documentation
  • Loading branch information
phadej committed Sep 9, 2020
1 parent 2020512 commit 67ddd62
Show file tree
Hide file tree
Showing 7 changed files with 106 additions and 22 deletions.
59 changes: 55 additions & 4 deletions Cabal/src/Distribution/FieldGrammar/Newtypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,14 @@ module Distribution.FieldGrammar.Newtypes (
Sep (..),
-- ** Type
List,
-- * Set
-- ** Set
alaSet,
alaSet',
Set',
-- ** NonEmpty
alaNonEmpty,
alaNonEmpty',
NonEmpty',
-- * Version & License
SpecVersion (..),
TestedWith (..),
Expand All @@ -46,6 +50,7 @@ import Distribution.Version
(LowerBound (..), Version, VersionRange, VersionRangeF (..), anyVersion, asVersionIntervals, cataVersionRange, mkVersion, version0, versionNumbers)
import Text.PrettyPrint (Doc, comma, fsep, punctuate, text, vcat)

import qualified Data.List.NonEmpty as NE
import qualified Data.Set as Set
import qualified Distribution.Compat.CharParsing as P
import qualified Distribution.SPDX as SPDX
Expand All @@ -68,31 +73,41 @@ data NoCommaFSep = NoCommaFSep
class Sep sep where
prettySep :: Proxy sep -> [Doc] -> Doc

parseSep :: CabalParsing m => Proxy sep -> m a -> m [a]
parseSep :: CabalParsing m => Proxy sep -> m a -> m [a]
parseSepNE :: CabalParsing m => Proxy sep -> m a -> m (NonEmpty a)

instance Sep CommaVCat where
prettySep _ = vcat . punctuate comma
parseSep _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV2_2 then parsecLeadingCommaList p else parsecCommaList p
parseSepNE _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV2_2 then parsecLeadingCommaNonEmpty p else parsecCommaNonEmpty p
instance Sep CommaFSep where
prettySep _ = fsep . punctuate comma
parseSep _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV2_2 then parsecLeadingCommaList p else parsecCommaList p
parseSepNE _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV2_2 then parsecLeadingCommaNonEmpty p else parsecCommaNonEmpty p
instance Sep VCat where
prettySep _ = vcat
parseSep _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV3_0 then parsecLeadingOptCommaList p else parsecOptCommaList p
parseSepNE _ p = NE.some1 (p <* P.spaces)
instance Sep FSep where
prettySep _ = fsep
parseSep _ p = do
v <- askCabalSpecVersion
if v >= CabalSpecV3_0 then parsecLeadingOptCommaList p else parsecOptCommaList p
parseSepNE _ p = NE.some1 (p <* P.spaces)
instance Sep NoCommaFSep where
prettySep _ = fsep
parseSep _ p = many (p <* P.spaces)
prettySep _ = fsep
parseSep _ p = many (p <* P.spaces)
parseSepNE _ p = NE.some1 (p <* P.spaces)

-- | List separated with optional commas. Displayed with @sep@, arguments of
-- type @a@ are parsed and pretty-printed as @b@.
Expand Down Expand Up @@ -158,6 +173,42 @@ instance (Newtype a b, Ord a, Sep sep, Parsec b) => Parsec (Set' sep b a) where
instance (Newtype a b, Sep sep, Pretty b) => Pretty (Set' sep b a) where
pretty = prettySep (Proxy :: Proxy sep) . map (pretty . (pack :: a -> b)) . Set.toList . unpack

--
-- | Like 'List', but for 'NonEmpty'.
--
-- @since 3.2.0.0
newtype NonEmpty' sep b a = NonEmpty' { _getNonEmpty :: NonEmpty a }

-- | 'alaNonEmpty' and 'alaNonEmpty'' are simply 'NonEmpty'' constructor, with additional phantom
-- arguments to constrain the resulting type
--
-- >>> :t alaNonEmpty VCat
-- alaNonEmpty VCat :: NonEmpty a -> NonEmpty' VCat (Identity a) a
--
-- >>> :t alaNonEmpty' FSep Token
-- alaNonEmpty' FSep Token :: NonEmpty String -> NonEmpty' FSep Token String
--
-- >>> unpack' (alaNonEmpty' FSep Token) <$> eitherParsec "foo bar foo"
-- Right (fromList ["bar","foo"])
--
-- @since 3.2.0.0
alaNonEmpty :: sep -> NonEmpty a -> NonEmpty' sep (Identity a) a
alaNonEmpty _ = NonEmpty'

-- | More general version of 'alaNonEmpty'.
--
-- @since 3.2.0.0
alaNonEmpty' :: sep -> (a -> b) -> NonEmpty a -> NonEmpty' sep b a
alaNonEmpty' _ _ = NonEmpty'

instance Newtype (NonEmpty a) (NonEmpty' sep wrapper a)

instance (Newtype a b, Sep sep, Parsec b) => Parsec (NonEmpty' sep b a) where
parsec = pack . fmap (unpack :: b -> a) <$> parseSepNE (Proxy :: Proxy sep) parsec

instance (Newtype a b, Sep sep, Pretty b) => Pretty (NonEmpty' sep b a) where
pretty = prettySep (Proxy :: Proxy sep) . map (pretty . (pack :: a -> b)) . NE.toList . unpack

-------------------------------------------------------------------------------
-- Identifiers
-------------------------------------------------------------------------------
Expand Down
9 changes: 7 additions & 2 deletions cabal-install/src/Distribution/Client/ProjectConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ import Distribution.Simple.InstallDirs
( PathTemplate, fromPathTemplate
, toPathTemplate, substPathTemplate, initialPathTemplateEnv )
import Distribution.Simple.Utils
( die', warn, notice, info, createDirectoryIfMissingVerbose )
( die', warn, notice, info, createDirectoryIfMissingVerbose, rawSystemIOWithEnv )
import Distribution.Client.Utils
( determineNumJobs )
import Distribution.Utils.NubList
Expand Down Expand Up @@ -1172,7 +1172,12 @@ syncAndReadSourcePackagesRemoteRepos verbosity
syncSourceRepos verbosity vcs
[ (repo, repoPath)
| (repo, _, repoPath) <- repoGroupWithPaths ]
-- TODO phadej 2020-06-18 add post-sync script

-- Run post-checkout-command if it is specified
for_ repoGroupWithPaths $ \(repo, _, repoPath) ->
for_ (srpCommand repo) $ \(cmd :| args) -> liftIO $ do
exitCode <- rawSystemIOWithEnv verbosity cmd args (Just repoPath) Nothing Nothing Nothing Nothing
unless (exitCode /= ExitSuccess) $ exitWith exitCode

-- But for reading we go through each 'SourceRepo' including its subdir
-- value and have to know which path each one ended up in.
Expand Down
8 changes: 6 additions & 2 deletions cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1224,7 +1224,9 @@ legacyPackageConfigFieldDescrs =

legacyPackageConfigFGSectionDescrs
:: ( FieldGrammar c g, Applicative (g SourceRepoList)
, c (Identity RepoType), c (List NoCommaFSep FilePathNT String)
, c (Identity RepoType)
, c (List NoCommaFSep FilePathNT String)
, c (NonEmpty' NoCommaFSep Token String)
)
=> [FGSectionDescr g LegacyProjectConfig]
legacyPackageConfigFGSectionDescrs =
Expand Down Expand Up @@ -1253,7 +1255,9 @@ legacyPackageConfigSectionDescrs =

packageRepoSectionDescr
:: ( FieldGrammar c g, Applicative (g SourceRepoList)
, c (Identity RepoType), c (List NoCommaFSep FilePathNT String)
, c (Identity RepoType)
, c (List NoCommaFSep FilePathNT String)
, c (NonEmpty' NoCommaFSep Token String)
)
=> FGSectionDescr g LegacyProjectConfig
packageRepoSectionDescr = FGSectionDescr
Expand Down
17 changes: 12 additions & 5 deletions cabal-install/src/Distribution/Client/Types/SourceRepo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ data SourceRepositoryPackage f = SourceRepositoryPackage
, srpTag :: !(Maybe String)
, srpBranch :: !(Maybe String)
, srpSubdir :: !(f FilePath)
, srpCommand :: !(Maybe (NonEmpty String))
}
deriving (Generic)

Expand Down Expand Up @@ -88,6 +89,10 @@ srpSubdirLens :: Lens (SourceRepositoryPackage f) (SourceRepositoryPackage g) (f
srpSubdirLens f s = fmap (\x -> s { srpSubdir = x }) (f (srpSubdir s))
{-# INLINE srpSubdirLens #-}

srpCommandLens :: Lens' (SourceRepositoryPackage f) (Maybe (NonEmpty String))
srpCommandLens f s = fmap (\x -> s { srpCommand = x }) (f (srpCommand s))
{-# INLINE srpCommandLens #-}

-------------------------------------------------------------------------------
-- Parser & PPrinter
-------------------------------------------------------------------------------
Expand All @@ -96,13 +101,15 @@ sourceRepositoryPackageGrammar
:: ( FieldGrammar c g, Applicative (g SourceRepoList)
, c (Identity RepoType)
, c (List NoCommaFSep FilePathNT String)
, c (NonEmpty' NoCommaFSep Token String)
)
=> g SourceRepoList SourceRepoList
sourceRepositoryPackageGrammar = SourceRepositoryPackage
<$> uniqueField "type" srpTypeLens
<*> uniqueFieldAla "location" Token srpLocationLens
<*> optionalFieldAla "tag" Token srpTagLens
<*> optionalFieldAla "branch" Token srpBranchLens
<*> monoidalFieldAla "subdir" (alaList' NoCommaFSep FilePathNT) srpSubdirLens -- note: NoCommaFSep is somewhat important for roundtrip, as "." is there...
<$> uniqueField "type" srpTypeLens
<*> uniqueFieldAla "location" Token srpLocationLens
<*> optionalFieldAla "tag" Token srpTagLens
<*> optionalFieldAla "branch" Token srpBranchLens
<*> monoidalFieldAla "subdir" (alaList' NoCommaFSep FilePathNT) srpSubdirLens -- note: NoCommaFSep is somewhat important for roundtrip, as "." is there...
<*> optionalFieldAla "post-checkout-command" (alaNonEmpty' NoCommaFSep Token) srpCommandLens
{-# SPECIALIZE sourceRepositoryPackageGrammar :: ParsecFieldGrammar' SourceRepoList #-}
{-# SPECIALIZE sourceRepositoryPackageGrammar :: PrettyFieldGrammar' SourceRepoList #-}
1 change: 1 addition & 0 deletions cabal-install/src/Distribution/Client/VCS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,7 @@ validatePDSourceRepo repo = do
, srpTag = PD.repoTag repo
, srpBranch = PD.repoBranch repo
, srpSubdir = PD.repoSubdir repo
, srpCommand = mempty
}
where
a ?! e = maybe (Left e) Right a
Expand Down
2 changes: 1 addition & 1 deletion changelog.d/documentation
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
synopsis: Documentation improvements
prs: #6971
prs: #6971 #6813

description: {

Expand Down
32 changes: 24 additions & 8 deletions doc/cabal-project.rst
Original file line number Diff line number Diff line change
Expand Up @@ -147,14 +147,7 @@ Specifying Packages from Remote Version Control Locations

Starting with Cabal 2.4, there is now a stanza
``source-repository-package`` for specifying packages from an external
version control which supports the following fields:

- :pkg-field:`source-repository:type`
- :pkg-field:`source-repository:location`
- :pkg-field:`source-repository:tag`
- :pkg-field:`source-repository:subdir`

A simple example is shown below:
version control.

.. code-block:: cabal
Expand All @@ -171,6 +164,29 @@ A simple example is shown below:
tag: 3d274c14ca3077c3a081ba7ad57c5182da65c8c1
subdir: cborg
source-repository-package
type: git
location: https://github.com/haskell/network.git
tag: e76fdc753e660dfa615af6c8b6a2ad9ddf6afe70
post-checkout-command: autoreconf -i
cabal-install 3.4 sdists the ``source-repository-package`` repositories and uses resulting tarballs as project packages.
This allows sharing of packages across different projects.

.. cfg-field:: type: VCS kind

.. cfg-field:: location: VCS location (usually URL)

.. cfg-field:: type:: VCS tag

.. cfg-field:: subdir: subdirectory list

Use one or more subdirectories of the repository.

.. cfg-field:: post-checkout-command: command

Run command in the checked out repository, prior sdisting.

Global configuration options
----------------------------

Expand Down

0 comments on commit 67ddd62

Please sign in to comment.