| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Types.PackageIndex
Synopsis
- data PackageDownload = PackageDownload {
- pdSHA256 :: !StaticSHA256
 - pdUrl :: !ByteString
 - pdSize :: !Word64
 
 - newtype HSPackageDownload = HSPackageDownload {}
 - newtype PackageCache index = PackageCache (HashMap PackageName (HashMap Version (index, Maybe PackageDownload, NonEmpty ([CabalHash], OffsetSize))))
 - data OffsetSize = OffsetSize !Int64 !Int64
 - data PackageIndex = PackageIndex {
- indexName :: !IndexName
 - indexLocation :: !Text
 - indexType :: !IndexType
 - indexDownloadPrefix :: !Text
 - indexRequireHashes :: !Bool
 
 - newtype IndexName = IndexName {}
 - indexNameText :: IndexName -> Text
 - data IndexType
 - data HackageSecurity = HackageSecurity {
- hsKeyIds :: ![Text]
 - hsKeyThreshold :: !Int
 
 
Documentation
data PackageDownload Source #
Constructors
| PackageDownload | |
Fields 
  | |
Instances
newtype HSPackageDownload Source #
Hackage Security provides a different JSON format, we'll have our own JSON parser for it.
Constructors
| HSPackageDownload | |
Fields  | |
Instances
| FromJSON HSPackageDownload Source # | |
Defined in Stack.Types.PackageIndex Methods parseJSON :: Value -> Parser HSPackageDownload # parseJSONList :: Value -> Parser [HSPackageDownload] #  | |
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.
Constructors
| PackageCache (HashMap PackageName (HashMap Version (index, Maybe PackageDownload, NonEmpty ([CabalHash], OffsetSize)))) | 
Instances
| Eq index => Eq (PackageCache index) Source # | |
Defined in Stack.Types.PackageIndex Methods (==) :: PackageCache index -> PackageCache index -> Bool # (/=) :: PackageCache index -> PackageCache index -> Bool #  | |
| Data index => Data (PackageCache index) Source # | |
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 # | |
Defined in Stack.Types.PackageIndex Methods showsPrec :: Int -> PackageCache index -> ShowS # show :: PackageCache index -> String # showList :: [PackageCache index] -> ShowS #  | |
| Generic (PackageCache index) Source # | |
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 # | |
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 # | |
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 # | |
Defined in Stack.Types.PackageIndex Methods rnf :: PackageCache index -> () #  | |
| Store index => Store (PackageCache index) Source # | |
Defined in Stack.Types.PackageIndex Methods size :: Size (PackageCache index) # poke :: PackageCache index -> Poke () # peek :: Peek (PackageCache index) #  | |
| type Rep (PackageCache index) Source # | |
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
PackageIndex, IndexName & IndexLocation
data PackageIndex Source #
Information on a single package index
Constructors
| PackageIndex | |
Fields 
  | |
Instances
| Show PackageIndex Source # | |
Defined in Stack.Types.PackageIndex Methods showsPrec :: Int -> PackageIndex -> ShowS # show :: PackageIndex -> String # showList :: [PackageIndex] -> ShowS #  | |
| FromJSON (WithJSONWarnings PackageIndex) Source # | |
Defined in Stack.Types.PackageIndex Methods parseJSON :: Value -> Parser (WithJSONWarnings PackageIndex) # parseJSONList :: Value -> Parser [WithJSONWarnings PackageIndex] #  | |
Unique name for a package index
Constructors
| IndexName | |
Fields  | |
Instances
| Eq IndexName Source # | |
| Ord IndexName Source # | |
| Show IndexName Source # | |
| Hashable IndexName Source # | |
Defined in Stack.Types.PackageIndex  | |
| ToJSON IndexName Source # | |
Defined in Stack.Types.PackageIndex  | |
| FromJSON IndexName Source # | |
| Store IndexName Source # | |
indexNameText :: IndexName -> Text Source #
Constructors
| ITHackageSecurity !HackageSecurity | |
| ITVanilla | 
Instances
| Eq IndexType Source # | |
| Ord IndexType Source # | |
| Show IndexType Source # | |
data HackageSecurity Source #
Constructors
| HackageSecurity | |
Fields 
  | |