Cabal-2.0.0.2: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.SourceRepo

Synopsis

Documentation

data SourceRepo Source #

Information about the source revision control system for a package.

When specifying a repo it is useful to know the meaning or intention of the information as doing so enables automation. There are two obvious common purposes: one is to find the repo for the latest development version, the other is to find the repo for this specific release. The ReopKind specifies which one we mean (or another custom one).

A package can specify one or the other kind or both. Most will specify just a head repo but some may want to specify a repo to reconstruct the sources for this package release.

The required information is the RepoType which tells us if it's using Darcs, Git for example. The repoLocation and other details are interpreted according to the repo type.

Constructors

SourceRepo 

Fields

  • repoKind :: RepoKind

    The kind of repo. This field is required.

  • repoType :: Maybe RepoType

    The type of the source repository system for this repo, eg Darcs or Git. This field is required.

  • repoLocation :: Maybe String

    The location of the repository. For most RepoTypes this is a URL. This field is required.

  • repoModule :: Maybe String

    CVS can put multiple "modules" on one server and requires a module name in addition to the location to identify a particular repo. Logically this is part of the location but unfortunately has to be specified separately. This field is required for the CVS RepoType and should not be given otherwise.

  • repoBranch :: Maybe String

    The name or identifier of the branch, if any. Many source control systems have the notion of multiple branches in a repo that exist in the same location. For example Git and CVS use this while systems like Darcs use different locations for different branches. This field is optional but should be used if necessary to identify the sources, especially for the RepoThis repo kind.

  • repoTag :: Maybe String

    The tag identify a particular state of the repository. This should be given for the RepoThis repo kind and not for RepoHead kind.

  • repoSubdir :: Maybe FilePath

    Some repositories contain multiple projects in different subdirectories This field specifies the subdirectory where this packages sources can be found, eg the subdirectory containing the .cabal file. It is interpreted relative to the root of the repository. This field is optional. If not given the default is "." ie no subdirectory.

Instances

Eq SourceRepo Source # 
Data SourceRepo Source # 

Methods

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

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

toConstr :: SourceRepo -> Constr #

dataTypeOf :: SourceRepo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SourceRepo Source # 
Show SourceRepo Source # 
Generic SourceRepo Source # 

Associated Types

type Rep SourceRepo :: * -> * #

Binary SourceRepo Source # 
type Rep SourceRepo Source # 

data RepoKind Source #

What this repo info is for, what it represents.

Constructors

RepoHead

The repository for the "head" or development version of the project. This repo is where we should track the latest development activity or the usual repo people should get to contribute patches.

RepoThis

The repository containing the sources for this exact package version or release. For this kind of repo a tag should be given to give enough information to re-create the exact sources.

RepoKindUnknown String 

Instances

Eq RepoKind Source # 
Data RepoKind Source # 

Methods

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

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

toConstr :: RepoKind -> Constr #

dataTypeOf :: RepoKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoKind Source # 
Read RepoKind Source # 
Show RepoKind Source # 
Generic RepoKind Source # 

Associated Types

type Rep RepoKind :: * -> * #

Methods

from :: RepoKind -> Rep RepoKind x #

to :: Rep RepoKind x -> RepoKind #

Binary RepoKind Source # 

Methods

put :: RepoKind -> Put #

get :: Get RepoKind #

putList :: [RepoKind] -> Put #

Text RepoKind Source # 
type Rep RepoKind Source # 
type Rep RepoKind = D1 (MetaData "RepoKind" "Distribution.Types.SourceRepo" "Cabal-2.0.0.2-B4YxsRmpeLCDyDZ1N9nEz7" False) ((:+:) (C1 (MetaCons "RepoHead" PrefixI False) U1) ((:+:) (C1 (MetaCons "RepoThis" PrefixI False) U1) (C1 (MetaCons "RepoKindUnknown" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

data RepoType Source #

An enumeration of common source control systems. The fields used in the SourceRepo depend on the type of repo. The tools and methods used to obtain and track the repo depend on the repo type.

Instances

Eq RepoType Source # 
Data RepoType Source # 

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 :: (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 Source # 
Read RepoType Source # 
Show RepoType Source # 
Generic RepoType Source # 

Associated Types

type Rep RepoType :: * -> * #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

Binary RepoType Source # 

Methods

put :: RepoType -> Put #

get :: Get RepoType #

putList :: [RepoType] -> Put #

Text RepoType Source # 
type Rep RepoType Source # 
type Rep RepoType = D1 (MetaData "RepoType" "Distribution.Types.SourceRepo" "Cabal-2.0.0.2-B4YxsRmpeLCDyDZ1N9nEz7" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Darcs" PrefixI False) U1) (C1 (MetaCons "Git" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SVN" PrefixI False) U1) (C1 (MetaCons "CVS" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Mercurial" PrefixI False) U1) (C1 (MetaCons "GnuArch" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Bazaar" PrefixI False) U1) ((:+:) (C1 (MetaCons "Monotone" PrefixI False) U1) (C1 (MetaCons "OtherRepoType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))