stack-1.9.3: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.PackageIndex

Contents

Synopsis

Documentation

data PackageDownload Source #

Instances
Eq PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Data PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

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

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

toConstr :: PackageDownload -> Constr #

dataTypeOf :: PackageDownload -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Generic PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Associated Types

type Rep PackageDownload :: Type -> Type #

NFData PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

rnf :: PackageDownload -> () #

FromJSON PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

Store PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

type Rep PackageDownload Source # 
Instance details

Defined in Stack.Types.PackageIndex

type Rep PackageDownload = D1 (MetaData "PackageDownload" "Stack.Types.PackageIndex" "stack-1.9.3-A8b1pQY9CjdHmL7IWv3q9b" False) (C1 (MetaCons "PackageDownload" PrefixI True) (S1 (MetaSel (Just "pdSHA256") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StaticSHA256) :*: (S1 (MetaSel (Just "pdUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "pdSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64))))

newtype HSPackageDownload Source #

Hackage Security provides a different JSON format, we'll have our own JSON parser for it.

newtype PackageCache index Source #

Cached information about packages in an index. We have a mapping from package name to a version map. Within the version map, we map from the version to information on an individual version. Each version has optional download information (about the package's tarball itself), and cabal file information. The cabal file information is a non-empty list of all cabal file revisions. Each file revision indicates the hash of the contents of the cabal file, and the offset into the index tarball.

The reason for each Version mapping to a two element list of CabalHashes is because some older Stackage snapshots have CRs in their cabal files. For compatibility with these older snapshots, both hashes are stored: the first element of the two element list being the original hash, and the (potential) second element with the CRs stripped. [Note: This is was initially stored as a two element list, and cannot be easily packed into more explict ADT or newtype because of some template-haskell that would need to be modified as well: the versionedDecodeOrLoad function call found in the getPackageCaches function in PackageIndex.]

It's assumed that cabal files appear in the index tarball in the correct revision order.

Instances
Eq index => Eq (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

(==) :: PackageCache index -> PackageCache index -> Bool #

(/=) :: PackageCache index -> PackageCache index -> Bool #

Data index => Data (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

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

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

toConstr :: PackageCache index -> Constr #

dataTypeOf :: PackageCache index -> DataType #

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

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

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

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

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

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

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

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

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

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

Show index => Show (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

showsPrec :: Int -> PackageCache index -> ShowS #

show :: PackageCache index -> String #

showList :: [PackageCache index] -> ShowS #

Generic (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Associated Types

type Rep (PackageCache index) :: Type -> Type #

Methods

from :: PackageCache index -> Rep (PackageCache index) x #

to :: Rep (PackageCache index) x -> PackageCache index #

Semigroup (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

(<>) :: PackageCache index -> PackageCache index -> PackageCache index #

sconcat :: NonEmpty (PackageCache index) -> PackageCache index #

stimes :: Integral b => b -> PackageCache index -> PackageCache index #

Monoid (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

mempty :: PackageCache index #

mappend :: PackageCache index -> PackageCache index -> PackageCache index #

mconcat :: [PackageCache index] -> PackageCache index #

NFData index => NFData (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

rnf :: PackageCache index -> () #

Store index => Store (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

size :: Size (PackageCache index) #

poke :: PackageCache index -> Poke () #

peek :: Peek (PackageCache index) #

type Rep (PackageCache index) Source # 
Instance details

Defined in Stack.Types.PackageIndex

type Rep (PackageCache index) = D1 (MetaData "PackageCache" "Stack.Types.PackageIndex" "stack-1.9.3-A8b1pQY9CjdHmL7IWv3q9b" True) (C1 (MetaCons "PackageCache" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap PackageName (HashMap Version (index, Maybe PackageDownload, NonEmpty ([CabalHash], OffsetSize)))))))

data OffsetSize Source #

offset in bytes into the 01-index.tar file for the .cabal file contents, and size in bytes of the .cabal file

Constructors

OffsetSize !Int64 !Int64 
Instances
Eq OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

Data OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

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

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

toConstr :: OffsetSize -> Constr #

dataTypeOf :: OffsetSize -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

Generic OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

Associated Types

type Rep OffsetSize :: Type -> Type #

NFData OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

Methods

rnf :: OffsetSize -> () #

Store OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

type Rep OffsetSize Source # 
Instance details

Defined in Stack.Types.PackageIndex

type Rep OffsetSize = D1 (MetaData "OffsetSize" "Stack.Types.PackageIndex" "stack-1.9.3-A8b1pQY9CjdHmL7IWv3q9b" False) (C1 (MetaCons "OffsetSize" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64)))

PackageIndex, IndexName & IndexLocation

data PackageIndex Source #

Information on a single package index

Constructors

PackageIndex 

Fields

newtype IndexName Source #

Unique name for a package index

Constructors

IndexName