| Copyright | (c) David Himmelstrup 2005 Duncan Coutts 2011 |
|---|---|
| License | BSD-like |
| Maintainer | cabal-devel@haskell.org |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Distribution.Client.Types
Description
Various common data types for the entire cabal-install system
Synopsis
- newtype AllowNewer = AllowNewer {}
- newtype AllowOlder = AllowOlder {}
- data RelaxDeps
- mkRelaxDepSome :: [RelaxedDep] -> RelaxDeps
- data RelaxDepMod
- data RelaxDepScope
- = RelaxDepScopeAll
- | RelaxDepScopePackage !PackageName
- | RelaxDepScopePackageId !PackageId
- data RelaxDepSubject
- = RelaxDepSubjectAll
- | RelaxDepSubjectPkg !PackageName
- data RelaxedDep = RelaxedDep !RelaxDepScope !RelaxDepMod !RelaxDepSubject
- isRelaxDeps :: RelaxDeps -> Bool
- type InstalledPackageId = ComponentId
- data ConfiguredId = ConfiguredId {
- confSrcId :: PackageId
- confCompName :: Maybe ComponentName
- confInstId :: ComponentId
- annotatedIdToConfiguredId :: AnnotatedId ComponentId -> ConfiguredId
- class HasConfiguredId a where
- configuredId :: a -> ConfiguredId
- data ConfiguredPackage loc = ConfiguredPackage {
- confPkgId :: InstalledPackageId
- confPkgSource :: SourcePackage loc
- confPkgFlags :: FlagAssignment
- confPkgStanzas :: [OptionalStanza]
- confPkgDeps :: ComponentDeps [ConfiguredId]
- type BuildOutcome = Either BuildFailure BuildResult
- type BuildOutcomes = Map UnitId BuildOutcome
- data BuildFailure
- data BuildResult = BuildResult DocsResult TestsResult (Maybe InstalledPackageInfo)
- data TestsResult
- data DocsResult
- data PackageLocation local
- = LocalUnpackedPackage FilePath
- | LocalTarballPackage FilePath
- | RemoteTarballPackage URI local
- | RepoTarballPackage Repo PackageId local
- | RemoteSourceRepoPackage SourceRepoMaybe local
- type UnresolvedPkgLoc = PackageLocation (Maybe FilePath)
- type ResolvedPkgLoc = PackageLocation FilePath
- type UnresolvedSourcePackage = SourcePackage UnresolvedPkgLoc
- data PackageSpecifier pkg
- = NamedPackage PackageName [PackageProperty]
- | SpecificSourcePackage pkg
- pkgSpecifierTarget :: Package pkg => PackageSpecifier pkg -> PackageName
- pkgSpecifierConstraints :: Package pkg => PackageSpecifier pkg -> [LabeledPackageConstraint]
- newtype GenericReadyPackage srcpkg = ReadyPackage srcpkg
- type ReadyPackage = GenericReadyPackage (ConfiguredPackage UnresolvedPkgLoc)
- data RemoteRepo = RemoteRepo {}
- emptyRemoteRepo :: RepoName -> RemoteRepo
- data LocalRepo = LocalRepo {}
- emptyLocalRepo :: RepoName -> LocalRepo
- localRepoCacheKey :: LocalRepo -> String
- data Repo
- = RepoLocalNoIndex { }
- | RepoRemote { }
- | RepoSecure { }
- isRepoRemote :: Repo -> Bool
- maybeRepoRemote :: Repo -> Maybe RemoteRepo
- newtype RepoName = RepoName String
- unRepoName :: RepoName -> String
- data SourcePackageDb = SourcePackageDb {
- packageIndex :: PackageIndex UnresolvedSourcePackage
- packagePreferences :: Map PackageName VersionRange
- data WriteGhcEnvironmentFilesPolicy
Documentation
newtype AllowNewer Source #
RelaxDeps in the context of upper bounds (i.e. for --allow-newer flag)
Constructors
| AllowNewer | |
Fields | |
Instances
newtype AllowOlder Source #
RelaxDeps in the context of lower bounds (i.e. for --allow-older flag)
Constructors
| AllowOlder | |
Fields | |
Instances
Generic data type for policy when relaxing bounds in dependencies.
Don't use this directly: use AllowOlder or AllowNewer depending
on whether or not you are relaxing an lower or upper bound
(respectively).
Constructors
| RelaxDepsSome [RelaxedDep] | Ignore upper (resp. lower) bounds in some (or no) dependencies on the given packages.
|
| RelaxDepsAll | Ignore upper (resp. lower) bounds in dependencies on all packages. Note: This is should be semantically equivalent to RelaxDepsSome [RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll] (TODO: consider normalising |
Instances
| Eq RelaxDeps Source # | |
| Read RelaxDeps Source # | |
| Show RelaxDeps Source # | |
| Generic RelaxDeps Source # | |
| Semigroup RelaxDeps Source # |
|
| Monoid RelaxDeps Source # |
|
| Binary RelaxDeps Source # | |
| Structured RelaxDeps Source # | |
Defined in Distribution.Client.Types.AllowNewer | |
| Parsec RelaxDeps Source # |
This is not a glitch, even it looks like:
|
Defined in Distribution.Client.Types.AllowNewer | |
| Pretty RelaxDeps Source # | |
Defined in Distribution.Client.Types.AllowNewer | |
| type Rep RelaxDeps Source # | |
Defined in Distribution.Client.Types.AllowNewer type Rep RelaxDeps = D1 ('MetaData "RelaxDeps" "Distribution.Client.Types.AllowNewer" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "RelaxDepsSome" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelaxedDep])) :+: C1 ('MetaCons "RelaxDepsAll" 'PrefixI 'False) (U1 :: Type -> Type)) | |
mkRelaxDepSome :: [RelaxedDep] -> RelaxDeps Source #
A smarter RelaxedDepsSome, *:* is the same as all.
data RelaxDepMod Source #
Modifier for dependency relaxation
Constructors
| RelaxDepModNone | Default semantics |
| RelaxDepModCaret | Apply relaxation only to |
Instances
data RelaxDepScope Source #
Specify the scope of a relaxation, i.e. limit which depending packages are allowed to have their version constraints relaxed.
Constructors
| RelaxDepScopeAll | Apply relaxation in any package |
| RelaxDepScopePackage !PackageName | Apply relaxation to in all versions of a package |
| RelaxDepScopePackageId !PackageId | Apply relaxation to a specific version of a package only |
Instances
data RelaxDepSubject Source #
Express whether to relax bounds on all packages, or a single package
Constructors
| RelaxDepSubjectAll | |
| RelaxDepSubjectPkg !PackageName |
Instances
data RelaxedDep Source #
Dependencies can be relaxed either for all packages in the install plan, or only for some packages.
Constructors
| RelaxedDep !RelaxDepScope !RelaxDepMod !RelaxDepSubject |
Instances
isRelaxDeps :: RelaxDeps -> Bool Source #
type InstalledPackageId = ComponentId Source #
Within Cabal the library we no longer have a InstalledPackageId type.
That's because it deals with the compilers' notion of a registered library,
and those really are libraries not packages. Those are now named units.
The package management layer does however deal with installed packages, as whole packages not just as libraries. So we do still need a type for installed package ids. At the moment however we track instaled packages via their primary library, which is a unit id. In future this may change slightly and we may distinguish these two types and have an explicit conversion when we register units with the compiler.
data ConfiguredId Source #
A ConfiguredId is a package ID for a configured package.
Once we configure a source package we know its UnitId. It is still however useful in lots of places to also know the source ID for the package. We therefore bundle the two.
An already installed package of course is also "configured" (all its configuration parameters and dependencies have been specified).
Constructors
| ConfiguredId | |
Fields
| |
Instances
annotatedIdToConfiguredId :: AnnotatedId ComponentId -> ConfiguredId Source #
class HasConfiguredId a where Source #
Methods
configuredId :: a -> ConfiguredId Source #
Instances
| HasConfiguredId InstalledPackageInfo Source # | |
Defined in Distribution.Client.Types.ConfiguredId Methods configuredId :: InstalledPackageInfo -> ConfiguredId Source # | |
| HasConfiguredId (ConfiguredPackage loc) Source # |
|
Defined in Distribution.Client.Types.ConfiguredPackage Methods configuredId :: ConfiguredPackage loc -> ConfiguredId Source # | |
data ConfiguredPackage loc Source #
A ConfiguredPackage is a not-yet-installed package along with the
total configuration information. The configuration information is total in
the sense that it provides all the configuration information and so the
final configure process will be independent of the environment.
ConfiguredPackage is assumed to not support Backpack. Only the
v2-build codepath supports Backpack.
Constructors
| ConfiguredPackage | |
Fields
| |
Instances
type BuildOutcome = Either BuildFailure BuildResult Source #
A summary of the outcome for building a single package.
type BuildOutcomes = Map UnitId BuildOutcome Source #
A summary of the outcome for building a whole set of packages.
data BuildFailure Source #
Constructors
Instances
data BuildResult Source #
Constructors
| BuildResult DocsResult TestsResult (Maybe InstalledPackageInfo) |
Instances
data TestsResult Source #
Constructors
| TestsNotTried | |
| TestsOk |
Instances
| Show TestsResult Source # | |
Defined in Distribution.Client.Types.BuildResults Methods showsPrec :: Int -> TestsResult -> ShowS # show :: TestsResult -> String # showList :: [TestsResult] -> ShowS # | |
| Generic TestsResult Source # | |
Defined in Distribution.Client.Types.BuildResults Associated Types type Rep TestsResult :: Type -> Type # | |
| Binary TestsResult Source # | |
Defined in Distribution.Client.Types.BuildResults | |
| Structured TestsResult Source # | |
Defined in Distribution.Client.Types.BuildResults | |
| type Rep TestsResult Source # | |
Defined in Distribution.Client.Types.BuildResults type Rep TestsResult = D1 ('MetaData "TestsResult" "Distribution.Client.Types.BuildResults" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "TestsNotTried" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TestsOk" 'PrefixI 'False) (U1 :: Type -> Type)) | |
data DocsResult Source #
Constructors
| DocsNotTried | |
| DocsFailed | |
| DocsOk |
Instances
| Show DocsResult Source # | |
Defined in Distribution.Client.Types.BuildResults Methods showsPrec :: Int -> DocsResult -> ShowS # show :: DocsResult -> String # showList :: [DocsResult] -> ShowS # | |
| Generic DocsResult Source # | |
Defined in Distribution.Client.Types.BuildResults Associated Types type Rep DocsResult :: Type -> Type # | |
| Binary DocsResult Source # | |
Defined in Distribution.Client.Types.BuildResults | |
| Structured DocsResult Source # | |
Defined in Distribution.Client.Types.BuildResults | |
| type Rep DocsResult Source # | |
Defined in Distribution.Client.Types.BuildResults type Rep DocsResult = D1 ('MetaData "DocsResult" "Distribution.Client.Types.BuildResults" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "DocsNotTried" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DocsFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DocsOk" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data PackageLocation local Source #
Constructors
| LocalUnpackedPackage FilePath | An unpacked package in the given dir, or current dir |
| LocalTarballPackage FilePath | A package as a tarball that's available as a local tarball |
| RemoteTarballPackage URI local | A package as a tarball from a remote URI |
| RepoTarballPackage Repo PackageId local | A package available as a tarball from a repository. It may be from a local repository or from a remote repository, with a locally cached copy. ie a package available from hackage |
| RemoteSourceRepoPackage SourceRepoMaybe local | A package available from a version control system source repository |
Instances
type UnresolvedPkgLoc = PackageLocation (Maybe FilePath) Source #
type ResolvedPkgLoc = PackageLocation FilePath Source #
type UnresolvedSourcePackage = SourcePackage UnresolvedPkgLoc Source #
Convenience alias for 'SourcePackage UnresolvedPkgLoc'.
data PackageSpecifier pkg Source #
A fully or partially resolved reference to a package.
Constructors
| NamedPackage PackageName [PackageProperty] | A partially specified reference to a package (either source or installed). It is specified by package name and optionally some required properties. Use a dependency resolver to pick a specific package satisfying these properties. |
| SpecificSourcePackage pkg | A fully specified source package. |
Instances
pkgSpecifierTarget :: Package pkg => PackageSpecifier pkg -> PackageName Source #
pkgSpecifierConstraints :: Package pkg => PackageSpecifier pkg -> [LabeledPackageConstraint] Source #
newtype GenericReadyPackage srcpkg Source #
Like ConfiguredPackage, but with all dependencies guaranteed to be
installed already, hence itself ready to be installed.
Constructors
| ReadyPackage srcpkg |
Instances
Remote repository
data RemoteRepo Source #
Constructors
| RemoteRepo | |
Fields
| |
Instances
emptyRemoteRepo :: RepoName -> RemoteRepo Source #
Construct a partial RemoteRepo value to fold the field parser list over.
Local repository (no-index)
no-index style local repositories.
Constructors
| LocalRepo | |
Fields | |
Instances
| Eq LocalRepo Source # | |
| Ord LocalRepo Source # | |
| Show LocalRepo Source # | |
| Generic LocalRepo Source # | |
| Binary LocalRepo Source # | |
| Structured LocalRepo Source # | |
Defined in Distribution.Client.Types.Repo | |
| Parsec LocalRepo Source # | Note: doesn't parse |
Defined in Distribution.Client.Types.Repo | |
| Pretty LocalRepo Source # | |
Defined in Distribution.Client.Types.Repo | |
| type Rep LocalRepo Source # | |
Defined in Distribution.Client.Types.Repo type Rep LocalRepo = D1 ('MetaData "LocalRepo" "Distribution.Client.Types.Repo" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "LocalRepo" 'PrefixI 'True) (S1 ('MetaSel ('Just "localRepoName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RepoName) :*: (S1 ('MetaSel ('Just "localRepoPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "localRepoSharedCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) | |
emptyLocalRepo :: RepoName -> LocalRepo Source #
Construct a partial LocalRepo value to fold the field parser list over.
localRepoCacheKey :: LocalRepo -> String Source #
Calculate a cache key for local-repo.
For remote repositories we just use name, but local repositories may
all be named "local", so we add a bit of localRepoPath into the
mix.
Repository
Different kinds of repositories
NOTE: It is important that this type remains serializable.
Constructors
| RepoLocalNoIndex | Local repository, without index. |
Fields | |
| RepoRemote | Standard (unsecured) remote repositores |
Fields | |
| RepoSecure | Secure repositories Although this contains the same fields as Not all access to a secure repo goes through the hackage-security
library currently; code paths that do not still make use of the
|
Fields | |
Instances
isRepoRemote :: Repo -> Bool Source #
Check if this is a remote repo
maybeRepoRemote :: Repo -> Maybe RemoteRepo Source #
Extract RemoteRepo from Repo if remote.
Repository name.
May be used as path segment.
Instances
| Eq RepoName Source # | |
| Ord RepoName Source # | |
Defined in Distribution.Client.Types.RepoName | |
| Show RepoName Source # | |
| Generic RepoName Source # | |
| Binary RepoName Source # | |
| NFData RepoName Source # | |
Defined in Distribution.Client.Types.RepoName | |
| Structured RepoName Source # | |
Defined in Distribution.Client.Types.RepoName | |
| Parsec RepoName Source # |
|
Defined in Distribution.Client.Types.RepoName | |
| Pretty RepoName Source # | |
Defined in Distribution.Client.Types.RepoName | |
| type Rep RepoName Source # | |
Defined in Distribution.Client.Types.RepoName type Rep RepoName = D1 ('MetaData "RepoName" "Distribution.Client.Types.RepoName" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'True) (C1 ('MetaCons "RepoName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) | |
unRepoName :: RepoName -> String Source #
data SourcePackageDb Source #
This is the information we get from a 00-index.tar.gz hackage index.
Constructors
| SourcePackageDb | |
Fields
| |
Instances
data WriteGhcEnvironmentFilesPolicy Source #
Whether 'v2-build' should write a .ghc.environment file after
success. Possible values: always, never (the default), 'ghc8.4.4+'
(8.4.4 is the earliest version that supports
'-package-env -').
Constructors
| AlwaysWriteGhcEnvironmentFiles | |
| NeverWriteGhcEnvironmentFiles | |
| WriteGhcEnvironmentFilesOnlyForGhc844AndNewer |