cabal-install-3.8.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellNone
LanguageHaskell2010

Distribution.Client.VCS

Synopsis

VCS driver type

data VCS program Source #

A driver for a version control system, e.g. git, darcs etc.

vcsRepoType :: VCS program -> RepoType Source #

The type of repository this driver is for.

vcsProgram :: VCS program -> program Source #

The vcs program itself. This is used at type Program and ConfiguredProgram.

Type re-exports

data RepoType #

Instances

Instances details
Eq RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Data RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoType -> c RepoType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoType #

toConstr :: RepoType -> Constr #

dataTypeOf :: RepoType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType) #

gmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

Ord RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Read RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Show RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Generic RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Associated Types

type Rep RepoType :: Type -> Type #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

Binary RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Methods

put :: RepoType -> Put #

get :: Get RepoType #

putList :: [RepoType] -> Put #

NFData RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Methods

rnf :: RepoType -> () #

Structured RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Parsec RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

Methods

parsec :: CabalParsing m => m RepoType #

Pretty RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

type Rep RepoType 
Instance details

Defined in Distribution.Types.SourceRepo

type Rep RepoType = D1 ('MetaData "RepoType" "Distribution.Types.SourceRepo" "Cabal-syntax-3.8.1.0-3wqkBKyVQKyGg3OBBvtt1F" 'False) (C1 ('MetaCons "KnownRepoType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownRepoType)) :+: C1 ('MetaCons "OtherRepoType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Program #

Represents a program which can be configured.

Note: rather than constructing this directly, start with simpleProgram and override any extra fields.

Instances

Instances details
Show Program 
Instance details

Defined in Distribution.Simple.Program.Types

data ConfiguredProgram #

Represents a program which has been configured and is thus ready to be run.

These are usually made by configuring a Program, but if you have to construct one directly then start with simpleConfiguredProgram and override any extra fields.

Instances

Instances details
Eq ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Read ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Show ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Generic ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Associated Types

type Rep ConfiguredProgram :: Type -> Type #

Binary ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

Structured ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ConfiguredProgram 
Instance details

Defined in Distribution.Simple.Program.Types

type Rep ConfiguredProgram = D1 ('MetaData "ConfiguredProgram" "Distribution.Simple.Program.Types" "Cabal-3.8.1.0-B0R5uDiDOgc9Mcr4OAtXbo" 'False) (C1 ('MetaCons "ConfiguredProgram" 'PrefixI 'True) (((S1 ('MetaSel ('Just "programId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "programVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :*: (S1 ('MetaSel ('Just "programDefaultArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "programOverrideArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "programOverrideEnv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Maybe String)]) :*: S1 ('MetaSel ('Just "programProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))) :*: (S1 ('MetaSel ('Just "programLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramLocation) :*: S1 ('MetaSel ('Just "programMonitorFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))))

Validating SourceRepos and configuring VCS drivers

validateSourceRepo :: SourceRepositoryPackage f -> Either SourceRepoProblem (SourceRepositoryPackage f, String, RepoType, VCS Program) Source #

Validates that the SourceRepo specifies a location URI and a repository type that is supported by a VCS driver.

| It also returns the VCS driver we should use to work with it.

validateSourceRepos :: [SourceRepositoryPackage f] -> Either [(SourceRepositoryPackage f, SourceRepoProblem)] [(SourceRepositoryPackage f, String, RepoType, VCS Program)] Source #

As validateSourceRepo but for a bunch of SourceRepos, and return things in a convenient form to pass to configureVCSs, or to report problems.

Running the VCS driver

cloneSourceRepo :: Verbosity -> VCS ConfiguredProgram -> SourceRepositoryPackage f -> [Char] -> IO () Source #

Clone a single source repo into a fresh directory, using a configured VCS.

This is for making a new copy, not synchronising an existing copy. It will fail if the destination directory already exists.

Make sure to validate the SourceRepo using validateSourceRepo first.

syncSourceRepos :: Verbosity -> VCS ConfiguredProgram -> [(SourceRepositoryPackage f, FilePath)] -> Rebuild () Source #

Syncronise a set of SourceRepos referring to the same repository with corresponding local directories. The local directories may or may not already exist.

The SourceRepo values used in a single invocation of syncSourceRepos, or used across a series of invocations with any local directory must refer to the same repository. That means it must be the same location but they can differ in the branch, or tag or subdir.

The reason to allow multiple related SourceRepos is to allow for the network or storage to be shared between different checkouts of the repo. For example if a single repo contains multiple packages in different subdirs and in some project it may make sense to use a different state of the repo for one subdir compared to another.

The individual VCS drivers

knownVCSs :: Map RepoType (VCS Program) Source #

The set of all supported VCS drivers, organised by RepoType.

vcsBzr :: VCS Program Source #

VCS driver for Bazaar.

vcsDarcs :: VCS Program Source #

VCS driver for Darcs.

vcsGit :: VCS Program Source #

VCS driver for Git.

vcsHg :: VCS Program Source #

VCS driver for Mercurial.

vcsSvn :: VCS Program Source #

VCS driver for Subversion.

vcsPijul :: VCS Program Source #

VCS driver for Pijul. Documentation for Pijul can be found at https://pijul.org/manual/introduction.html

2020-04-09 Oleg:

As far as I understand pijul, there are branches and "tags" in pijul, but there aren't a "commit hash" identifying an arbitrary state.

One can create `a pijul tag`, which will make a patch hash, which depends on everything currently in the repository. I guess if you try to apply that patch, you'll be forced to apply all the dependencies too. In other words, there are no named tags.

It's not clear to me whether there is an option to "apply this patch *and* all of its dependencies". And relatedly, whether how to make sure that there are no other patches applied.

With branches it's easier, as you can pull and checkout them, and they seem to be similar enough. Yet, pijul documentations says

Note that the purpose of branches in Pijul is quite different from Git,

since Git's "feature branches" can usually be implemented by just patches.

I guess it means that indeed instead of creating a branch and making PR in GitHub workflow, you'd just create a patch and offer it. You can do that with git too. Push (a branch with) commit to remote and ask other to cherry-pick that commit. Yet, in git identity of commit changes when it applied to other trees, where patches in pijul have will continue to have the same hash.

Unfortunately pijul doesn't talk about conflict resolution. It seems that you get something like:

% pijul status On branch merge

Unresolved conflicts: (fix conflicts and record the resolution with "pijul record ...")

foo

% cat foo first line >> >>>>>>>>>>>>>>>>>>>>>>>>>>>>> branch BBB ================================ branch AAA <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< last line

And then the `pijul dependencies` would draw you a graph like

  • ----> foo on branch B -----> resolve confict Initial patch
  • ----> foo on branch A ----->

Which is seems reasonable.

So currently, pijul support is very experimental, and most likely won't work, even the basics are in place. Tests are also written but disabled, as the branching model differs from git one, for which tests are written.