| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Fetch
Description
Functionality for downloading packages securely for cabal's usage.
Synopsis
- unpackPackages :: HasCabalLoader env => Maybe SnapshotDef -> FilePath -> [String] -> RIO env ()
 - unpackPackageIdent :: HasCabalLoader env => Path Abs Dir -> Path Rel Dir -> PackageIdentifierRevision -> RIO env (Path Abs Dir)
 - unpackPackageIdents :: HasCabalLoader env => Path Abs Dir -> Maybe (Path Rel Dir) -> [PackageIdentifierRevision] -> RIO env (Map PackageIdentifier (Path Abs Dir))
 - fetchPackages :: HasCabalLoader env => Set PackageIdentifier -> RIO env ()
 - untar :: forall b1 b2. Path b1 File -> Path Rel Dir -> Path b2 Dir -> IO [(FilePath, Text)]
 - resolvePackages :: HasCabalLoader env => Maybe SnapshotDef -> [PackageIdentifierRevision] -> Set PackageName -> RIO env [ResolvedPackage]
 - resolvePackagesAllowMissing :: forall env. HasCabalLoader env => Maybe SnapshotDef -> [PackageIdentifierRevision] -> Set PackageName -> RIO env (Set PackageName, HashSet PackageIdentifierRevision, [ResolvedPackage])
 - data ResolvedPackage = ResolvedPackage {}
 - withCabalFiles :: HasCabalLoader env => IndexName -> [(ResolvedPackage, a)] -> (PackageIdentifier -> a -> ByteString -> IO b) -> RIO env [b]
 - loadFromIndex :: HasCabalLoader env => PackageIdentifierRevision -> RIO env ByteString
 
Documentation
Arguments
| :: HasCabalLoader env | |
| => Maybe SnapshotDef | when looking up by name, take from this build plan  | 
| -> FilePath | destination  | 
| -> [String] | names or identifiers  | 
| -> RIO env () | 
Intended to work for the command line command.
Arguments
| :: HasCabalLoader env | |
| => Path Abs Dir | unpack directory  | 
| -> Path Rel Dir | the dist rename directory, see: https://github.com/fpco/stack/issues/157  | 
| -> PackageIdentifierRevision | |
| -> RIO env (Path Abs Dir) | 
Same as unpackPackageIdents, but for a single package.
Arguments
| :: HasCabalLoader env | |
| => Path Abs Dir | unpack directory  | 
| -> Maybe (Path Rel Dir) | the dist rename directory, see: https://github.com/fpco/stack/issues/157  | 
| -> [PackageIdentifierRevision] | |
| -> RIO env (Map PackageIdentifier (Path Abs Dir)) | 
Ensure that all of the given package idents are unpacked into the build unpack directory, and return the paths to all of the subdirectories.
fetchPackages :: HasCabalLoader env => Set PackageIdentifier -> RIO env () Source #
Fetch packages into the cache without unpacking
untar :: forall b1 b2. Path b1 File -> Path Rel Dir -> Path b2 Dir -> IO [(FilePath, Text)] Source #
Internal function used to unpack tarball.
Takes a path to a .tar.gz file, the name of the directory it should contain, and a destination folder to extract the tarball into. Returns unexpected entries, as pairs of paths and descriptions.
Arguments
| :: HasCabalLoader env | |
| => Maybe SnapshotDef | when looking up by name, take from this build plan  | 
| -> [PackageIdentifierRevision] | |
| -> Set PackageName | |
| -> RIO env [ResolvedPackage] | 
Resolve a set of package names and identifiers into FetchPackage values.
resolvePackagesAllowMissing Source #
Arguments
| :: HasCabalLoader env | |
| => Maybe SnapshotDef | when looking up by name, take from this build plan  | 
| -> [PackageIdentifierRevision] | |
| -> Set PackageName | |
| -> RIO env (Set PackageName, HashSet PackageIdentifierRevision, [ResolvedPackage]) | 
Turn package identifiers and package names into a list of
 ResolvedPackages. Returns any unresolved names and
 identifier. These are considered unresolved even if the only
 mismatch is in the cabal file info (MSS 2017-07-17: old versions of
 this code had special handling to treat missing cabal file info as
 a warning, that's no longer necessary or desirable since all info
 should be present and checked).
data ResolvedPackage Source #
Constructors
| ResolvedPackage | |
Fields 
  | |
Instances
| Show ResolvedPackage Source # | |
Defined in Stack.Fetch Methods showsPrec :: Int -> ResolvedPackage -> ShowS # show :: ResolvedPackage -> String # showList :: [ResolvedPackage] -> ShowS #  | |
withCabalFiles :: HasCabalLoader env => IndexName -> [(ResolvedPackage, a)] -> (PackageIdentifier -> a -> ByteString -> IO b) -> RIO env [b] Source #
Add the cabal files to a list of idents with their caches.
loadFromIndex :: HasCabalLoader env => PackageIdentifierRevision -> RIO env ByteString Source #