cabal-install-3.10.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.Types.Repo

Synopsis

Remote repository

data RemoteRepo Source #

Constructors

RemoteRepo 

Fields

  • remoteRepoName :: RepoName
     
  • remoteRepoURI :: URI
     
  • remoteRepoSecure :: Maybe Bool

    Enable secure access?

    Nothing here represents "whatever the default is"; this is important to allow for a smooth transition from opt-in to opt-out security (once we switch to opt-out, all access to the central Hackage repository should be secure by default)

  • remoteRepoRootKeys :: [String]

    Root key IDs (for bootstrapping)

  • remoteRepoKeyThreshold :: Int

    Threshold for verification during bootstrapping

  • remoteRepoShouldTryHttps :: Bool

    Normally a repo just specifies an HTTP or HTTPS URI, but as a special case we may know a repo supports both and want to try HTTPS if we can, but still allow falling back to HTTP.

    This field is not currently stored in the config file, but is filled in automagically for known repos.

Instances

Instances details
Parsec RemoteRepo Source #

Note: serialised format represents RemoteRepo only partially.

Instance details

Defined in Distribution.Client.Types.Repo

Methods

parsec :: CabalParsing m => m RemoteRepo #

Pretty RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Structured RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Generic RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Associated Types

type Rep RemoteRepo :: Type -> Type #

Show RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Binary RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Eq RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Ord RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

type Rep RemoteRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

type Rep RemoteRepo = D1 ('MetaData "RemoteRepo" "Distribution.Client.Types.Repo" "cabal-install-3.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" 'False) (C1 ('MetaCons "RemoteRepo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "remoteRepoName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RepoName) :*: (S1 ('MetaSel ('Just "remoteRepoURI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URI) :*: S1 ('MetaSel ('Just "remoteRepoSecure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "remoteRepoRootKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "remoteRepoKeyThreshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "remoteRepoShouldTryHttps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

emptyRemoteRepo :: RepoName -> RemoteRepo Source #

Construct a partial RemoteRepo value to fold the field parser list over.

Local repository (no-index)

data LocalRepo Source #

no-index style local repositories.

https://github.com/haskell/cabal/issues/6359

Instances

Instances details
Parsec LocalRepo Source #

Note: doesn't parse localRepoSharedCache field.

Instance details

Defined in Distribution.Client.Types.Repo

Methods

parsec :: CabalParsing m => m LocalRepo #

Pretty LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Structured LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Generic LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Associated Types

type Rep LocalRepo :: Type -> Type #

Show LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Binary LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Eq LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Ord LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

type Rep LocalRepo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

type Rep LocalRepo = D1 ('MetaData "LocalRepo" "Distribution.Client.Types.Repo" "cabal-install-3.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" '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

data Repo Source #

Different kinds of repositories

NOTE: It is important that this type remains serializable.

Constructors

RepoLocalNoIndex

Local repository, without index.

https://github.com/haskell/cabal/issues/6359

RepoRemote

Standard (unsecured) remote repositories

RepoSecure

Secure repositories

Although this contains the same fields as RepoRemote, we use a separate constructor to avoid confusing the two.

Not all access to a secure repo goes through the hackage-security library currently; code paths that do not still make use of the repoRemote and repoLocalDir fields directly.

Instances

Instances details
Structured Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Generic Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Associated Types

type Rep Repo :: Type -> Type #

Methods

from :: Repo -> Rep Repo x #

to :: Rep Repo x -> Repo #

Show Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

Binary Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Methods

put :: Repo -> Put #

get :: Get Repo #

putList :: [Repo] -> Put #

Eq Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Methods

(==) :: Repo -> Repo -> Bool #

(/=) :: Repo -> Repo -> Bool #

Ord Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

Methods

compare :: Repo -> Repo -> Ordering #

(<) :: Repo -> Repo -> Bool #

(<=) :: Repo -> Repo -> Bool #

(>) :: Repo -> Repo -> Bool #

(>=) :: Repo -> Repo -> Bool #

max :: Repo -> Repo -> Repo #

min :: Repo -> Repo -> Repo #

type Rep Repo Source # 
Instance details

Defined in Distribution.Client.Types.Repo

type Rep Repo = D1 ('MetaData "Repo" "Distribution.Client.Types.Repo" "cabal-install-3.10.1.0-FbhGUvZ0l0XIx7QbOQfSVh" 'False) (C1 ('MetaCons "RepoLocalNoIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoLocal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalRepo) :*: S1 ('MetaSel ('Just "repoLocalDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: (C1 ('MetaCons "RepoRemote" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoRemote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemoteRepo) :*: S1 ('MetaSel ('Just "repoLocalDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "RepoSecure" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoRemote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RemoteRepo) :*: S1 ('MetaSel ('Just "repoLocalDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))))

isRepoRemote :: Repo -> Bool Source #

Check if this is a remote repo

maybeRepoRemote :: Repo -> Maybe RemoteRepo Source #

Extract RemoteRepo from Repo if remote.