Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Content addressable Haskell package management, providing for secure, reproducible acquisition of Haskell package contents and metadata.
Since: 0.1.0.0
Synopsis
- data PantryConfig
- data PackageIndexConfig = PackageIndexConfig {}
- data HackageSecurityConfig = HackageSecurityConfig {
- hscKeyIds :: ![Text]
- hscKeyThreshold :: !Int
- hscIgnoreExpiry :: !Bool
- defaultPackageIndexConfig :: PackageIndexConfig
- defaultDownloadPrefix :: Text
- defaultHackageSecurityConfig :: HackageSecurityConfig
- defaultCasaRepoPrefix :: CasaRepoPrefix
- defaultCasaMaxPerRequest :: Int
- defaultSnapshotLocation :: SnapName -> RawSnapshotLocation
- class HasPantryConfig env where
- pantryConfigL :: Lens' env PantryConfig
- withPantryConfig :: HasLogFunc env => Path Abs Dir -> PackageIndexConfig -> HpackExecutable -> Int -> CasaRepoPrefix -> Int -> (SnapName -> RawSnapshotLocation) -> (PantryConfig -> RIO env a) -> RIO env a
- data HpackExecutable
- data PantryApp
- runPantryApp :: MonadIO m => RIO PantryApp a -> m a
- runPantryAppClean :: MonadIO m => RIO PantryApp a -> m a
- runPantryAppWith :: MonadIO m => Int -> CasaRepoPrefix -> Int -> RIO PantryApp a -> m a
- hpackExecutableL :: Lens' PantryConfig HpackExecutable
- data PantryException
- = PackageIdentifierRevisionParseFail !Text
- | InvalidCabalFile !(Either RawPackageLocationImmutable (Path Abs File)) !(Maybe Version) ![PError] ![PWarning]
- | TreeWithoutCabalFile !RawPackageLocationImmutable
- | TreeWithMultipleCabalFiles !RawPackageLocationImmutable ![SafeFilePath]
- | MismatchedCabalName !(Path Abs File) !PackageName
- | NoCabalFileFound !(Path Abs Dir)
- | MultipleCabalFilesFound !(Path Abs Dir) ![Path Abs File]
- | InvalidWantedCompiler !Text
- | InvalidSnapshotLocation !(Path Abs Dir) !Text
- | InvalidOverrideCompiler !WantedCompiler !WantedCompiler
- | InvalidFilePathSnapshot !Text
- | InvalidSnapshot !RawSnapshotLocation !SomeException
- | MismatchedPackageMetadata !RawPackageLocationImmutable !RawPackageMetadata !(Maybe TreeKey) !PackageIdentifier
- | Non200ResponseStatus !Status
- | InvalidBlobKey !(Mismatch BlobKey)
- | Couldn'tParseSnapshot !RawSnapshotLocation !String
- | WrongCabalFileName !RawPackageLocationImmutable !SafeFilePath !PackageName
- | DownloadInvalidSHA256 !Text !(Mismatch SHA256)
- | DownloadInvalidSize !Text !(Mismatch FileSize)
- | DownloadTooLarge !Text !(Mismatch FileSize)
- | LocalInvalidSHA256 !(Path Abs File) !(Mismatch SHA256)
- | LocalInvalidSize !(Path Abs File) !(Mismatch FileSize)
- | UnknownArchiveType !ArchiveLocation
- | InvalidTarFileType !ArchiveLocation !FilePath !FileType
- | UnsupportedTarball !ArchiveLocation !Text
- | NoHackageCryptographicHash !PackageIdentifier
- | FailedToCloneRepo !SimpleRepo
- | TreeReferencesMissingBlob !RawPackageLocationImmutable !SafeFilePath !BlobKey
- | CompletePackageMetadataMismatch !RawPackageLocationImmutable !PackageMetadata
- | CRC32Mismatch !ArchiveLocation !FilePath !(Mismatch Word32)
- | UnknownHackagePackage !PackageIdentifierRevision !FuzzyResults
- | CannotCompleteRepoNonSHA1 !Repo
- | MutablePackageLocationFromUrl !Text
- | MismatchedCabalFileForHackage !PackageIdentifierRevision !(Mismatch PackageIdentifier)
- | PackageNameParseFail !Text
- | PackageVersionParseFail !Text
- | InvalidCabalFilePath !(Path Abs File)
- | DuplicatePackageNames !Utf8Builder ![(PackageName, [RawPackageLocationImmutable])]
- | MigrationFailure !Text !(Path Abs File) !SomeException
- | InvalidTreeFromCasa !BlobKey !ByteString
- | ParseSnapNameException !Text
- | HpackLibraryException !(Path Abs File) !SomeException
- | HpackExeException !FilePath !(Path Abs Dir) !SomeException
- data PackageName
- data Version
- data FlagName
- data PackageIdentifier = PackageIdentifier {}
- newtype FileSize = FileSize Word
- newtype RelFilePath = RelFilePath Text
- data ResolvedPath t = ResolvedPath {
- resolvedRelative :: !RelFilePath
- resolvedAbsolute :: !(Path Abs t)
- data Unresolved a
- data SHA256
- newtype TreeKey = TreeKey BlobKey
- data BlobKey = BlobKey !SHA256 !FileSize
- data RawPackageMetadata = RawPackageMetadata {
- rpmName :: !(Maybe PackageName)
- rpmVersion :: !(Maybe Version)
- rpmTreeKey :: !(Maybe TreeKey)
- data PackageMetadata = PackageMetadata {
- pmIdent :: !PackageIdentifier
- pmTreeKey :: !TreeKey
- data Package = Package {
- packageTreeKey :: !TreeKey
- packageTree :: !Tree
- packageCabalEntry :: !PackageCabal
- packageIdent :: !PackageIdentifier
- data CabalFileInfo
- newtype Revision = Revision Word
- data PackageIdentifierRevision = PackageIdentifierRevision !PackageName !Version !CabalFileInfo
- data UsePreferredVersions
- data RawArchive = RawArchive {
- raLocation :: !ArchiveLocation
- raHash :: !(Maybe SHA256)
- raSize :: !(Maybe FileSize)
- raSubdir :: !Text
- data Archive = Archive {}
- data ArchiveLocation
- = ALUrl !Text
- | ALFilePath !(ResolvedPath File)
- data Repo = Repo {
- repoUrl :: !Text
- repoCommit :: !Text
- repoType :: !RepoType
- repoSubdir :: !Text
- data RepoType
- data SimpleRepo = SimpleRepo {}
- withRepo :: forall env a. (HasLogFunc env, HasProcessContext env) => SimpleRepo -> RIO env a -> RIO env a
- fetchRepos :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, PackageMetadata)] -> RIO env ()
- fetchReposRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, RawPackageMetadata)] -> RIO env ()
- data RawPackageLocation
- data PackageLocation
- toRawPL :: PackageLocation -> RawPackageLocation
- data RawPackageLocationImmutable
- data PackageLocationImmutable
- data RawSnapshotLocation
- = RSLCompiler !WantedCompiler
- | RSLUrl !Text !(Maybe BlobKey)
- | RSLFilePath !(ResolvedPath File)
- | RSLSynonym !SnapName
- data SnapshotLocation
- = SLCompiler !WantedCompiler
- | SLUrl !Text !BlobKey
- | SLFilePath !(ResolvedPath File)
- toRawSL :: SnapshotLocation -> RawSnapshotLocation
- data RawSnapshot = RawSnapshot {
- rsCompiler :: !WantedCompiler
- rsPackages :: !(Map PackageName RawSnapshotPackage)
- rsDrop :: !(Set PackageName)
- data Snapshot = Snapshot {}
- data RawSnapshotPackage = RawSnapshotPackage {
- rspLocation :: !RawPackageLocationImmutable
- rspFlags :: !(Map FlagName Bool)
- rspHidden :: !Bool
- rspGhcOptions :: ![Text]
- data SnapshotPackage = SnapshotPackage {
- spLocation :: !PackageLocationImmutable
- spFlags :: !(Map FlagName Bool)
- spHidden :: !Bool
- spGhcOptions :: ![Text]
- data RawSnapshotLayer = RawSnapshotLayer {
- rslParent :: !RawSnapshotLocation
- rslCompiler :: !(Maybe WantedCompiler)
- rslLocations :: ![RawPackageLocationImmutable]
- rslDropPackages :: !(Set PackageName)
- rslFlags :: !(Map PackageName (Map FlagName Bool))
- rslHidden :: !(Map PackageName Bool)
- rslGhcOptions :: !(Map PackageName [Text])
- rslPublishTime :: !(Maybe UTCTime)
- data SnapshotLayer = SnapshotLayer {
- slParent :: !SnapshotLocation
- slCompiler :: !(Maybe WantedCompiler)
- slLocations :: ![PackageLocationImmutable]
- slDropPackages :: !(Set PackageName)
- slFlags :: !(Map PackageName (Map FlagName Bool))
- slHidden :: !(Map PackageName Bool)
- slGhcOptions :: !(Map PackageName [Text])
- slPublishTime :: !(Maybe UTCTime)
- toRawSnapshotLayer :: SnapshotLayer -> RawSnapshotLayer
- data WantedCompiler
- data SnapName
- snapshotLocation :: HasPantryConfig env => SnapName -> RIO env RawSnapshotLocation
- resolvePaths :: MonadIO m => Maybe (Path Abs Dir) -> Unresolved a -> m a
- loadPackageRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env Package
- tryLoadPackageRawViaCasa :: (HasLogFunc env, HasPantryConfig env, HasProcessContext env) => RawPackageLocationImmutable -> TreeKey -> RIO env (Maybe Package)
- loadPackage :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env Package
- loadRawSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env (Either WantedCompiler (RawSnapshotLayer, CompletedSL))
- loadSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => SnapshotLocation -> RIO env (Either WantedCompiler RawSnapshotLayer)
- loadSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => SnapshotLocation -> RIO env RawSnapshot
- loadAndCompleteSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => SnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshot' :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Bool -> SnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshotRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawSnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- loadAndCompleteSnapshotRaw' :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Bool -> RawSnapshotLocation -> Map RawSnapshotLocation SnapshotLocation -> Map RawPackageLocationImmutable PackageLocationImmutable -> RIO env (Snapshot, [CompletedSL], [CompletedPLI])
- data CompletedSL = CompletedSL !RawSnapshotLocation !SnapshotLocation
- data CompletedPLI = CompletedPLI !RawPackageLocationImmutable !PackageLocationImmutable
- addPackagesToSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Utf8Builder -> [RawPackageLocationImmutable] -> AddPackagesConfig -> Map PackageName RawSnapshotPackage -> RIO env (Map PackageName RawSnapshotPackage, AddPackagesConfig)
- data AddPackagesConfig = AddPackagesConfig {
- apcDrop :: !(Set PackageName)
- apcFlags :: !(Map PackageName (Map FlagName Bool))
- apcHiddens :: !(Map PackageName Bool)
- apcGhcOptions :: !(Map PackageName [Text])
- data CompletePackageLocation = CompletePackageLocation {}
- completePackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env CompletePackageLocation
- completeSnapshotLocation :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env SnapshotLocation
- warnMissingCabalFile :: HasLogFunc env => RawPackageLocationImmutable -> RIO env ()
- parseWantedCompiler :: Text -> Either PantryException WantedCompiler
- parseSnapName :: MonadThrow m => Text -> m SnapName
- parseRawSnapshotLocation :: Text -> Unresolved RawSnapshotLocation
- parsePackageIdentifierRevision :: Text -> Either PantryException PackageIdentifierRevision
- parseHackageText :: Text -> Either PantryException (PackageIdentifier, BlobKey)
- parsePackageIdentifier :: String -> Maybe PackageIdentifier
- parsePackageName :: String -> Maybe PackageName
- parsePackageNameThrowing :: MonadThrow m => String -> m PackageName
- parseFlagName :: String -> Maybe FlagName
- parseVersion :: String -> Maybe Version
- parseVersionThrowing :: MonadThrow m => String -> m Version
- packageIdentifierString :: PackageIdentifier -> String
- packageNameString :: PackageName -> String
- flagNameString :: FlagName -> String
- versionString :: Version -> String
- moduleNameString :: ModuleName -> String
- newtype CabalString a = CabalString {
- unCabalString :: a
- toCabalStringMap :: Map a v -> Map (CabalString a) v
- unCabalStringMap :: Map (CabalString a) v -> Map a v
- gpdPackageIdentifier :: GenericPackageDescription -> PackageIdentifier
- gpdPackageName :: GenericPackageDescription -> PackageName
- gpdVersion :: GenericPackageDescription -> Version
- fetchPackages :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env, Foldable f) => f PackageLocationImmutable -> RIO env ()
- unpackPackageLocationRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Path Abs Dir -> RawPackageLocationImmutable -> RIO env ()
- unpackPackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Path Abs Dir -> PackageLocationImmutable -> RIO env ()
- getPackageLocationName :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageName
- getRawPackageLocationIdent :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageIdentifier
- packageLocationIdent :: PackageLocationImmutable -> PackageIdentifier
- packageLocationVersion :: PackageLocationImmutable -> Version
- getRawPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env TreeKey
- getPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env TreeKey
- loadCabalFileRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> RawPackageLocation -> RIO env GenericPackageDescription
- loadCabalFile :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> PackageLocation -> RIO env GenericPackageDescription
- loadCabalFileRawImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env GenericPackageDescription
- loadCabalFileImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env GenericPackageDescription
- loadCabalFilePath :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> Path Abs Dir -> RIO env (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File)
- findOrGenerateCabalFile :: forall env. (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => Maybe Text -> Path Abs Dir -> RIO env (PackageName, Path Abs File)
- data PrintWarnings
- updateHackageIndex :: (HasPantryConfig env, HasLogFunc env) => Maybe Utf8Builder -> RIO env DidUpdateOccur
- data DidUpdateOccur
- data RequireHackageIndex
- hackageIndexTarballL :: HasPantryConfig env => SimpleGetter env (Path Abs File)
- getHackagePackageVersions :: (HasPantryConfig env, HasLogFunc env) => RequireHackageIndex -> UsePreferredVersions -> PackageName -> RIO env (Map Version (Map Revision BlobKey))
- getLatestHackageVersion :: (HasPantryConfig env, HasLogFunc env) => RequireHackageIndex -> PackageName -> UsePreferredVersions -> RIO env (Maybe PackageIdentifierRevision)
- getLatestHackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RequireHackageIndex -> PackageName -> UsePreferredVersions -> RIO env (Maybe PackageLocationImmutable)
- getLatestHackageRevision :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RequireHackageIndex -> PackageName -> Version -> RIO env (Maybe (Revision, BlobKey, TreeKey))
- getHackageTypoCorrections :: (HasPantryConfig env, HasLogFunc env) => PackageName -> RIO env [PackageName]
- loadGlobalHints :: (HasTerm env, HasPantryConfig env) => WantedCompiler -> RIO env (Maybe (Map PackageName Version))
- partitionReplacedDependencies :: Ord id => Map PackageName a -> (a -> PackageName) -> (a -> id) -> (a -> [id]) -> Set PackageName -> (Map PackageName [PackageName], Map PackageName a)
- newtype SnapshotCacheHash = SnapshotCacheHash {}
- withSnapshotCache :: (HasPantryConfig env, HasLogFunc env) => SnapshotCacheHash -> RIO env (Map PackageName (Set ModuleName)) -> ((ModuleName -> RIO env [PackageName]) -> RIO env a) -> RIO env a
Running
data PantryConfig Source #
Configuration value used by the entire pantry package. Create one
using withPantryConfig
. See also PantryApp
for a convenience
approach to using pantry.
Since: 0.1.0.0
data PackageIndexConfig Source #
Configuration to securely download package metadata and contents. For most
purposes, you'll want to use the default Hackage settings via
defaultPackageIndexConfig
.
NOTE It's highly recommended to only use the official Hackage server or a mirror. See https://github.com/commercialhaskell/stack/issues/4137.
Since: 0.6.0
Instances
Show PackageIndexConfig Source # | |
Defined in Pantry.Types showsPrec :: Int -> PackageIndexConfig -> ShowS # show :: PackageIndexConfig -> String # showList :: [PackageIndexConfig] -> ShowS # | |
FromJSON (WithJSONWarnings PackageIndexConfig) Source # | If the Since: 0.6.0 |
Defined in Pantry.Types |
data HackageSecurityConfig Source #
Configuration for Hackage Security to securely download package metadata
and contents. For most purposes, you'll want to use the default Hackage
settings via defaultHackageSecurityConfig
.
NOTE It's highly recommended to only use the official Hackage server or a mirror. See https://github.com/commercialhaskell/stack/issues/4137.
Since: 0.6.0
HackageSecurityConfig | |
|
Instances
Show HackageSecurityConfig Source # | |
Defined in Pantry.Types showsPrec :: Int -> HackageSecurityConfig -> ShowS # show :: HackageSecurityConfig -> String # showList :: [HackageSecurityConfig] -> ShowS # | |
FromJSON (WithJSONWarnings HackageSecurityConfig) Source # | If the Since: 0.1.1.0 |
Defined in Pantry.Types |
defaultPackageIndexConfig :: PackageIndexConfig Source #
Default PackageIndexConfig
value using the official Hackage server.
Since: 0.6.0
defaultDownloadPrefix :: Text Source #
The download prefix for the official Hackage server.
Since: 0.6.0
defaultHackageSecurityConfig :: HackageSecurityConfig Source #
Default HackageSecurityConfig
value using the official Hackage server.
The value of the hscIgnoreExpiry
field is True
.
Since: 0.7.0
defaultCasaRepoPrefix :: CasaRepoPrefix Source #
Default pull URL for Casa.
Since: 0.1.1.1
defaultCasaMaxPerRequest :: Int Source #
Default max keys to pull per request.
Since: 0.1.1.1
defaultSnapshotLocation :: SnapName -> RawSnapshotLocation Source #
Default location of snapshot synonyms , i.e. commercialhaskell's GitHub repository.
Since: 0.5.0.0
class HasPantryConfig env where Source #
An environment which contains a PantryConfig
.
Since: 0.1.0.0
pantryConfigL :: Lens' env PantryConfig Source #
Lens to get or set the PantryConfig
Since: 0.1.0.0
Instances
HasPantryConfig PantryApp Source # | |
Defined in Pantry |
:: HasLogFunc env | |
=> Path Abs Dir | pantry root directory, where the SQLite database and Hackage downloads are kept. |
-> PackageIndexConfig | Package index configuration. You probably want
|
-> HpackExecutable | When converting an hpack |
-> Int | Maximum connection count |
-> CasaRepoPrefix | The casa pull URL e.g. https://casa.fpcomplete.com/v1/pull. |
-> Int | Max casa keys to pull per request. |
-> (SnapName -> RawSnapshotLocation) | The location of snapshot synonyms |
-> (PantryConfig -> RIO env a) | What to do with the config |
-> RIO env a |
Create a new PantryConfig
with the given settings.
For something easier to use in simple cases, see runPantryApp
.
Since: 0.1.0.0
data HpackExecutable Source #
What to use for running hpack
Since: 0.1.0.0
HpackBundled | Compiled in library |
HpackCommand !FilePath | Executable at the provided path |
Instances
Read HpackExecutable Source # | |
Defined in Pantry.Types | |
Show HpackExecutable Source # | |
Defined in Pantry.Types showsPrec :: Int -> HpackExecutable -> ShowS # show :: HpackExecutable -> String # showList :: [HpackExecutable] -> ShowS # | |
Eq HpackExecutable Source # | |
Defined in Pantry.Types (==) :: HpackExecutable -> HpackExecutable -> Bool # (/=) :: HpackExecutable -> HpackExecutable -> Bool # | |
Ord HpackExecutable Source # | |
Defined in Pantry.Types compare :: HpackExecutable -> HpackExecutable -> Ordering # (<) :: HpackExecutable -> HpackExecutable -> Bool # (<=) :: HpackExecutable -> HpackExecutable -> Bool # (>) :: HpackExecutable -> HpackExecutable -> Bool # (>=) :: HpackExecutable -> HpackExecutable -> Bool # max :: HpackExecutable -> HpackExecutable -> HpackExecutable # min :: HpackExecutable -> HpackExecutable -> HpackExecutable # |
Convenience
Convenient data type that allows you to work with pantry more
easily than using withPantryConfig
directly. Uses basically sane
settings, like sharing a pantry directory with Stack.
You can use runPantryApp
to use this.
Since: 0.1.0.0
runPantryApp :: MonadIO m => RIO PantryApp a -> m a Source #
Run some code against pantry using basic sane settings.
For testing, see runPantryAppClean
.
Since: 0.1.0.0
runPantryAppClean :: MonadIO m => RIO PantryApp a -> m a Source #
Like runPantryApp
, but uses an empty pantry directory instead
of sharing with Stack. Useful for testing.
Since: 0.1.0.0
runPantryAppWith :: MonadIO m => Int -> CasaRepoPrefix -> Int -> RIO PantryApp a -> m a Source #
Run some code against pantry using basic sane settings.
For testing, see runPantryAppClean
.
Since: 0.1.1.1
hpackExecutableL :: Lens' PantryConfig HpackExecutable Source #
Lens to view or modify the HpackExecutable
of a PantryConfig
Since: 0.1.0.0
Types
Exceptions
data PantryException Source #
Things that can go wrong in pantry. Note two things:
- Many other exception types may be thrown from underlying libraries. Pantry does not attempt to wrap these underlying exceptions.
- We may add more constructors to this data type in minor version bumps of pantry. This technically breaks the PVP. You should not be writing pattern matches against this type that expect total matching.
Since: 0.1.0.0
Instances
Exception PantryException Source # | |
Defined in Pantry.Types | |
Show PantryException Source # | |
Defined in Pantry.Types showsPrec :: Int -> PantryException -> ShowS # show :: PantryException -> String # showList :: [PantryException] -> ShowS # | |
Display PantryException Source # | |
Defined in Pantry.Types display :: PantryException -> Utf8Builder # textDisplay :: PantryException -> Text # |
Cabal types
data PackageName #
A package name.
Use mkPackageName
and unPackageName
to convert from/to a
String
.
This type is opaque since Cabal-2.0
Since: Cabal-2.0.0.2
Instances
A Version
represents the version of a software entity.
Instances of Eq
and Ord
are provided, which gives exact
equality and lexicographic ordering of the version number
components (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.).
This type is opaque and distinct from the Version
type in
Data.Version since Cabal-2.0
. The difference extends to the
Binary
instance using a different (and more compact) encoding.
Since: Cabal-2.0.0.2
Instances
A FlagName
is the name of a user-defined configuration flag
Use mkFlagName
and unFlagName
to convert from/to a String
.
This type is opaque since Cabal-2.0
Since: Cabal-2.0.0.2
Instances
Parsec FlagName | |
Defined in Distribution.Types.Flag parsec :: CabalParsing m => m FlagName # | |
Pretty FlagName | |
Defined in Distribution.Types.Flag prettyVersioned :: CabalSpecVersion -> FlagName -> Doc # | |
Structured FlagName | |
Defined in Distribution.Types.Flag | |
Data FlagName | |
Defined in Distribution.Types.Flag gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FlagName -> c FlagName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FlagName # toConstr :: FlagName -> Constr # dataTypeOf :: FlagName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FlagName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FlagName) # gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r # gmapQ :: (forall d. Data d => d -> u) -> FlagName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FlagName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName # | |
IsString FlagName | Since: Cabal-2.0.0.2 |
Defined in Distribution.Types.Flag fromString :: String -> FlagName # | |
Generic FlagName | |
Read FlagName | |
Show FlagName | |
Binary FlagName | |
NFData FlagName | |
Defined in Distribution.Types.Flag | |
Eq FlagName | |
Ord FlagName | |
Defined in Distribution.Types.Flag | |
type Rep FlagName | |
Defined in Distribution.Types.Flag |
data PackageIdentifier #
The name and version of a package.
PackageIdentifier | |
|
Instances
Files
File size in bytes
Since: 0.1.0.0
Instances
FromJSON FileSize Source # | |
ToJSON FileSize Source # | |
Defined in Pantry.Types | |
Generic FileSize Source # | |
Show FileSize Source # | |
NFData FileSize Source # | |
Defined in Pantry.Types | |
Eq FileSize Source # | |
Ord FileSize Source # | |
Defined in Pantry.Types | |
Hashable FileSize Source # | |
Defined in Pantry.Types | |
PersistField FileSize Source # | |
Defined in Pantry.Types | |
PersistFieldSql FileSize Source # | |
Display FileSize Source # | |
Defined in Pantry.Types display :: FileSize -> Utf8Builder # textDisplay :: FileSize -> Text # | |
type Rep FileSize Source # | |
Defined in Pantry.Types |
newtype RelFilePath Source #
File path relative to the configuration file it was parsed from
Since: 0.1.0.0
Instances
data ResolvedPath t Source #
A combination of the relative path provided in a config file, together with the resolved absolute path.
Since: 0.1.0.0
ResolvedPath | |
|
Instances
data Unresolved a Source #
Wraps a value which potentially contains relative paths. Needs to be provided with a base directory to resolve these paths.
Unwrap this using resolvePaths
.
Since: 0.1.0.0
Instances
Cryptography
A SHA256 hash, stored in a static size for more efficient memory representation.
Since: 0.1.0.0
Instances
FromJSON SHA256 Source # | |
ToJSON SHA256 Source # | |
Defined in Pantry.SHA256 | |
Data SHA256 Source # | |
Defined in Pantry.SHA256 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |
Generic SHA256 Source # | |
Show SHA256 Source # | |
NFData SHA256 Source # | |
Defined in Pantry.SHA256 | |
Eq SHA256 Source # | |
Ord SHA256 Source # | |
Hashable SHA256 Source # | |
Defined in Pantry.SHA256 | |
PersistField SHA256 Source # | |
Defined in Pantry.SHA256 toPersistValue :: SHA256 -> PersistValue # | |
PersistFieldSql SHA256 Source # | |
Display SHA256 Source # | |
Defined in Pantry.SHA256 display :: SHA256 -> Utf8Builder # textDisplay :: SHA256 -> Text # | |
type Rep SHA256 Source # | |
Defined in Pantry.SHA256 |
The hash of the binary representation of a Tree
.
Since: 0.1.0.0
Instances
FromJSON TreeKey Source # | |
ToJSON TreeKey Source # | |
Defined in Pantry.Types | |
Generic TreeKey Source # | |
Show TreeKey Source # | |
NFData TreeKey Source # | |
Defined in Pantry.Types | |
Eq TreeKey Source # | |
Ord TreeKey Source # | |
Display TreeKey Source # | |
Defined in Pantry.Types display :: TreeKey -> Utf8Builder # textDisplay :: TreeKey -> Text # | |
type Rep TreeKey Source # | |
Defined in Pantry.Types |
A key for looking up a blob, which combines the SHA256 hash of the contents and the file size.
The file size may seem redundant with the hash. However, it is necessary for safely downloading blobs from an untrusted source. See https://www.fpcomplete.com/blog/2018/07/pantry-part-2-trees-keys.
Since: 0.1.0.0
Instances
FromJSON BlobKey Source # | |
ToJSON BlobKey Source # | |
Defined in Pantry.Types | |
Generic BlobKey Source # | |
Show BlobKey Source # | |
NFData BlobKey Source # | |
Defined in Pantry.Types | |
Eq BlobKey Source # | |
Ord BlobKey Source # | |
Display BlobKey Source # | |
Defined in Pantry.Types display :: BlobKey -> Utf8Builder # textDisplay :: BlobKey -> Text # | |
type Rep BlobKey Source # | |
Defined in Pantry.Types type Rep BlobKey = D1 ('MetaData "BlobKey" "Pantry.Types" "pantry-0.8.0-3S5du7uXdVa4yiSYuSkRbn" 'False) (C1 ('MetaCons "BlobKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FileSize))) |
Packages
data RawPackageMetadata Source #
Metadata provided by a config file for archives and repos. This information can be used for optimized lookups of information like package identifiers, or for validating that the user configuration has the expected information.
Since: 0.1.0.0
RawPackageMetadata | |
|
Instances
data PackageMetadata Source #
Exact metadata specifying concrete package
Since: 0.1.0.0
PackageMetadata | |
|
Instances
Parsed tree with more information on the Haskell package it contains.
Since: 0.1.0.0
Package | |
|
Hackage
data CabalFileInfo Source #
How to choose a cabal file for a package from Hackage. This is to
work with Hackage cabal file revisions, which makes
PackageIdentifier
insufficient for specifying a package from
Hackage.
Since: 0.1.0.0
CFILatest | Take the latest revision of the cabal file available. This isn't reproducible at all, but the running assumption (not necessarily true) is that cabal file revisions do not change semantics of the build. Since: 0.1.0.0 |
CFIHash !SHA256 !(Maybe FileSize) | Identify by contents of the cabal file itself. Only reason for
Since: 0.1.0.0 |
CFIRevision !Revision | Identify by revision number, with 0 being the original and
counting upward. This relies on Hackage providing consistent
versioning. Since: 0.1.0.0 |
Instances
The revision number of a package from Hackage, counting upwards from 0 (the original cabal file).
See caveats on CFIRevision
.
Since: 0.1.0.0
Instances
Data Revision Source # | |
Defined in Pantry.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Revision -> c Revision # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Revision # toConstr :: Revision -> Constr # dataTypeOf :: Revision -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Revision) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Revision) # gmapT :: (forall b. Data b => b -> b) -> Revision -> Revision # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQ :: (forall d. Data d => d -> u) -> Revision -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Revision -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # | |
Generic Revision Source # | |
Show Revision Source # | |
NFData Revision Source # | |
Defined in Pantry.Types | |
Eq Revision Source # | |
Ord Revision Source # | |
Defined in Pantry.Types | |
Hashable Revision Source # | |
Defined in Pantry.Types | |
PersistField Revision Source # | |
Defined in Pantry.Types | |
PersistFieldSql Revision Source # | |
Display Revision Source # | |
Defined in Pantry.Types display :: Revision -> Utf8Builder # textDisplay :: Revision -> Text # | |
type Rep Revision Source # | |
Defined in Pantry.Types |
data PackageIdentifierRevision Source #
A full specification for a package from Hackage, including the package name, version, and how to load up the correct cabal file revision.
Since: 0.1.0.0
Instances
data UsePreferredVersions Source #
Should we pay attention to Hackage's preferred versions?
Since: 0.1.0.0
Instances
Show UsePreferredVersions Source # | |
Defined in Pantry.Hackage showsPrec :: Int -> UsePreferredVersions -> ShowS # show :: UsePreferredVersions -> String # showList :: [UsePreferredVersions] -> ShowS # |
Archives
data RawArchive Source #
A raw package archive, specified by a user, could have no hash and file size information.
Since: 0.1.0.0
RawArchive | |
|
Instances
A package archive, could be from a URL or a local file path. Local file path archives are assumed to be unchanging over time, and so are allowed in custom snapshots.
Since: 0.1.0.0
Archive | |
|
Instances
Generic Archive Source # | |
Show Archive Source # | |
NFData Archive Source # | |
Defined in Pantry.Types | |
Eq Archive Source # | |
Ord Archive Source # | |
type Rep Archive Source # | |
Defined in Pantry.Types type Rep Archive = D1 ('MetaData "Archive" "Pantry.Types" "pantry-0.8.0-3S5du7uXdVa4yiSYuSkRbn" 'False) (C1 ('MetaCons "Archive" 'PrefixI 'True) ((S1 ('MetaSel ('Just "archiveLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArchiveLocation) :*: S1 ('MetaSel ('Just "archiveHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256)) :*: (S1 ('MetaSel ('Just "archiveSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FileSize) :*: S1 ('MetaSel ('Just "archiveSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
data ArchiveLocation Source #
Location that an archive is stored at
Since: 0.1.0.0
ALUrl !Text | Archive stored at an HTTP(S) URL Since: 0.1.0.0 |
ALFilePath !(ResolvedPath File) | Archive stored at a local file path Since: 0.1.0.0 |
Instances
Repos
Information on packages stored in a source control repository.
Since: 0.1.0.0
Repo | |
|
Instances
Generic Repo Source # | |
Show Repo Source # | |
NFData Repo Source # | |
Defined in Pantry.Types | |
Eq Repo Source # | |
Ord Repo Source # | |
Display Repo Source # | |
Defined in Pantry.Types display :: Repo -> Utf8Builder # textDisplay :: Repo -> Text # | |
type Rep Repo Source # | |
Defined in Pantry.Types type Rep Repo = D1 ('MetaData "Repo" "Pantry.Types" "pantry-0.8.0-3S5du7uXdVa4yiSYuSkRbn" 'False) (C1 ('MetaCons "Repo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "repoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "repoCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "repoType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoType) :*: S1 ('MetaSel ('Just "repoSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
The type of a source control repository.
Since: 0.1.0.0
data SimpleRepo Source #
Repository without subdirectory information.
Since: 0.5.3
Instances
withRepo :: forall env a. (HasLogFunc env, HasProcessContext env) => SimpleRepo -> RIO env a -> RIO env a Source #
Clone the repository and execute the action with the working directory set to the repository root.
Since: 0.1.0.0
fetchRepos :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, PackageMetadata)] -> RIO env () Source #
Fetch the given repositories at once and populate the pantry database.
Since: 0.5.3
fetchReposRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, RawPackageMetadata)] -> RIO env () Source #
Like fetchRepos
, except with RawPackageMetadata
instead of PackageMetadata
.
Since: 0.5.3
Package location
data RawPackageLocation Source #
Location to load a package from. Can either be immutable (see
PackageLocationImmutable
) or a local directory which is expected
to change over time. Raw version doesn't include exact package
version (e.g. could refer to the latest revision on Hackage)
Since: 0.1.0.0
Instances
data PackageLocation Source #
Location to load a package from. Can either be immutable (see
PackageLocationImmutable
) or a local directory which is expected
to change over time.
Since: 0.1.0.0
Instances
toRawPL :: PackageLocation -> RawPackageLocation Source #
Convert PackageLocation
to its "raw" equivalent
Since: 0.1.0.0
data RawPackageLocationImmutable Source #
Location for remote packages or archives assumed to be immutable. as user specifies it i.e. not an exact location
Since: 0.1.0.0
RPLIHackage !PackageIdentifierRevision !(Maybe TreeKey) | |
RPLIArchive !RawArchive !RawPackageMetadata | |
RPLIRepo !Repo !RawPackageMetadata |
Instances
data PackageLocationImmutable Source #
Location for remote packages or archives assumed to be immutable.
Since: 0.1.0.0
PLIHackage !PackageIdentifier !BlobKey !TreeKey | |
PLIArchive !Archive !PackageMetadata | |
PLIRepo !Repo !PackageMetadata |
Instances
Snapshots
data RawSnapshotLocation Source #
Where to load a snapshot from in raw form (RSUrl could have a missing BlobKey)
Since: 0.1.0.0
RSLCompiler !WantedCompiler | Don't use an actual snapshot, just a version of the compiler with its shipped packages. Since: 0.1.0.0 |
RSLUrl !Text !(Maybe BlobKey) | Download the snapshot from the given URL. The optional
Since: 0.1.0.0 |
RSLFilePath !(ResolvedPath File) | Snapshot at a local file path. Since: 0.1.0.0 |
RSLSynonym !SnapName | Snapshot synonym (LTS/Nightly). Since: 0.5.0.0 |
Instances
data SnapshotLocation Source #
Where to load a snapshot from.
Since: 0.1.0.0
SLCompiler !WantedCompiler | Don't use an actual snapshot, just a version of the compiler with its shipped packages. Since: 0.1.0.0 |
SLUrl !Text !BlobKey | Download the snapshot from the given URL. The optional
Since: 0.1.0.0 |
SLFilePath !(ResolvedPath File) | Snapshot at a local file path. Since: 0.1.0.0 |
Instances
toRawSL :: SnapshotLocation -> RawSnapshotLocation Source #
Convert snapshot location to its "raw" equivalent.
Since: 0.1.0.0
data RawSnapshot Source #
A flattened representation of all the layers in a snapshot.
Since: 0.1.0.0
RawSnapshot | |
|
A flattened representation of all the layers in a snapshot.
Since: 0.1.0.0
Snapshot | |
|
data RawSnapshotPackage Source #
Settings for a package found in a snapshot.
Since: 0.1.0.0
RawSnapshotPackage | |
|
data SnapshotPackage Source #
Settings for a package found in a snapshot.
Since: 0.1.0.0
SnapshotPackage | |
|
Instances
Show SnapshotPackage Source # | |
Defined in Pantry.Types showsPrec :: Int -> SnapshotPackage -> ShowS # show :: SnapshotPackage -> String # showList :: [SnapshotPackage] -> ShowS # |
data RawSnapshotLayer Source #
A single layer of a snapshot, i.e. a specific YAML configuration file.
Since: 0.1.0.0
RawSnapshotLayer | |
|
Instances
data SnapshotLayer Source #
A single layer of a snapshot, i.e. a specific YAML configuration file.
Since: 0.1.0.0
SnapshotLayer | |
|
Instances
toRawSnapshotLayer :: SnapshotLayer -> RawSnapshotLayer Source #
Convert snapshot layer into its "raw" equivalent.
Since: 0.1.0.0
data WantedCompiler Source #
Which compiler a snapshot wants to use. The build tool may elect to do some fuzzy matching of versions (e.g., allowing different patch versions).
Since: 0.1.0.0
Instances
A snapshot synonym.
It is expanded according to the field snapshotLocation
of a PantryConfig
.
@ since 0.5.0.0
Instances
ToJSON SnapName Source # | |
Defined in Pantry.Types | |
Generic SnapName Source # | |
Show SnapName Source # | |
NFData SnapName Source # | |
Defined in Pantry.Types | |
Eq SnapName Source # | |
Ord SnapName Source # | |
Defined in Pantry.Types | |
Display SnapName Source # | |
Defined in Pantry.Types display :: SnapName -> Utf8Builder # textDisplay :: SnapName -> Text # | |
type Rep SnapName Source # | |
Defined in Pantry.Types type Rep SnapName = D1 ('MetaData "SnapName" "Pantry.Types" "pantry-0.8.0-3S5du7uXdVa4yiSYuSkRbn" 'False) (C1 ('MetaCons "LTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Nightly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day))) |
snapshotLocation :: HasPantryConfig env => SnapName -> RIO env RawSnapshotLocation Source #
Get the location of a snapshot synonym from the PantryConfig
.
Since: 0.5.0.0
Loading values
Resolve all of the file paths in an Unresolved
relative to the
given directory.
Since: 0.1.0.0
loadPackageRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env Package Source #
Load a Package
from a RawPackageLocationImmutable
.
Load the package either from the local DB, Casa, or as a last resort, the third party (hackage, archive or repo).
Since: 0.1.0.0
tryLoadPackageRawViaCasa :: (HasLogFunc env, HasPantryConfig env, HasProcessContext env) => RawPackageLocationImmutable -> TreeKey -> RIO env (Maybe Package) Source #
Maybe load the package from Casa.
loadPackage :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env Package Source #
Load a Package
from a PackageLocationImmutable
.
Since: 0.1.0.0
loadRawSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env (Either WantedCompiler (RawSnapshotLayer, CompletedSL)) Source #
Parse a SnapshotLayer
value from a SnapshotLocation
.
Returns a Left
value if provided an SLCompiler
constructor. Otherwise, returns a Right
value providing both the
Snapshot
and a hash of the input configuration file.
Since: 0.1.0.0
loadSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => SnapshotLocation -> RIO env (Either WantedCompiler RawSnapshotLayer) Source #
Parse a SnapshotLayer
value from a SnapshotLocation
.
Returns a Left
value if provided an SLCompiler
constructor. Otherwise, returns a Right
value providing both the
Snapshot
and a hash of the input configuration file.
Since: 0.1.0.0
loadSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => SnapshotLocation -> RIO env RawSnapshot Source #
Parse a RawSnapshot
(all layers) from a SnapshotLocation
.
Since: 0.1.0.0
loadAndCompleteSnapshot Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> SnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
Parse a Snapshot
(all layers) from a SnapshotLocation
noting
any incomplete package locations. Debug output will include the raw snapshot
layer.
Since: 0.1.0.0
loadAndCompleteSnapshot' Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Bool | Debug output includes the raw snapshot layer |
-> SnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
As for loadAndCompleteSnapshot
but allows toggling of the debug output of
the raw snapshot layer.
Since: 0.5.7
loadAndCompleteSnapshotRaw Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RawSnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
Parse a Snapshot
(all layers) from a RawSnapshotLocation
completing
any incomplete package locations. Debug output will include the raw snapshot
layer.
Since: 0.1.0.0
loadAndCompleteSnapshotRaw' Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Bool | Debug output includes the raw snapshot layer |
-> RawSnapshotLocation | |
-> Map RawSnapshotLocation SnapshotLocation | Cached snapshot locations from lock file |
-> Map RawPackageLocationImmutable PackageLocationImmutable | Cached locations from lock file |
-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) |
As for loadAndCompleteSnapshotRaw
but allows toggling of the debug output
of the raw snapshot layer.
Since: 0.5.7
data CompletedSL Source #
A completed snapshot location, including the original raw and completed information.
Since: 0.1.0.0
data CompletedPLI Source #
A completed package location, including the original raw and completed information.
Since: 0.1.0.0
addPackagesToSnapshot Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Utf8Builder | Text description of where these new packages are coming from, for error messages only |
-> [RawPackageLocationImmutable] | new packages |
-> AddPackagesConfig | |
-> Map PackageName RawSnapshotPackage | packages from parent |
-> RIO env (Map PackageName RawSnapshotPackage, AddPackagesConfig) |
Add more packages to a snapshot
Note that any settings on a parent flag which is being replaced will be
ignored. For example, if package foo
is in the parent and has flag bar
set, and foo
also appears in new packages, then bar
will no longer be
set.
Returns any of the AddPackagesConfig
values not used.
Since: 0.1.0.0
data AddPackagesConfig Source #
Package settings to be passed to addPackagesToSnapshot
.
Since: 0.1.0.0
AddPackagesConfig | |
|
Completion functions
data CompletePackageLocation Source #
Complete package location, plus whether the package has a cabal file. This is relevant to reproducibility, see https://tech.fpcomplete.com/blog/storing-generated-cabal-files
Since: 0.4.0.0
completePackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env CompletePackageLocation Source #
Fill in optional fields in a PackageLocationImmutable
for more reproducible builds.
Since: 0.1.0.0
completeSnapshotLocation :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env SnapshotLocation Source #
Add in hashes to make a SnapshotLocation
reproducible.
Since: 0.1.0.0
warnMissingCabalFile :: HasLogFunc env => RawPackageLocationImmutable -> RIO env () Source #
Warn if the package uses PCHpack
.
Since: 0.4.0.0
Parsers
parseWantedCompiler :: Text -> Either PantryException WantedCompiler Source #
Parse a Text
into a WantedCompiler
value.
Since: 0.1.0.0
parseSnapName :: MonadThrow m => Text -> m SnapName Source #
Parse the short representation of a SnapName
.
Since: 0.5.0.0
parseRawSnapshotLocation :: Text -> Unresolved RawSnapshotLocation Source #
Parse a Text
into an Unresolved
RawSnapshotLocation
.
Since: 0.1.0.0
parsePackageIdentifierRevision :: Text -> Either PantryException PackageIdentifierRevision Source #
Parse a PackageIdentifierRevision
Since: 0.1.0.0
parseHackageText :: Text -> Either PantryException (PackageIdentifier, BlobKey) Source #
Parse a hackage text.
Since: 0.1.0.0
Cabal values
parsePackageIdentifier :: String -> Maybe PackageIdentifier Source #
This is almost a copy of Cabal's parser for package identifiers, the main difference is in the fact that Stack requires version to be present while Cabal uses "null version" as a default value
Since: 0.1.0.0
parsePackageName :: String -> Maybe PackageName Source #
Parse a package name from a Value
.
Since: 0.1.0.0
parsePackageNameThrowing :: MonadThrow m => String -> m PackageName Source #
Parse a package name from a Value
throwing on failure
Since: 0.1.0.0
parseVersionThrowing :: MonadThrow m => String -> m Version Source #
Parse a package version from a Value
throwing on failure
Since: 0.1.0.0
Cabal helpers
packageIdentifierString :: PackageIdentifier -> String Source #
Render a package identifier as a Value
.
Since: 0.1.0.0
packageNameString :: PackageName -> String Source #
Render a package name as a Value
.
Since: 0.1.0.0
moduleNameString :: ModuleName -> String Source #
Render a module name as a Value
.
Since: 0.1.0.0
newtype CabalString a Source #
Newtype wrapper for easier JSON integration with Cabal types.
Since: 0.1.0.0
CabalString | |
|
Instances
toCabalStringMap :: Map a v -> Map (CabalString a) v Source #
Wrap the keys in a Map
with a CabalString
to get a ToJSON
instance.
Since: 0.1.0.0
unCabalStringMap :: Map (CabalString a) v -> Map a v Source #
Unwrap the CabalString
from the keys in a Map
to use a
FromJSON
instance.
Since: 0.1.0.0
gpdPackageIdentifier :: GenericPackageDescription -> PackageIdentifier Source #
Get the PackageIdentifier
from a GenericPackageDescription
.
Since: 0.1.0.0
gpdPackageName :: GenericPackageDescription -> PackageName Source #
Get the PackageName
from a GenericPackageDescription
.
Since: 0.1.0.0
gpdVersion :: GenericPackageDescription -> Version Source #
Get the Version
from a GenericPackageDescription
.
Since: 0.1.0.0
Package location
fetchPackages :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env, Foldable f) => f PackageLocationImmutable -> RIO env () Source #
Download all of the packages provided into the local cache without performing any unpacking. Can be useful for build tools wanting to prefetch or provide an offline mode.
Since: 0.1.0.0
unpackPackageLocationRaw Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Path Abs Dir | unpack directory |
-> RawPackageLocationImmutable | |
-> RIO env () |
Unpack a given RawPackageLocationImmutable
into the given
directory. Does not generate any extra subdirectories.
Since: 0.1.0.0
unpackPackageLocation Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Path Abs Dir | unpack directory |
-> PackageLocationImmutable | |
-> RIO env () |
Unpack a given PackageLocationImmutable
into the given
directory. Does not generate any extra subdirectories.
Since: 0.1.0.0
getPackageLocationName :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageName Source #
Get the PackageName
of the package at the given location.
Since: 0.1.0.0
getRawPackageLocationIdent :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageIdentifier Source #
Get the PackageIdentifier
of the package at the given location.
Since: 0.1.0.0
packageLocationIdent :: PackageLocationImmutable -> PackageIdentifier Source #
Get the PackageIdentifier
of the package at the given location.
Since: 0.1.0.0
packageLocationVersion :: PackageLocationImmutable -> Version Source #
Get version of the package at the given location.
Since: 0.1.0.0
getRawPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env TreeKey Source #
Get the TreeKey
of the package at the given location.
Since: 0.1.0.0
getPackageLocationTreeKey :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env TreeKey Source #
Get the TreeKey
of the package at the given location.
Since: 0.1.0.0
Cabal files
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> RawPackageLocation | |
-> RIO env GenericPackageDescription |
Same as loadCabalFileRawImmutable
, but takes a RawPackageLocation
.
Never prints warnings, see loadCabalFilePath
for that.
Since: 0.8.0
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> PackageLocation | |
-> RIO env GenericPackageDescription |
Same as loadCabalFileImmutable
, but takes a PackageLocation
. Never
prints warnings, see loadCabalFilePath
for that.
Since: 0.8.0
loadCabalFileRawImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env GenericPackageDescription Source #
Load the cabal file for the given RawPackageLocationImmutable
.
This function ignores all warnings.
Note that, for now, this will not allow support for hpack files in
these package locations. Instead, all PackageLocationImmutable
s
will require a .cabal file. This may be relaxed in the future.
Since: 0.1.0.0
loadCabalFileImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env GenericPackageDescription Source #
Load the cabal file for the given PackageLocationImmutable
.
This function ignores all warnings.
Since: 0.1.0.0
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> Path Abs Dir | project directory, with a cabal file or hpack file |
-> RIO env (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File) |
Parse the Cabal file for the package inside the given directory. Performs various sanity checks, such as the file name being correct and having only a single Cabal file.
Since: 0.8.0
findOrGenerateCabalFile Source #
:: forall env. (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> Maybe Text | The program name used by Hpack (the library), defaults to "hpack". |
-> Path Abs Dir | package directory |
-> RIO env (PackageName, Path Abs File) |
Get the file name for the Cabal file in the given directory.
If no Cabal file is present, or more than one is present, an exception is
thrown via throwM
.
If the directory contains a file named package.yaml, Hpack is used to generate a Cabal file from it.
Since: 0.8.0
data PrintWarnings Source #
Should we print warnings when loading a cabal file?
Since: 0.1.0.0
Hackage index
:: (HasPantryConfig env, HasLogFunc env) | |
=> Maybe Utf8Builder | reason for updating, if any |
-> RIO env DidUpdateOccur |
Download the most recent 01-index.tar file from Hackage and update the database tables.
This function will only perform an update once per PantryConfig
for user sanity. See the return value to find out if it happened.
Since: 0.1.0.0
data DidUpdateOccur Source #
Did an update occur when running updateHackageIndex
?
Since: 0.1.0.0
data RequireHackageIndex Source #
Require that the Hackage index is populated.
Since: 0.1.0.0
YesRequireHackageIndex | If there is nothing in the Hackage index, then perform an update |
NoRequireHackageIndex | Do not perform an update |
Instances
Show RequireHackageIndex Source # | |
Defined in Pantry.Hackage showsPrec :: Int -> RequireHackageIndex -> ShowS # show :: RequireHackageIndex -> String # showList :: [RequireHackageIndex] -> ShowS # |
hackageIndexTarballL :: HasPantryConfig env => SimpleGetter env (Path Abs File) Source #
Where does pantry download its 01-index.tar file from Hackage?
Since: 0.1.0.0
getHackagePackageVersions Source #
:: (HasPantryConfig env, HasLogFunc env) | |
=> RequireHackageIndex | |
-> UsePreferredVersions | |
-> PackageName | package name |
-> RIO env (Map Version (Map Revision BlobKey)) |
Returns the versions of the package available on Hackage.
Since: 0.1.0.0
getLatestHackageVersion Source #
:: (HasPantryConfig env, HasLogFunc env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> UsePreferredVersions | |
-> RIO env (Maybe PackageIdentifierRevision) |
Returns the latest version of the given package available from Hackage.
Since: 0.1.0.0
getLatestHackageLocation Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> UsePreferredVersions | |
-> RIO env (Maybe PackageLocationImmutable) |
Returns location of the latest version of the given package available from Hackage.
Since: 0.1.0.0
getLatestHackageRevision Source #
:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) | |
=> RequireHackageIndex | |
-> PackageName | package name |
-> Version | |
-> RIO env (Maybe (Revision, BlobKey, TreeKey)) |
Returns the latest revision of the given package version available from Hackage.
Since: 0.1.0.0
getHackageTypoCorrections :: (HasPantryConfig env, HasLogFunc env) => PackageName -> RIO env [PackageName] Source #
Try to come up with typo corrections for given package identifier using Hackage package names. This can provide more user-friendly information in error messages.
Since: 0.1.0.0
loadGlobalHints :: (HasTerm env, HasPantryConfig env) => WantedCompiler -> RIO env (Maybe (Map PackageName Version)) Source #
Load the global hints from GitHub.
Since: 0.1.0.0
partitionReplacedDependencies Source #
:: Ord id | |
=> Map PackageName a | global packages |
-> (a -> PackageName) | package name getter |
-> (a -> id) | returns unique package id used for dependency pruning |
-> (a -> [id]) | returns unique package ids of direct package dependencies |
-> Set PackageName | overrides which global dependencies should get pruned |
-> (Map PackageName [PackageName], Map PackageName a) |
Partition a map of global packages with its versions into a Set of replaced packages and its dependencies and a map of remaining (untouched) packages.
Since: 0.1.0.0
Snapshot cache
newtype SnapshotCacheHash Source #
An arbitrary hash for a snapshot, used for finding module names in a snapshot. Mostly intended for Stack's usage.
Since: 0.1.0.0
Instances
Show SnapshotCacheHash Source # | |
Defined in Pantry.Types showsPrec :: Int -> SnapshotCacheHash -> ShowS # show :: SnapshotCacheHash -> String # showList :: [SnapshotCacheHash] -> ShowS # |
withSnapshotCache :: (HasPantryConfig env, HasLogFunc env) => SnapshotCacheHash -> RIO env (Map PackageName (Set ModuleName)) -> ((ModuleName -> RIO env [PackageName]) -> RIO env a) -> RIO env a Source #
Use a snapshot cache, which caches which modules are in which packages in a given snapshot. This is mostly intended for usage by Stack.
Since: 0.1.0.0