| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Cabal.Index
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
Arguments
| :: 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.
Constructors
| MetadataParseError FilePath String | 
Instances
| Show MetadataParseError Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> MetadataParseError -> ShowS # show :: MetadataParseError -> String # showList :: [MetadataParseError] -> ShowS # | |
| Exception MetadataParseError Source # | |
| Defined in Cabal.Index Methods toException :: MetadataParseError -> SomeException # fromException :: SomeException -> Maybe MetadataParseError # | |
data InvalidHash Source #
Thrown if we fail consistency check, we don't know a hash for some file.
Constructors
| InvalidHash PackageName Version String | 
Instances
| Show InvalidHash Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> InvalidHash -> ShowS # show :: InvalidHash -> String # showList :: [InvalidHash] -> ShowS # | |
| Exception InvalidHash Source # | |
| Defined in Cabal.Index Methods toException :: InvalidHash -> SomeException # fromException :: SomeException -> Maybe InvalidHash # displayException :: InvalidHash -> String # | |
newtype InvalidIndexFile Source #
Thrown when when not a .cabal, package.json or preferred-versions
 file is encountered.
Constructors
| InvalidIndexFile String | 
Instances
| Show InvalidIndexFile Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> InvalidIndexFile -> ShowS # show :: InvalidIndexFile -> String # showList :: [InvalidIndexFile] -> ShowS # | |
| Exception InvalidIndexFile Source # | |
| Defined in Cabal.Index Methods toException :: InvalidIndexFile -> SomeException # | |
data NoHackageRepository Source #
Constructors
| NoHackageRepository | 
Instances
| Show NoHackageRepository Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> NoHackageRepository -> ShowS # show :: NoHackageRepository -> String # showList :: [NoHackageRepository] -> ShowS # | |
| Exception NoHackageRepository Source # | |
| Defined in Cabal.Index Methods toException :: NoHackageRepository -> SomeException # fromException :: SomeException -> Maybe NoHackageRepository # | |
Metadata types
data PackageInfo Source #
Package information.
Constructors
| PackageInfo | |
| Fields 
 | |
Instances
| Eq PackageInfo Source # | |
| Defined in Cabal.Index | |
| Show PackageInfo Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> PackageInfo -> ShowS # show :: PackageInfo -> String # showList :: [PackageInfo] -> ShowS # | |
| Generic PackageInfo Source # | |
| Defined in Cabal.Index Associated Types type Rep PackageInfo :: Type -> Type # | |
| 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.
Constructors
| ReleaseInfo | |
| Fields 
 | |
Instances
| Eq ReleaseInfo Source # | |
| Defined in Cabal.Index | |
| Show ReleaseInfo Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> ReleaseInfo -> ShowS # show :: ReleaseInfo -> String # showList :: [ReleaseInfo] -> ShowS # | |
| Generic ReleaseInfo Source # | |
| Defined in Cabal.Index Associated Types type Rep ReleaseInfo :: Type -> Type # | |
| Binary ReleaseInfo Source # | |
| Defined in Cabal.Index | |
| type Rep ReleaseInfo Source # | |
| Defined in Cabal.Index type Rep ReleaseInfo = D1 (MetaData "ReleaseInfo" "Cabal.Index" "cabal-install-parsers-0.4-w4mTgtw0tJ6iqwagB75LL" False) (C1 (MetaCons "ReleaseInfo" PrefixI True) ((S1 (MetaSel (Just "riRevision") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Just "riTarOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TarEntryOffset)) :*: (S1 (MetaSel (Just "riCabal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SHA256) :*: S1 (MetaSel (Just "riTarball") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SHA256)))) | |
Hashes
SHA256 digest. 256 bytes.
sha256 :: ByteString -> SHA256 Source #
Hash strict ByteString.
getSHA256 :: SHA256 -> ByteString Source #
Get ByteString representation of SHA256.
Generic folding
Arguments
| :: 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 #
Constructors
| IndexEntry | |
| Fields 
 | |
Instances
| Show IndexEntry Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> IndexEntry -> ShowS # show :: IndexEntry -> String # showList :: [IndexEntry] -> ShowS # | |
data IndexFileType Source #
Varions files in 01-index.tar.
Constructors
| CabalFile PackageName Version | |
| PackageJson PackageName Version | |
| PreferredVersions PackageName | 
Instances
| Show IndexFileType Source # | |
| Defined in Cabal.Index Methods showsPrec :: Int -> IndexFileType -> ShowS # show :: IndexFileType -> String # showList :: [IndexFileType] -> ShowS # | |