Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- indexMetadata :: FilePath -> Maybe EpochTime -> IO (Map PackageName PackageInfo)
- cachedHackageMetadata :: IO (FilePath, Map PackageName PackageInfo)
- data MetadataParseError = MetadataParseError FilePath String
- data InvalidHash = InvalidHash PackageName Version String
- newtype InvalidIndexFile = InvalidIndexFile String
- data NoHackageRepository = NoHackageRepository
- data PackageInfo = PackageInfo {}
- piPreferredVersions :: PackageInfo -> Map Version ReleaseInfo
- data ReleaseInfo = ReleaseInfo {
- riRevision :: !Word32
- riTarOffset :: !TarEntryOffset
- riCabal :: !SHA256
- riTarball :: !SHA256
- data SHA256 = SHA256 !Word64 !Word64 !Word64 !Word64
- sha256 :: ByteString -> SHA256
- mkSHA256 :: Text -> Either String SHA256
- unsafeMkSHA256 :: Text -> SHA256
- getSHA256 :: SHA256 -> ByteString
- foldIndex :: FilePath -> a -> (IndexEntry -> ByteString -> a -> IO a) -> IO a
- data IndexEntry = IndexEntry {}
- data IndexFileType
Metadata construction
:: FilePath | location |
-> Maybe EpochTime | index state to stop |
-> IO (Map PackageName PackageInfo) |
Read index file and return the metadata about packages.
It takes about 6 seconds on my machine. Consider using cachedHackageMetadata
.
cachedHackageMetadata :: IO (FilePath, Map PackageName PackageInfo) Source #
Read the config and then Hackage index metadata.
This method caches the result in XDG_CACHE/cabal-parsers
directory.
Returns the location of index tarball and its contents.
Exceptions thrown
data MetadataParseError Source #
Thrown when we cannot parse package.json
or preferred-versions
files.
Instances
Show MetadataParseError Source # | |
Defined in Cabal.Index showsPrec :: Int -> MetadataParseError -> ShowS # show :: MetadataParseError -> String # showList :: [MetadataParseError] -> ShowS # | |
Exception MetadataParseError Source # | |
Defined in Cabal.Index |
data InvalidHash Source #
Thrown if we fail consistency check, we don't know a hash for some file.
Instances
Show InvalidHash Source # | |
Defined in Cabal.Index showsPrec :: Int -> InvalidHash -> ShowS # show :: InvalidHash -> String # showList :: [InvalidHash] -> ShowS # | |
Exception InvalidHash Source # | |
Defined in Cabal.Index |
newtype InvalidIndexFile Source #
Thrown when when not a .cabal
, package.json
or preferred-versions
file is encountered.
Instances
Show InvalidIndexFile Source # | |
Defined in Cabal.Index showsPrec :: Int -> InvalidIndexFile -> ShowS # show :: InvalidIndexFile -> String # showList :: [InvalidIndexFile] -> ShowS # | |
Exception InvalidIndexFile Source # | |
Defined in Cabal.Index |
data NoHackageRepository Source #
Instances
Show NoHackageRepository Source # | |
Defined in Cabal.Index showsPrec :: Int -> NoHackageRepository -> ShowS # show :: NoHackageRepository -> String # showList :: [NoHackageRepository] -> ShowS # | |
Exception NoHackageRepository Source # | |
Defined in Cabal.Index |
Metadata types
data PackageInfo Source #
Package information.
PackageInfo | |
|
Instances
Eq PackageInfo Source # | |
Defined in Cabal.Index (==) :: PackageInfo -> PackageInfo -> Bool # (/=) :: PackageInfo -> PackageInfo -> Bool # | |
Show PackageInfo Source # | |
Defined in Cabal.Index showsPrec :: Int -> PackageInfo -> ShowS # show :: PackageInfo -> String # showList :: [PackageInfo] -> ShowS # | |
Generic PackageInfo Source # | |
Defined in Cabal.Index type Rep PackageInfo :: Type -> Type # from :: PackageInfo -> Rep PackageInfo x # to :: Rep PackageInfo x -> PackageInfo # | |
Binary PackageInfo Source # | |
Defined in Cabal.Index | |
type Rep PackageInfo Source # | |
Defined in Cabal.Index type Rep PackageInfo = D1 (MetaData "PackageInfo" "Cabal.Index" "cabal-install-parsers-0.4-w4mTgtw0tJ6iqwagB75LL" False) (C1 (MetaCons "PackageInfo" PrefixI True) (S1 (MetaSel (Just "piVersions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Version ReleaseInfo)) :*: S1 (MetaSel (Just "piPreferred") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange))) |
piPreferredVersions :: PackageInfo -> Map Version ReleaseInfo Source #
Like piVersions
, but return only piPreferred
versions.
data ReleaseInfo Source #
Package's release information.
ReleaseInfo | |
|
Instances
Hashes
SHA256 digest. 256 bytes.
sha256 :: ByteString -> SHA256 Source #
Hash strict ByteString
.
getSHA256 :: SHA256 -> ByteString Source #
Get ByteString
representation of SHA256
.
Generic folding
:: FilePath | path to the |
-> a | initial value |
-> (IndexEntry -> ByteString -> a -> IO a) | |
-> IO a |
Fold over Hackage 01-index.tar
file.
May throw FormatError
or InvalidIndexFile
.
data IndexEntry Source #
IndexEntry | |
|
Instances
Show IndexEntry Source # | |
Defined in Cabal.Index showsPrec :: Int -> IndexEntry -> ShowS # show :: IndexEntry -> String # showList :: [IndexEntry] -> ShowS # |
data IndexFileType Source #
Varions files in 01-index.tar
.
Instances
Show IndexFileType Source # | |
Defined in Cabal.Index showsPrec :: Int -> IndexFileType -> ShowS # show :: IndexFileType -> String # showList :: [IndexFileType] -> ShowS # |